{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A helper widget for setting a window\'s title and subtitle.
-- 
-- \<picture>
--   \<source srcset=\"window-title-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"window-title.png\" alt=\"window-title\">
-- \<\/picture>
-- 
-- @AdwWindowTitle@ shows a title and subtitle. It\'s intended to be used as the
-- title child of t'GI.Gtk.Objects.HeaderBar.HeaderBar' or [class/@headerBar@/].
-- 
-- == CSS nodes
-- 
-- @AdwWindowTitle@ has a single CSS node with name @windowtitle@.

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

module GI.Adw.Objects.WindowTitle
    ( 

-- * Exported types
    WindowTitle(..)                         ,
    IsWindowTitle                           ,
    toWindowTitle                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getSubtitle]("GI.Adw.Objects.WindowTitle#g:method:getSubtitle"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTitle]("GI.Adw.Objects.WindowTitle#g:method:getTitle"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setSubtitle]("GI.Adw.Objects.WindowTitle#g:method:setSubtitle"), [setTitle]("GI.Adw.Objects.WindowTitle#g:method:setTitle"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveWindowTitleMethod                ,
#endif

-- ** getSubtitle #method:getSubtitle#

#if defined(ENABLE_OVERLOADING)
    WindowTitleGetSubtitleMethodInfo        ,
#endif
    windowTitleGetSubtitle                  ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    WindowTitleGetTitleMethodInfo           ,
#endif
    windowTitleGetTitle                     ,


-- ** new #method:new#

    windowTitleNew                          ,


-- ** setSubtitle #method:setSubtitle#

#if defined(ENABLE_OVERLOADING)
    WindowTitleSetSubtitleMethodInfo        ,
#endif
    windowTitleSetSubtitle                  ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    WindowTitleSetTitleMethodInfo           ,
#endif
    windowTitleSetTitle                     ,




 -- * Properties


-- ** subtitle #attr:subtitle#
-- | The subtitle to display.
-- 
-- The subtitle should give the user additional details.

#if defined(ENABLE_OVERLOADING)
    WindowTitleSubtitlePropertyInfo         ,
#endif
    constructWindowTitleSubtitle            ,
    getWindowTitleSubtitle                  ,
    setWindowTitleSubtitle                  ,
#if defined(ENABLE_OVERLOADING)
    windowTitleSubtitle                     ,
#endif


-- ** title #attr:title#
-- | The title to display.
-- 
-- The title typically identifies the current view or content item, and
-- generally does not use the application name.

#if defined(ENABLE_OVERLOADING)
    WindowTitleTitlePropertyInfo            ,
#endif
    constructWindowTitleTitle               ,
    getWindowTitleTitle                     ,
    setWindowTitleTitle                     ,
#if defined(ENABLE_OVERLOADING)
    windowTitleTitle                        ,
#endif




    ) 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "adw_window_title_get_type"
    c_adw_window_title_get_type :: IO B.Types.GType

instance B.Types.TypedObject WindowTitle where
    glibType :: IO GType
glibType = IO GType
c_adw_window_title_get_type

instance B.Types.GObject WindowTitle

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

instance O.HasParentTypes WindowTitle
type instance O.ParentTypes WindowTitle = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveWindowTitleMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWindowTitleMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveWindowTitleMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveWindowTitleMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveWindowTitleMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveWindowTitleMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveWindowTitleMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveWindowTitleMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveWindowTitleMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveWindowTitleMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveWindowTitleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveWindowTitleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveWindowTitleMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveWindowTitleMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveWindowTitleMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveWindowTitleMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveWindowTitleMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveWindowTitleMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveWindowTitleMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveWindowTitleMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveWindowTitleMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveWindowTitleMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveWindowTitleMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveWindowTitleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveWindowTitleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveWindowTitleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveWindowTitleMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveWindowTitleMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveWindowTitleMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveWindowTitleMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveWindowTitleMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveWindowTitleMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveWindowTitleMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveWindowTitleMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveWindowTitleMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveWindowTitleMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveWindowTitleMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveWindowTitleMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveWindowTitleMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveWindowTitleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveWindowTitleMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveWindowTitleMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveWindowTitleMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveWindowTitleMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveWindowTitleMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveWindowTitleMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveWindowTitleMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveWindowTitleMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveWindowTitleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveWindowTitleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveWindowTitleMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveWindowTitleMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveWindowTitleMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveWindowTitleMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveWindowTitleMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveWindowTitleMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveWindowTitleMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveWindowTitleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveWindowTitleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveWindowTitleMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveWindowTitleMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveWindowTitleMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveWindowTitleMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveWindowTitleMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveWindowTitleMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveWindowTitleMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveWindowTitleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveWindowTitleMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveWindowTitleMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveWindowTitleMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveWindowTitleMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveWindowTitleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveWindowTitleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveWindowTitleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveWindowTitleMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveWindowTitleMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveWindowTitleMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveWindowTitleMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveWindowTitleMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveWindowTitleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveWindowTitleMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveWindowTitleMethod "updateNextAccessibleSibling" o = Gtk.Accessible.AccessibleUpdateNextAccessibleSiblingMethodInfo
    ResolveWindowTitleMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveWindowTitleMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveWindowTitleMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveWindowTitleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveWindowTitleMethod "getAccessibleParent" o = Gtk.Accessible.AccessibleGetAccessibleParentMethodInfo
    ResolveWindowTitleMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveWindowTitleMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveWindowTitleMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveWindowTitleMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveWindowTitleMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveWindowTitleMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveWindowTitleMethod "getAtContext" o = Gtk.Accessible.AccessibleGetAtContextMethodInfo
    ResolveWindowTitleMethod "getBounds" o = Gtk.Accessible.AccessibleGetBoundsMethodInfo
    ResolveWindowTitleMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveWindowTitleMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveWindowTitleMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveWindowTitleMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveWindowTitleMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveWindowTitleMethod "getColor" o = Gtk.Widget.WidgetGetColorMethodInfo
    ResolveWindowTitleMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveWindowTitleMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveWindowTitleMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveWindowTitleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveWindowTitleMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveWindowTitleMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveWindowTitleMethod "getFirstAccessibleChild" o = Gtk.Accessible.AccessibleGetFirstAccessibleChildMethodInfo
    ResolveWindowTitleMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveWindowTitleMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveWindowTitleMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveWindowTitleMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveWindowTitleMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveWindowTitleMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveWindowTitleMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveWindowTitleMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveWindowTitleMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveWindowTitleMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveWindowTitleMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveWindowTitleMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveWindowTitleMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveWindowTitleMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveWindowTitleMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveWindowTitleMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveWindowTitleMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveWindowTitleMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveWindowTitleMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveWindowTitleMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveWindowTitleMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveWindowTitleMethod "getNextAccessibleSibling" o = Gtk.Accessible.AccessibleGetNextAccessibleSiblingMethodInfo
    ResolveWindowTitleMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveWindowTitleMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveWindowTitleMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveWindowTitleMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveWindowTitleMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveWindowTitleMethod "getPlatformState" o = Gtk.Accessible.AccessibleGetPlatformStateMethodInfo
    ResolveWindowTitleMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveWindowTitleMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveWindowTitleMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveWindowTitleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveWindowTitleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveWindowTitleMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveWindowTitleMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveWindowTitleMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveWindowTitleMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveWindowTitleMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveWindowTitleMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveWindowTitleMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveWindowTitleMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveWindowTitleMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveWindowTitleMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveWindowTitleMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveWindowTitleMethod "getSubtitle" o = WindowTitleGetSubtitleMethodInfo
    ResolveWindowTitleMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveWindowTitleMethod "getTitle" o = WindowTitleGetTitleMethodInfo
    ResolveWindowTitleMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveWindowTitleMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveWindowTitleMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveWindowTitleMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveWindowTitleMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveWindowTitleMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveWindowTitleMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveWindowTitleMethod "setAccessibleParent" o = Gtk.Accessible.AccessibleSetAccessibleParentMethodInfo
    ResolveWindowTitleMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveWindowTitleMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveWindowTitleMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveWindowTitleMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveWindowTitleMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveWindowTitleMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveWindowTitleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveWindowTitleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveWindowTitleMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveWindowTitleMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveWindowTitleMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveWindowTitleMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveWindowTitleMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveWindowTitleMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveWindowTitleMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveWindowTitleMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveWindowTitleMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveWindowTitleMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveWindowTitleMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveWindowTitleMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveWindowTitleMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveWindowTitleMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveWindowTitleMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveWindowTitleMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveWindowTitleMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveWindowTitleMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveWindowTitleMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveWindowTitleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveWindowTitleMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveWindowTitleMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveWindowTitleMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveWindowTitleMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveWindowTitleMethod "setSubtitle" o = WindowTitleSetSubtitleMethodInfo
    ResolveWindowTitleMethod "setTitle" o = WindowTitleSetTitleMethodInfo
    ResolveWindowTitleMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveWindowTitleMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveWindowTitleMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveWindowTitleMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveWindowTitleMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveWindowTitleMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveWindowTitleMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "subtitle"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@subtitle@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' windowTitle #subtitle
-- @
getWindowTitleSubtitle :: (MonadIO m, IsWindowTitle o) => o -> m T.Text
getWindowTitleSubtitle :: forall (m :: * -> *) o. (MonadIO m, IsWindowTitle o) => o -> m Text
getWindowTitleSubtitle o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getWindowTitleSubtitle" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"subtitle"

-- | Set the value of the “@subtitle@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' windowTitle [ #subtitle 'Data.GI.Base.Attributes.:=' value ]
-- @
setWindowTitleSubtitle :: (MonadIO m, IsWindowTitle o) => o -> T.Text -> m ()
setWindowTitleSubtitle :: forall (m :: * -> *) o.
(MonadIO m, IsWindowTitle o) =>
o -> Text -> m ()
setWindowTitleSubtitle o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"subtitle" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@subtitle@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWindowTitleSubtitle :: (IsWindowTitle o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWindowTitleSubtitle :: forall o (m :: * -> *).
(IsWindowTitle o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWindowTitleSubtitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"subtitle" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data WindowTitleSubtitlePropertyInfo
instance AttrInfo WindowTitleSubtitlePropertyInfo where
    type AttrAllowedOps WindowTitleSubtitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint WindowTitleSubtitlePropertyInfo = IsWindowTitle
    type AttrSetTypeConstraint WindowTitleSubtitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint WindowTitleSubtitlePropertyInfo = (~) T.Text
    type AttrTransferType WindowTitleSubtitlePropertyInfo = T.Text
    type AttrGetType WindowTitleSubtitlePropertyInfo = T.Text
    type AttrLabel WindowTitleSubtitlePropertyInfo = "subtitle"
    type AttrOrigin WindowTitleSubtitlePropertyInfo = WindowTitle
    attrGet = getWindowTitleSubtitle
    attrSet = setWindowTitleSubtitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructWindowTitleSubtitle
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.subtitle"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#g:attr:subtitle"
        })
#endif

-- VVV Prop "title"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' windowTitle #title
-- @
getWindowTitleTitle :: (MonadIO m, IsWindowTitle o) => o -> m T.Text
getWindowTitleTitle :: forall (m :: * -> *) o. (MonadIO m, IsWindowTitle o) => o -> m Text
getWindowTitleTitle o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getWindowTitleTitle" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"title"

-- | Set the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' windowTitle [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setWindowTitleTitle :: (MonadIO m, IsWindowTitle o) => o -> T.Text -> m ()
setWindowTitleTitle :: forall (m :: * -> *) o.
(MonadIO m, IsWindowTitle o) =>
o -> Text -> m ()
setWindowTitleTitle o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@title@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWindowTitleTitle :: (IsWindowTitle o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWindowTitleTitle :: forall o (m :: * -> *).
(IsWindowTitle o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWindowTitleTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data WindowTitleTitlePropertyInfo
instance AttrInfo WindowTitleTitlePropertyInfo where
    type AttrAllowedOps WindowTitleTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint WindowTitleTitlePropertyInfo = IsWindowTitle
    type AttrSetTypeConstraint WindowTitleTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint WindowTitleTitlePropertyInfo = (~) T.Text
    type AttrTransferType WindowTitleTitlePropertyInfo = T.Text
    type AttrGetType WindowTitleTitlePropertyInfo = T.Text
    type AttrLabel WindowTitleTitlePropertyInfo = "title"
    type AttrOrigin WindowTitleTitlePropertyInfo = WindowTitle
    attrGet = getWindowTitleTitle
    attrSet = setWindowTitleTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructWindowTitleTitle
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.title"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#g:attr:title"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WindowTitle
type instance O.AttributeList WindowTitle = WindowTitleAttributeList
type WindowTitleAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("subtitle", WindowTitleSubtitlePropertyInfo), '("title", WindowTitleTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
windowTitleSubtitle :: AttrLabelProxy "subtitle"
windowTitleSubtitle = AttrLabelProxy

windowTitleTitle :: AttrLabelProxy "title"
windowTitleTitle = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList WindowTitle = WindowTitleSignalList
type WindowTitleSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method WindowTitle::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a title" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "subtitle"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a subtitle" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Adw" , name = "WindowTitle" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_window_title_new" adw_window_title_new :: 
    CString ->                              -- title : TBasicType TUTF8
    CString ->                              -- subtitle : TBasicType TUTF8
    IO (Ptr WindowTitle)

-- | Creates a new @AdwWindowTitle@.
windowTitleNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@title@/: a title
    -> T.Text
    -- ^ /@subtitle@/: a subtitle
    -> m WindowTitle
    -- ^ __Returns:__ the newly created @AdwWindowTitle@
windowTitleNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> m WindowTitle
windowTitleNew Text
title Text
subtitle = IO WindowTitle -> m WindowTitle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowTitle -> m WindowTitle)
-> IO WindowTitle -> m WindowTitle
forall a b. (a -> b) -> a -> b
$ do
    CString
title' <- Text -> IO CString
textToCString Text
title
    CString
subtitle' <- Text -> IO CString
textToCString Text
subtitle
    Ptr WindowTitle
result <- CString -> CString -> IO (Ptr WindowTitle)
adw_window_title_new CString
title' CString
subtitle'
    Text -> Ptr WindowTitle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"windowTitleNew" Ptr WindowTitle
result
    WindowTitle
result' <- ((ManagedPtr WindowTitle -> WindowTitle)
-> Ptr WindowTitle -> IO WindowTitle
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WindowTitle -> WindowTitle
WindowTitle) Ptr WindowTitle
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
subtitle'
    WindowTitle -> IO WindowTitle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WindowTitle
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method WindowTitle::get_subtitle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "WindowTitle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window title" , 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 "adw_window_title_get_subtitle" adw_window_title_get_subtitle :: 
    Ptr WindowTitle ->                      -- self : TInterface (Name {namespace = "Adw", name = "WindowTitle"})
    IO CString

-- | Gets the subtitle of /@self@/.
windowTitleGetSubtitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowTitle a) =>
    a
    -- ^ /@self@/: a window title
    -> m T.Text
    -- ^ __Returns:__ the subtitle
windowTitleGetSubtitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowTitle a) =>
a -> m Text
windowTitleGetSubtitle a
self = IO Text -> m Text
forall a. IO a -> m a
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 WindowTitle
self' <- a -> IO (Ptr WindowTitle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr WindowTitle -> IO CString
adw_window_title_get_subtitle Ptr WindowTitle
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"windowTitleGetSubtitle" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WindowTitleGetSubtitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWindowTitle a) => O.OverloadedMethod WindowTitleGetSubtitleMethodInfo a signature where
    overloadedMethod = windowTitleGetSubtitle

instance O.OverloadedMethodInfo WindowTitleGetSubtitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.windowTitleGetSubtitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#v:windowTitleGetSubtitle"
        })


#endif

-- method WindowTitle::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "WindowTitle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window title" , 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 "adw_window_title_get_title" adw_window_title_get_title :: 
    Ptr WindowTitle ->                      -- self : TInterface (Name {namespace = "Adw", name = "WindowTitle"})
    IO CString

-- | Gets the title of /@self@/.
windowTitleGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowTitle a) =>
    a
    -- ^ /@self@/: a window title
    -> m T.Text
    -- ^ __Returns:__ the title
windowTitleGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowTitle a) =>
a -> m Text
windowTitleGetTitle a
self = IO Text -> m Text
forall a. IO a -> m a
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 WindowTitle
self' <- a -> IO (Ptr WindowTitle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr WindowTitle -> IO CString
adw_window_title_get_title Ptr WindowTitle
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"windowTitleGetTitle" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WindowTitleGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsWindowTitle a) => O.OverloadedMethod WindowTitleGetTitleMethodInfo a signature where
    overloadedMethod = windowTitleGetTitle

instance O.OverloadedMethodInfo WindowTitleGetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.windowTitleGetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#v:windowTitleGetTitle"
        })


#endif

-- method WindowTitle::set_subtitle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "WindowTitle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window title" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "subtitle"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a subtitle" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_window_title_set_subtitle" adw_window_title_set_subtitle :: 
    Ptr WindowTitle ->                      -- self : TInterface (Name {namespace = "Adw", name = "WindowTitle"})
    CString ->                              -- subtitle : TBasicType TUTF8
    IO ()

-- | Sets the subtitle of /@self@/.
-- 
-- The subtitle should give the user additional details.
windowTitleSetSubtitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowTitle a) =>
    a
    -- ^ /@self@/: a window title
    -> T.Text
    -- ^ /@subtitle@/: a subtitle
    -> m ()
windowTitleSetSubtitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowTitle a) =>
a -> Text -> m ()
windowTitleSetSubtitle a
self Text
subtitle = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowTitle
self' <- a -> IO (Ptr WindowTitle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
subtitle' <- Text -> IO CString
textToCString Text
subtitle
    Ptr WindowTitle -> CString -> IO ()
adw_window_title_set_subtitle Ptr WindowTitle
self' CString
subtitle'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
subtitle'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WindowTitleSetSubtitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsWindowTitle a) => O.OverloadedMethod WindowTitleSetSubtitleMethodInfo a signature where
    overloadedMethod = windowTitleSetSubtitle

instance O.OverloadedMethodInfo WindowTitleSetSubtitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.windowTitleSetSubtitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#v:windowTitleSetSubtitle"
        })


#endif

-- method WindowTitle::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "WindowTitle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a window title" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a title" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_window_title_set_title" adw_window_title_set_title :: 
    Ptr WindowTitle ->                      -- self : TInterface (Name {namespace = "Adw", name = "WindowTitle"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title of /@self@/.
-- 
-- The title typically identifies the current view or content item, and
-- generally does not use the application name.
windowTitleSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowTitle a) =>
    a
    -- ^ /@self@/: a window title
    -> T.Text
    -- ^ /@title@/: a title
    -> m ()
windowTitleSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowTitle a) =>
a -> Text -> m ()
windowTitleSetTitle a
self Text
title = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowTitle
self' <- a -> IO (Ptr WindowTitle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr WindowTitle -> CString -> IO ()
adw_window_title_set_title Ptr WindowTitle
self' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WindowTitleSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsWindowTitle a) => O.OverloadedMethod WindowTitleSetTitleMethodInfo a signature where
    overloadedMethod = windowTitleSetTitle

instance O.OverloadedMethodInfo WindowTitleSetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.WindowTitle.windowTitleSetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.6/docs/GI-Adw-Objects-WindowTitle.html#v:windowTitleSetTitle"
        })


#endif