{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkWindowControls@ shows window frame controls.
-- 
-- Typical window frame controls are minimize, maximize and close buttons,
-- and the window icon.
-- 
-- <<https://docs.gtk.org/gtk4/windowcontrols.png An example GtkWindowControls>>
-- 
-- @GtkWindowControls@ only displays start or end side of the controls (see
-- [WindowControls:side]("GI.Gtk.Objects.WindowControls#g:attr:side")), so it\'s intended to be always used
-- in pair with another @GtkWindowControls@ for the opposite side, for example:
-- 
-- 
-- === /xml code/
-- ><object class="GtkBox">
-- >  <child>
-- >    <object class="GtkWindowControls">
-- >      <property name="side">start</property>
-- >    </object>
-- >  </child>
-- >
-- >  ...
-- >
-- >  <child>
-- >    <object class="GtkWindowControls">
-- >      <property name="side">end</property>
-- >    </object>
-- >  </child>
-- ></object>
-- 
-- 
-- = CSS nodes
-- 
-- >windowcontrols
-- >├── [image.icon]
-- >├── [button.minimize]
-- >├── [button.maximize]
-- >╰── [button.close]
-- 
-- 
-- A @GtkWindowControls@\' CSS node is called windowcontrols. It contains
-- subnodes corresponding to each title button. Which of the title buttons
-- exist and where they are placed exactly depends on the desktop environment
-- and [WindowControls:decorationLayout]("GI.Gtk.Objects.WindowControls#g:attr:decorationLayout") value.
-- 
-- When [WindowControls:empty]("GI.Gtk.Objects.WindowControls#g:attr:empty") is 'P.True', it gets the .empty
-- style class.
-- 
-- = Accessibility
-- 
-- @GtkWindowControls@ uses the 'GI.Gtk.Enums.AccessibleRoleGroup' role.

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

module GI.Gtk.Objects.WindowControls
    ( 

-- * Exported types
    WindowControls(..)                      ,
    IsWindowControls                        ,
    toWindowControls                        ,


 -- * 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"), [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
-- [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"), [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"), [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"), [getDecorationLayout]("GI.Gtk.Objects.WindowControls#g:method:getDecorationLayout"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getEmpty]("GI.Gtk.Objects.WindowControls#g:method:getEmpty"), [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"), [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"), [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"), [getSide]("GI.Gtk.Objects.WindowControls#g:method:getSide"), [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"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [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
-- [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"), [setDecorationLayout]("GI.Gtk.Objects.WindowControls#g:method:setDecorationLayout"), [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"), [setSide]("GI.Gtk.Objects.WindowControls#g:method:setSide"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [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)
    ResolveWindowControlsMethod             ,
#endif

-- ** getDecorationLayout #method:getDecorationLayout#

#if defined(ENABLE_OVERLOADING)
    WindowControlsGetDecorationLayoutMethodInfo,
#endif
    windowControlsGetDecorationLayout       ,


-- ** getEmpty #method:getEmpty#

#if defined(ENABLE_OVERLOADING)
    WindowControlsGetEmptyMethodInfo        ,
#endif
    windowControlsGetEmpty                  ,


-- ** getSide #method:getSide#

#if defined(ENABLE_OVERLOADING)
    WindowControlsGetSideMethodInfo         ,
#endif
    windowControlsGetSide                   ,


-- ** new #method:new#

    windowControlsNew                       ,


-- ** setDecorationLayout #method:setDecorationLayout#

#if defined(ENABLE_OVERLOADING)
    WindowControlsSetDecorationLayoutMethodInfo,
#endif
    windowControlsSetDecorationLayout       ,


-- ** setSide #method:setSide#

#if defined(ENABLE_OVERLOADING)
    WindowControlsSetSideMethodInfo         ,
#endif
    windowControlsSetSide                   ,




 -- * Properties


-- ** decorationLayout #attr:decorationLayout#
-- | The decoration layout for window buttons.
-- 
-- If this property is not set, the
-- [Settings:gtkDecorationLayout]("GI.Gtk.Objects.Settings#g:attr:gtkDecorationLayout") setting is used.

#if defined(ENABLE_OVERLOADING)
    WindowControlsDecorationLayoutPropertyInfo,
#endif
    clearWindowControlsDecorationLayout     ,
    constructWindowControlsDecorationLayout ,
    getWindowControlsDecorationLayout       ,
    setWindowControlsDecorationLayout       ,
#if defined(ENABLE_OVERLOADING)
    windowControlsDecorationLayout          ,
#endif


-- ** empty #attr:empty#
-- | Whether the widget has any window buttons.

#if defined(ENABLE_OVERLOADING)
    WindowControlsEmptyPropertyInfo         ,
#endif
    getWindowControlsEmpty                  ,
#if defined(ENABLE_OVERLOADING)
    windowControlsEmpty                     ,
#endif


-- ** side #attr:side#
-- | Whether the widget shows start or end side of the decoration layout.
-- 
-- See [property/@gtk@/.WindowControls:decoration_layout].

#if defined(ENABLE_OVERLOADING)
    WindowControlsSidePropertyInfo          ,
#endif
    constructWindowControlsSide             ,
    getWindowControlsSide                   ,
    setWindowControlsSide                   ,
#if defined(ENABLE_OVERLOADING)
    windowControlsSide                      ,
#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.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 {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_window_controls_get_type"
    c_gtk_window_controls_get_type :: IO B.Types.GType

instance B.Types.TypedObject WindowControls where
    glibType :: IO GType
glibType = IO GType
c_gtk_window_controls_get_type

instance B.Types.GObject WindowControls

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "decoration-layout"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@decoration-layout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' windowControls #decorationLayout
-- @
getWindowControlsDecorationLayout :: (MonadIO m, IsWindowControls o) => o -> m (Maybe T.Text)
getWindowControlsDecorationLayout :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> m (Maybe Text)
getWindowControlsDecorationLayout o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe 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
"decoration-layout"

-- | Set the value of the “@decoration-layout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' windowControls [ #decorationLayout 'Data.GI.Base.Attributes.:=' value ]
-- @
setWindowControlsDecorationLayout :: (MonadIO m, IsWindowControls o) => o -> T.Text -> m ()
setWindowControlsDecorationLayout :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> Text -> m ()
setWindowControlsDecorationLayout 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
"decoration-layout" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@decoration-layout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWindowControlsDecorationLayout :: (IsWindowControls o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructWindowControlsDecorationLayout :: forall o (m :: * -> *).
(IsWindowControls o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructWindowControlsDecorationLayout 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
"decoration-layout" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@decoration-layout@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #decorationLayout
-- @
clearWindowControlsDecorationLayout :: (MonadIO m, IsWindowControls o) => o -> m ()
clearWindowControlsDecorationLayout :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> m ()
clearWindowControlsDecorationLayout o
obj = 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
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"decoration-layout" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data WindowControlsDecorationLayoutPropertyInfo
instance AttrInfo WindowControlsDecorationLayoutPropertyInfo where
    type AttrAllowedOps WindowControlsDecorationLayoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint WindowControlsDecorationLayoutPropertyInfo = IsWindowControls
    type AttrSetTypeConstraint WindowControlsDecorationLayoutPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint WindowControlsDecorationLayoutPropertyInfo = (~) T.Text
    type AttrTransferType WindowControlsDecorationLayoutPropertyInfo = T.Text
    type AttrGetType WindowControlsDecorationLayoutPropertyInfo = (Maybe T.Text)
    type AttrLabel WindowControlsDecorationLayoutPropertyInfo = "decoration-layout"
    type AttrOrigin WindowControlsDecorationLayoutPropertyInfo = WindowControls
    attrGet = getWindowControlsDecorationLayout
    attrSet = setWindowControlsDecorationLayout
    attrTransfer _ v = do
        return v
    attrConstruct = constructWindowControlsDecorationLayout
    attrClear = clearWindowControlsDecorationLayout
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.decorationLayout"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#g:attr:decorationLayout"
        })
#endif

-- VVV Prop "empty"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@empty@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' windowControls #empty
-- @
getWindowControlsEmpty :: (MonadIO m, IsWindowControls o) => o -> m Bool
getWindowControlsEmpty :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> m Bool
getWindowControlsEmpty o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"empty"

#if defined(ENABLE_OVERLOADING)
data WindowControlsEmptyPropertyInfo
instance AttrInfo WindowControlsEmptyPropertyInfo where
    type AttrAllowedOps WindowControlsEmptyPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint WindowControlsEmptyPropertyInfo = IsWindowControls
    type AttrSetTypeConstraint WindowControlsEmptyPropertyInfo = (~) ()
    type AttrTransferTypeConstraint WindowControlsEmptyPropertyInfo = (~) ()
    type AttrTransferType WindowControlsEmptyPropertyInfo = ()
    type AttrGetType WindowControlsEmptyPropertyInfo = Bool
    type AttrLabel WindowControlsEmptyPropertyInfo = "empty"
    type AttrOrigin WindowControlsEmptyPropertyInfo = WindowControls
    attrGet = getWindowControlsEmpty
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.empty"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#g:attr:empty"
        })
#endif

-- VVV Prop "side"
   -- Type: TInterface (Name {namespace = "Gtk", name = "PackType"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@side@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' windowControls #side
-- @
getWindowControlsSide :: (MonadIO m, IsWindowControls o) => o -> m Gtk.Enums.PackType
getWindowControlsSide :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> m PackType
getWindowControlsSide o
obj = IO PackType -> m PackType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PackType -> m PackType) -> IO PackType -> m PackType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO PackType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"side"

-- | Set the value of the “@side@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' windowControls [ #side 'Data.GI.Base.Attributes.:=' value ]
-- @
setWindowControlsSide :: (MonadIO m, IsWindowControls o) => o -> Gtk.Enums.PackType -> m ()
setWindowControlsSide :: forall (m :: * -> *) o.
(MonadIO m, IsWindowControls o) =>
o -> PackType -> m ()
setWindowControlsSide o
obj PackType
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 -> PackType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"side" PackType
val

-- | Construct a `GValueConstruct` with valid value for the “@side@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructWindowControlsSide :: (IsWindowControls o, MIO.MonadIO m) => Gtk.Enums.PackType -> m (GValueConstruct o)
constructWindowControlsSide :: forall o (m :: * -> *).
(IsWindowControls o, MonadIO m) =>
PackType -> m (GValueConstruct o)
constructWindowControlsSide PackType
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 -> PackType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"side" PackType
val

#if defined(ENABLE_OVERLOADING)
data WindowControlsSidePropertyInfo
instance AttrInfo WindowControlsSidePropertyInfo where
    type AttrAllowedOps WindowControlsSidePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint WindowControlsSidePropertyInfo = IsWindowControls
    type AttrSetTypeConstraint WindowControlsSidePropertyInfo = (~) Gtk.Enums.PackType
    type AttrTransferTypeConstraint WindowControlsSidePropertyInfo = (~) Gtk.Enums.PackType
    type AttrTransferType WindowControlsSidePropertyInfo = Gtk.Enums.PackType
    type AttrGetType WindowControlsSidePropertyInfo = Gtk.Enums.PackType
    type AttrLabel WindowControlsSidePropertyInfo = "side"
    type AttrOrigin WindowControlsSidePropertyInfo = WindowControls
    attrGet = getWindowControlsSide
    attrSet = setWindowControlsSide
    attrTransfer _ v = do
        return v
    attrConstruct = constructWindowControlsSide
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.side"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#g:attr:side"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WindowControls
type instance O.AttributeList WindowControls = WindowControlsAttributeList
type WindowControlsAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("decorationLayout", WindowControlsDecorationLayoutPropertyInfo), '("empty", WindowControlsEmptyPropertyInfo), '("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), '("side", WindowControlsSidePropertyInfo), '("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, *)])
#endif

#if defined(ENABLE_OVERLOADING)
windowControlsDecorationLayout :: AttrLabelProxy "decorationLayout"
windowControlsDecorationLayout = AttrLabelProxy

windowControlsEmpty :: AttrLabelProxy "empty"
windowControlsEmpty = AttrLabelProxy

windowControlsSide :: AttrLabelProxy "side"
windowControlsSide = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList WindowControls = WindowControlsSignalList
type WindowControlsSignalList = ('[ '("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, *)])

#endif

-- method WindowControls::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "side"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PackType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the side" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "WindowControls" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_controls_new" gtk_window_controls_new :: 
    CUInt ->                                -- side : TInterface (Name {namespace = "Gtk", name = "PackType"})
    IO (Ptr WindowControls)

-- | Creates a new @GtkWindowControls@.
windowControlsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.Enums.PackType
    -- ^ /@side@/: the side
    -> m WindowControls
    -- ^ __Returns:__ a new @GtkWindowControls@.
windowControlsNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PackType -> m WindowControls
windowControlsNew PackType
side = IO WindowControls -> m WindowControls
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowControls -> m WindowControls)
-> IO WindowControls -> m WindowControls
forall a b. (a -> b) -> a -> b
$ do
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PackType -> Int) -> PackType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackType -> Int
forall a. Enum a => a -> Int
fromEnum) PackType
side
    Ptr WindowControls
result <- CUInt -> IO (Ptr WindowControls)
gtk_window_controls_new CUInt
side'
    Text -> Ptr WindowControls -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"windowControlsNew" Ptr WindowControls
result
    WindowControls
result' <- ((ManagedPtr WindowControls -> WindowControls)
-> Ptr WindowControls -> IO WindowControls
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr WindowControls -> WindowControls
WindowControls) Ptr WindowControls
result
    WindowControls -> IO WindowControls
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return WindowControls
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method WindowControls::get_decoration_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowControls" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWindowControls`"
--                 , 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 "gtk_window_controls_get_decoration_layout" gtk_window_controls_get_decoration_layout :: 
    Ptr WindowControls ->                   -- self : TInterface (Name {namespace = "Gtk", name = "WindowControls"})
    IO CString

-- | Gets the decoration layout of this @GtkWindowControls@.
windowControlsGetDecorationLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowControls a) =>
    a
    -- ^ /@self@/: a @GtkWindowControls@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the decoration layout or 'P.Nothing' if it is unset
windowControlsGetDecorationLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowControls a) =>
a -> m (Maybe Text)
windowControlsGetDecorationLayout a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowControls
self' <- a -> IO (Ptr WindowControls)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr WindowControls -> IO CString
gtk_window_controls_get_decoration_layout Ptr WindowControls
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data WindowControlsGetDecorationLayoutMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsWindowControls a) => O.OverloadedMethod WindowControlsGetDecorationLayoutMethodInfo a signature where
    overloadedMethod = windowControlsGetDecorationLayout

instance O.OverloadedMethodInfo WindowControlsGetDecorationLayoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.windowControlsGetDecorationLayout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#v:windowControlsGetDecorationLayout"
        })


#endif

-- method WindowControls::get_empty
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowControls" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWindowControls`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_controls_get_empty" gtk_window_controls_get_empty :: 
    Ptr WindowControls ->                   -- self : TInterface (Name {namespace = "Gtk", name = "WindowControls"})
    IO CInt

-- | Gets whether the widget has any window buttons.
windowControlsGetEmpty ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowControls a) =>
    a
    -- ^ /@self@/: a @GtkWindowControls@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget has window buttons, otherwise 'P.False'
windowControlsGetEmpty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowControls a) =>
a -> m Bool
windowControlsGetEmpty a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 WindowControls
self' <- a -> IO (Ptr WindowControls)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr WindowControls -> IO CInt
gtk_window_controls_get_empty Ptr WindowControls
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WindowControlsGetEmptyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsWindowControls a) => O.OverloadedMethod WindowControlsGetEmptyMethodInfo a signature where
    overloadedMethod = windowControlsGetEmpty

instance O.OverloadedMethodInfo WindowControlsGetEmptyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.windowControlsGetEmpty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#v:windowControlsGetEmpty"
        })


#endif

-- method WindowControls::get_side
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowControls" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWindowControls`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PackType" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_controls_get_side" gtk_window_controls_get_side :: 
    Ptr WindowControls ->                   -- self : TInterface (Name {namespace = "Gtk", name = "WindowControls"})
    IO CUInt

-- | Gets the side to which this @GtkWindowControls@ instance belongs.
windowControlsGetSide ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowControls a) =>
    a
    -- ^ /@self@/: a @GtkWindowControls@
    -> m Gtk.Enums.PackType
    -- ^ __Returns:__ the side
windowControlsGetSide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowControls a) =>
a -> m PackType
windowControlsGetSide a
self = IO PackType -> m PackType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PackType -> m PackType) -> IO PackType -> m PackType
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowControls
self' <- a -> IO (Ptr WindowControls)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr WindowControls -> IO CUInt
gtk_window_controls_get_side Ptr WindowControls
self'
    let result' :: PackType
result' = (Int -> PackType
forall a. Enum a => Int -> a
toEnum (Int -> PackType) -> (CUInt -> Int) -> CUInt -> PackType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    PackType -> IO PackType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PackType
result'

#if defined(ENABLE_OVERLOADING)
data WindowControlsGetSideMethodInfo
instance (signature ~ (m Gtk.Enums.PackType), MonadIO m, IsWindowControls a) => O.OverloadedMethod WindowControlsGetSideMethodInfo a signature where
    overloadedMethod = windowControlsGetSide

instance O.OverloadedMethodInfo WindowControlsGetSideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.windowControlsGetSide",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#v:windowControlsGetSide"
        })


#endif

-- method WindowControls::set_decoration_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowControls" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWindowControls`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layout"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a decoration layout, or %NULL to unset the layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_controls_set_decoration_layout" gtk_window_controls_set_decoration_layout :: 
    Ptr WindowControls ->                   -- self : TInterface (Name {namespace = "Gtk", name = "WindowControls"})
    CString ->                              -- layout : TBasicType TUTF8
    IO ()

-- | Sets the decoration layout for the title buttons.
-- 
-- This overrides the [Settings:gtkDecorationLayout]("GI.Gtk.Objects.Settings#g:attr:gtkDecorationLayout")
-- setting.
-- 
-- The format of the string is button names, separated by commas.
-- A colon separates the buttons that should appear on the left
-- from those on the right. Recognized button names are minimize,
-- maximize, close and icon (the window icon).
-- 
-- For example, “icon:minimize,maximize,close” specifies a icon
-- on the left, and minimize, maximize and close buttons on the right.
-- 
-- If [WindowControls:side]("GI.Gtk.Objects.WindowControls#g:attr:side") value is /@gTKPACKSTART@/, /@self@/
-- will display the part before the colon, otherwise after that.
windowControlsSetDecorationLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowControls a) =>
    a
    -- ^ /@self@/: a @GtkWindowControls@
    -> Maybe (T.Text)
    -- ^ /@layout@/: a decoration layout, or 'P.Nothing' to unset the layout
    -> m ()
windowControlsSetDecorationLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowControls a) =>
a -> Maybe Text -> m ()
windowControlsSetDecorationLayout a
self Maybe Text
layout = 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 WindowControls
self' <- a -> IO (Ptr WindowControls)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybeLayout <- case Maybe Text
layout of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLayout -> do
            CString
jLayout' <- Text -> IO CString
textToCString Text
jLayout
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLayout'
    Ptr WindowControls -> CString -> IO ()
gtk_window_controls_set_decoration_layout Ptr WindowControls
self' CString
maybeLayout
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLayout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WindowControlsSetDecorationLayoutMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsWindowControls a) => O.OverloadedMethod WindowControlsSetDecorationLayoutMethodInfo a signature where
    overloadedMethod = windowControlsSetDecorationLayout

instance O.OverloadedMethodInfo WindowControlsSetDecorationLayoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.windowControlsSetDecorationLayout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#v:windowControlsSetDecorationLayout"
        })


#endif

-- method WindowControls::set_side
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowControls" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWindowControls`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "side"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PackType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a side" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_controls_set_side" gtk_window_controls_set_side :: 
    Ptr WindowControls ->                   -- self : TInterface (Name {namespace = "Gtk", name = "WindowControls"})
    CUInt ->                                -- side : TInterface (Name {namespace = "Gtk", name = "PackType"})
    IO ()

-- | Determines which part of decoration layout the @GtkWindowControls@ uses.
-- 
-- See [WindowControls:decorationLayout]("GI.Gtk.Objects.WindowControls#g:attr:decorationLayout").
windowControlsSetSide ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowControls a) =>
    a
    -- ^ /@self@/: a @GtkWindowControls@
    -> Gtk.Enums.PackType
    -- ^ /@side@/: a side
    -> m ()
windowControlsSetSide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWindowControls a) =>
a -> PackType -> m ()
windowControlsSetSide a
self PackType
side = 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 WindowControls
self' <- a -> IO (Ptr WindowControls)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PackType -> Int) -> PackType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackType -> Int
forall a. Enum a => a -> Int
fromEnum) PackType
side
    Ptr WindowControls -> CUInt -> IO ()
gtk_window_controls_set_side Ptr WindowControls
self' CUInt
side'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WindowControlsSetSideMethodInfo
instance (signature ~ (Gtk.Enums.PackType -> m ()), MonadIO m, IsWindowControls a) => O.OverloadedMethod WindowControlsSetSideMethodInfo a signature where
    overloadedMethod = windowControlsSetSide

instance O.OverloadedMethodInfo WindowControlsSetSideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.WindowControls.windowControlsSetSide",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-WindowControls.html#v:windowControlsSetSide"
        })


#endif