{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkLockButton@ is a widget to obtain and revoke authorizations
-- needed to operate the controls.
-- 
-- <<https://docs.gtk.org/gtk4/lock-button.png An example GtkLockButton>>
-- 
-- It is typically used in preference dialogs or control panels.
-- 
-- The required authorization is represented by a @GPermission@ object.
-- Concrete implementations of @GPermission@ may use PolicyKit or some
-- other authorization framework. To obtain a PolicyKit-based
-- @GPermission@, use @polkit_permission_new()@.
-- 
-- If the user is not currently allowed to perform the action, but can
-- obtain the permission, the widget looks like this:
-- 
-- <<https://docs.gtk.org/gtk4/lockbutton-locked.png>>
-- 
-- and the user can click the button to request the permission. Depending
-- on the platform, this may pop up an authentication dialog or ask the user
-- to authenticate in some other way. Once the user has obtained the permission,
-- the widget changes to this:
-- 
-- <<https://docs.gtk.org/gtk4/lockbutton-unlocked.png>>
-- 
-- and the permission can be dropped again by clicking the button. If the user
-- is not able to obtain the permission at all, the widget looks like this:
-- 
-- <<https://docs.gtk.org/gtk4/lockbutton-sorry.png>>
-- 
-- If the user has the permission and cannot drop it, the button is hidden.
-- 
-- The text (and tooltips) that are shown in the various cases can be adjusted
-- with the [LockButton:textLock]("GI.Gtk.Objects.LockButton#g:attr:textLock"),
-- [LockButton:textUnlock]("GI.Gtk.Objects.LockButton#g:attr:textUnlock"),
-- [LockButton:tooltipLock]("GI.Gtk.Objects.LockButton#g:attr:tooltipLock"),
-- [LockButton:tooltipUnlock]("GI.Gtk.Objects.LockButton#g:attr:tooltipUnlock") and
-- [LockButton:tooltipNotAuthorized]("GI.Gtk.Objects.LockButton#g:attr:tooltipNotAuthorized") properties.

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

module GI.Gtk.Objects.LockButton
    ( 

-- * Exported types
    LockButton(..)                          ,
    IsLockButton                            ,
    toLockButton                            ,


 -- * 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"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [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"), [getChild]("GI.Gtk.Objects.Button#g:method:getChild"), [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"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [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"), [getHasFrame]("GI.Gtk.Objects.Button#g:method:getHasFrame"), [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"), [getIconName]("GI.Gtk.Objects.Button#g:method:getIconName"), [getLabel]("GI.Gtk.Objects.Button#g:method:getLabel"), [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"), [getPermission]("GI.Gtk.Objects.LockButton#g:method:getPermission"), [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"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getUseUnderline]("GI.Gtk.Objects.Button#g:method:getUseUnderline"), [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
-- [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChild]("GI.Gtk.Objects.Button#g:method:setChild"), [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"), [setDetailedActionName]("GI.Gtk.Interfaces.Actionable#g:method:setDetailedActionName"), [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"), [setHasFrame]("GI.Gtk.Objects.Button#g:method:setHasFrame"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Gtk.Objects.Button#g:method:setIconName"), [setLabel]("GI.Gtk.Objects.Button#g:method:setLabel"), [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"), [setPermission]("GI.Gtk.Objects.LockButton#g:method:setPermission"), [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"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setUseUnderline]("GI.Gtk.Objects.Button#g:method:setUseUnderline"), [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)
    ResolveLockButtonMethod                 ,
#endif

-- ** getPermission #method:getPermission#

#if defined(ENABLE_OVERLOADING)
    LockButtonGetPermissionMethodInfo       ,
#endif
    lockButtonGetPermission                 ,


-- ** new #method:new#

    lockButtonNew                           ,


-- ** setPermission #method:setPermission#

#if defined(ENABLE_OVERLOADING)
    LockButtonSetPermissionMethodInfo       ,
#endif
    lockButtonSetPermission                 ,




 -- * Properties


-- ** permission #attr:permission#
-- | The \`GPermission object controlling this button.

#if defined(ENABLE_OVERLOADING)
    LockButtonPermissionPropertyInfo        ,
#endif
    clearLockButtonPermission               ,
    constructLockButtonPermission           ,
    getLockButtonPermission                 ,
#if defined(ENABLE_OVERLOADING)
    lockButtonPermission                    ,
#endif
    setLockButtonPermission                 ,


-- ** textLock #attr:textLock#
-- | The text to display when prompting the user to lock.

#if defined(ENABLE_OVERLOADING)
    LockButtonTextLockPropertyInfo          ,
#endif
    clearLockButtonTextLock                 ,
    constructLockButtonTextLock             ,
    getLockButtonTextLock                   ,
#if defined(ENABLE_OVERLOADING)
    lockButtonTextLock                      ,
#endif
    setLockButtonTextLock                   ,


-- ** textUnlock #attr:textUnlock#
-- | The text to display when prompting the user to unlock.

#if defined(ENABLE_OVERLOADING)
    LockButtonTextUnlockPropertyInfo        ,
#endif
    clearLockButtonTextUnlock               ,
    constructLockButtonTextUnlock           ,
    getLockButtonTextUnlock                 ,
#if defined(ENABLE_OVERLOADING)
    lockButtonTextUnlock                    ,
#endif
    setLockButtonTextUnlock                 ,


-- ** tooltipLock #attr:tooltipLock#
-- | The tooltip to display when prompting the user to lock.

#if defined(ENABLE_OVERLOADING)
    LockButtonTooltipLockPropertyInfo       ,
#endif
    clearLockButtonTooltipLock              ,
    constructLockButtonTooltipLock          ,
    getLockButtonTooltipLock                ,
#if defined(ENABLE_OVERLOADING)
    lockButtonTooltipLock                   ,
#endif
    setLockButtonTooltipLock                ,


-- ** tooltipNotAuthorized #attr:tooltipNotAuthorized#
-- | The tooltip to display when the user cannot obtain authorization.

#if defined(ENABLE_OVERLOADING)
    LockButtonTooltipNotAuthorizedPropertyInfo,
#endif
    clearLockButtonTooltipNotAuthorized     ,
    constructLockButtonTooltipNotAuthorized ,
    getLockButtonTooltipNotAuthorized       ,
#if defined(ENABLE_OVERLOADING)
    lockButtonTooltipNotAuthorized          ,
#endif
    setLockButtonTooltipNotAuthorized       ,


-- ** tooltipUnlock #attr:tooltipUnlock#
-- | The tooltip to display when prompting the user to unlock.

#if defined(ENABLE_OVERLOADING)
    LockButtonTooltipUnlockPropertyInfo     ,
#endif
    clearLockButtonTooltipUnlock            ,
    constructLockButtonTooltipUnlock        ,
    getLockButtonTooltipUnlock              ,
#if defined(ENABLE_OVERLOADING)
    lockButtonTooltipUnlock                 ,
#endif
    setLockButtonTooltipUnlock              ,




    ) 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 qualified GI.Gio.Objects.Permission as Gio.Permission
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
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.Button as Gtk.Button
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_lock_button_get_type"
    c_gtk_lock_button_get_type :: IO B.Types.GType

instance B.Types.TypedObject LockButton where
    glibType :: IO GType
glibType = IO GType
c_gtk_lock_button_get_type

instance B.Types.GObject LockButton

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "permission"
   -- Type: TInterface (Name {namespace = "Gio", name = "Permission"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@permission@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #permission
-- @
getLockButtonPermission :: (MonadIO m, IsLockButton o) => o -> m (Maybe Gio.Permission.Permission)
getLockButtonPermission :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Permission)
getLockButtonPermission o
obj = IO (Maybe Permission) -> m (Maybe Permission)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Permission) -> m (Maybe Permission))
-> IO (Maybe Permission) -> m (Maybe Permission)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Permission -> Permission)
-> IO (Maybe Permission)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"permission" ManagedPtr Permission -> Permission
Gio.Permission.Permission

-- | Set the value of the “@permission@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' lockButton [ #permission 'Data.GI.Base.Attributes.:=' value ]
-- @
setLockButtonPermission :: (MonadIO m, IsLockButton o, Gio.Permission.IsPermission a) => o -> a -> m ()
setLockButtonPermission :: forall (m :: * -> *) o a.
(MonadIO m, IsLockButton o, IsPermission a) =>
o -> a -> m ()
setLockButtonPermission o
obj a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"permission" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@permission@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructLockButtonPermission :: (IsLockButton o, MIO.MonadIO m, Gio.Permission.IsPermission a) => a -> m (GValueConstruct o)
constructLockButtonPermission :: forall o (m :: * -> *) a.
(IsLockButton o, MonadIO m, IsPermission a) =>
a -> m (GValueConstruct o)
constructLockButtonPermission a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"permission" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@permission@” 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' #permission
-- @
clearLockButtonPermission :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonPermission :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonPermission 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 Permission -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"permission" (Maybe Permission
forall a. Maybe a
Nothing :: Maybe Gio.Permission.Permission)

#if defined(ENABLE_OVERLOADING)
data LockButtonPermissionPropertyInfo
instance AttrInfo LockButtonPermissionPropertyInfo where
    type AttrAllowedOps LockButtonPermissionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonPermissionPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonPermissionPropertyInfo = Gio.Permission.IsPermission
    type AttrTransferTypeConstraint LockButtonPermissionPropertyInfo = Gio.Permission.IsPermission
    type AttrTransferType LockButtonPermissionPropertyInfo = Gio.Permission.Permission
    type AttrGetType LockButtonPermissionPropertyInfo = (Maybe Gio.Permission.Permission)
    type AttrLabel LockButtonPermissionPropertyInfo = "permission"
    type AttrOrigin LockButtonPermissionPropertyInfo = LockButton
    attrGet = getLockButtonPermission
    attrSet = setLockButtonPermission
    attrTransfer _ v = do
        unsafeCastTo Gio.Permission.Permission v
    attrConstruct = constructLockButtonPermission
    attrClear = clearLockButtonPermission
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.permission"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:permission"
        })
#endif

-- VVV Prop "text-lock"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@text-lock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #textLock
-- @
getLockButtonTextLock :: (MonadIO m, IsLockButton o) => o -> m (Maybe T.Text)
getLockButtonTextLock :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Text)
getLockButtonTextLock 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
"text-lock"

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

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

-- | Set the value of the “@text-lock@” 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' #textLock
-- @
clearLockButtonTextLock :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTextLock :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTextLock 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
"text-lock" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data LockButtonTextLockPropertyInfo
instance AttrInfo LockButtonTextLockPropertyInfo where
    type AttrAllowedOps LockButtonTextLockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonTextLockPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonTextLockPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LockButtonTextLockPropertyInfo = (~) T.Text
    type AttrTransferType LockButtonTextLockPropertyInfo = T.Text
    type AttrGetType LockButtonTextLockPropertyInfo = (Maybe T.Text)
    type AttrLabel LockButtonTextLockPropertyInfo = "text-lock"
    type AttrOrigin LockButtonTextLockPropertyInfo = LockButton
    attrGet = getLockButtonTextLock
    attrSet = setLockButtonTextLock
    attrTransfer _ v = do
        return v
    attrConstruct = constructLockButtonTextLock
    attrClear = clearLockButtonTextLock
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.textLock"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:textLock"
        })
#endif

-- VVV Prop "text-unlock"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@text-unlock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #textUnlock
-- @
getLockButtonTextUnlock :: (MonadIO m, IsLockButton o) => o -> m (Maybe T.Text)
getLockButtonTextUnlock :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Text)
getLockButtonTextUnlock 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
"text-unlock"

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

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

-- | Set the value of the “@text-unlock@” 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' #textUnlock
-- @
clearLockButtonTextUnlock :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTextUnlock :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTextUnlock 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
"text-unlock" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data LockButtonTextUnlockPropertyInfo
instance AttrInfo LockButtonTextUnlockPropertyInfo where
    type AttrAllowedOps LockButtonTextUnlockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonTextUnlockPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonTextUnlockPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LockButtonTextUnlockPropertyInfo = (~) T.Text
    type AttrTransferType LockButtonTextUnlockPropertyInfo = T.Text
    type AttrGetType LockButtonTextUnlockPropertyInfo = (Maybe T.Text)
    type AttrLabel LockButtonTextUnlockPropertyInfo = "text-unlock"
    type AttrOrigin LockButtonTextUnlockPropertyInfo = LockButton
    attrGet = getLockButtonTextUnlock
    attrSet = setLockButtonTextUnlock
    attrTransfer _ v = do
        return v
    attrConstruct = constructLockButtonTextUnlock
    attrClear = clearLockButtonTextUnlock
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.textUnlock"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:textUnlock"
        })
#endif

-- VVV Prop "tooltip-lock"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@tooltip-lock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #tooltipLock
-- @
getLockButtonTooltipLock :: (MonadIO m, IsLockButton o) => o -> m (Maybe T.Text)
getLockButtonTooltipLock :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Text)
getLockButtonTooltipLock 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
"tooltip-lock"

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

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

-- | Set the value of the “@tooltip-lock@” 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' #tooltipLock
-- @
clearLockButtonTooltipLock :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipLock :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipLock 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
"tooltip-lock" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data LockButtonTooltipLockPropertyInfo
instance AttrInfo LockButtonTooltipLockPropertyInfo where
    type AttrAllowedOps LockButtonTooltipLockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonTooltipLockPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonTooltipLockPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LockButtonTooltipLockPropertyInfo = (~) T.Text
    type AttrTransferType LockButtonTooltipLockPropertyInfo = T.Text
    type AttrGetType LockButtonTooltipLockPropertyInfo = (Maybe T.Text)
    type AttrLabel LockButtonTooltipLockPropertyInfo = "tooltip-lock"
    type AttrOrigin LockButtonTooltipLockPropertyInfo = LockButton
    attrGet = getLockButtonTooltipLock
    attrSet = setLockButtonTooltipLock
    attrTransfer _ v = do
        return v
    attrConstruct = constructLockButtonTooltipLock
    attrClear = clearLockButtonTooltipLock
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.tooltipLock"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:tooltipLock"
        })
#endif

-- VVV Prop "tooltip-not-authorized"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@tooltip-not-authorized@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #tooltipNotAuthorized
-- @
getLockButtonTooltipNotAuthorized :: (MonadIO m, IsLockButton o) => o -> m (Maybe T.Text)
getLockButtonTooltipNotAuthorized :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Text)
getLockButtonTooltipNotAuthorized 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
"tooltip-not-authorized"

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

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

-- | Set the value of the “@tooltip-not-authorized@” 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' #tooltipNotAuthorized
-- @
clearLockButtonTooltipNotAuthorized :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipNotAuthorized :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipNotAuthorized 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
"tooltip-not-authorized" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data LockButtonTooltipNotAuthorizedPropertyInfo
instance AttrInfo LockButtonTooltipNotAuthorizedPropertyInfo where
    type AttrAllowedOps LockButtonTooltipNotAuthorizedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonTooltipNotAuthorizedPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonTooltipNotAuthorizedPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LockButtonTooltipNotAuthorizedPropertyInfo = (~) T.Text
    type AttrTransferType LockButtonTooltipNotAuthorizedPropertyInfo = T.Text
    type AttrGetType LockButtonTooltipNotAuthorizedPropertyInfo = (Maybe T.Text)
    type AttrLabel LockButtonTooltipNotAuthorizedPropertyInfo = "tooltip-not-authorized"
    type AttrOrigin LockButtonTooltipNotAuthorizedPropertyInfo = LockButton
    attrGet = getLockButtonTooltipNotAuthorized
    attrSet = setLockButtonTooltipNotAuthorized
    attrTransfer _ v = do
        return v
    attrConstruct = constructLockButtonTooltipNotAuthorized
    attrClear = clearLockButtonTooltipNotAuthorized
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.tooltipNotAuthorized"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:tooltipNotAuthorized"
        })
#endif

-- VVV Prop "tooltip-unlock"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@tooltip-unlock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' lockButton #tooltipUnlock
-- @
getLockButtonTooltipUnlock :: (MonadIO m, IsLockButton o) => o -> m (Maybe T.Text)
getLockButtonTooltipUnlock :: forall (m :: * -> *) o.
(MonadIO m, IsLockButton o) =>
o -> m (Maybe Text)
getLockButtonTooltipUnlock 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
"tooltip-unlock"

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

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

-- | Set the value of the “@tooltip-unlock@” 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' #tooltipUnlock
-- @
clearLockButtonTooltipUnlock :: (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipUnlock :: forall (m :: * -> *) o. (MonadIO m, IsLockButton o) => o -> m ()
clearLockButtonTooltipUnlock 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
"tooltip-unlock" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data LockButtonTooltipUnlockPropertyInfo
instance AttrInfo LockButtonTooltipUnlockPropertyInfo where
    type AttrAllowedOps LockButtonTooltipUnlockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LockButtonTooltipUnlockPropertyInfo = IsLockButton
    type AttrSetTypeConstraint LockButtonTooltipUnlockPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LockButtonTooltipUnlockPropertyInfo = (~) T.Text
    type AttrTransferType LockButtonTooltipUnlockPropertyInfo = T.Text
    type AttrGetType LockButtonTooltipUnlockPropertyInfo = (Maybe T.Text)
    type AttrLabel LockButtonTooltipUnlockPropertyInfo = "tooltip-unlock"
    type AttrOrigin LockButtonTooltipUnlockPropertyInfo = LockButton
    attrGet = getLockButtonTooltipUnlock
    attrSet = setLockButtonTooltipUnlock
    attrTransfer _ v = do
        return v
    attrConstruct = constructLockButtonTooltipUnlock
    attrClear = clearLockButtonTooltipUnlock
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.LockButton.tooltipUnlock"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-LockButton.html#g:attr:tooltipUnlock"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LockButton
type instance O.AttributeList LockButton = LockButtonAttributeList
type LockButtonAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", Gtk.Button.ButtonChildPropertyInfo), '("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), '("hasFrame", Gtk.Button.ButtonHasFramePropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", Gtk.Button.ButtonIconNamePropertyInfo), '("label", Gtk.Button.ButtonLabelPropertyInfo), '("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), '("permission", LockButtonPermissionPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("textLock", LockButtonTextLockPropertyInfo), '("textUnlock", LockButtonTextUnlockPropertyInfo), '("tooltipLock", LockButtonTooltipLockPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipNotAuthorized", LockButtonTooltipNotAuthorizedPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("tooltipUnlock", LockButtonTooltipUnlockPropertyInfo), '("useUnderline", Gtk.Button.ButtonUseUnderlinePropertyInfo), '("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)
lockButtonPermission :: AttrLabelProxy "permission"
lockButtonPermission = AttrLabelProxy

lockButtonTextLock :: AttrLabelProxy "textLock"
lockButtonTextLock = AttrLabelProxy

lockButtonTextUnlock :: AttrLabelProxy "textUnlock"
lockButtonTextUnlock = AttrLabelProxy

lockButtonTooltipLock :: AttrLabelProxy "tooltipLock"
lockButtonTooltipLock = AttrLabelProxy

lockButtonTooltipNotAuthorized :: AttrLabelProxy "tooltipNotAuthorized"
lockButtonTooltipNotAuthorized = AttrLabelProxy

lockButtonTooltipUnlock :: AttrLabelProxy "tooltipUnlock"
lockButtonTooltipUnlock = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList LockButton = LockButtonSignalList
type LockButtonSignalList = ('[ '("activate", Gtk.Button.ButtonActivateSignalInfo), '("clicked", Gtk.Button.ButtonClickedSignalInfo), '("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 LockButton::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "permission"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Permission" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GPermission`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "LockButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_lock_button_new" gtk_lock_button_new :: 
    Ptr Gio.Permission.Permission ->        -- permission : TInterface (Name {namespace = "Gio", name = "Permission"})
    IO (Ptr LockButton)

-- | Creates a new lock button which reflects the /@permission@/.
lockButtonNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Permission.IsPermission a) =>
    Maybe (a)
    -- ^ /@permission@/: a @GPermission@
    -> m LockButton
    -- ^ __Returns:__ a new @GtkLockButton@
lockButtonNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPermission a) =>
Maybe a -> m LockButton
lockButtonNew Maybe a
permission = IO LockButton -> m LockButton
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LockButton -> m LockButton) -> IO LockButton -> m LockButton
forall a b. (a -> b) -> a -> b
$ do
    Ptr Permission
maybePermission <- case Maybe a
permission of
        Maybe a
Nothing -> Ptr Permission -> IO (Ptr Permission)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Permission
forall a. Ptr a
nullPtr
        Just a
jPermission -> do
            Ptr Permission
jPermission' <- a -> IO (Ptr Permission)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jPermission
            Ptr Permission -> IO (Ptr Permission)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Permission
jPermission'
    Ptr LockButton
result <- Ptr Permission -> IO (Ptr LockButton)
gtk_lock_button_new Ptr Permission
maybePermission
    Text -> Ptr LockButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"lockButtonNew" Ptr LockButton
result
    LockButton
result' <- ((ManagedPtr LockButton -> LockButton)
-> Ptr LockButton -> IO LockButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr LockButton -> LockButton
LockButton) Ptr LockButton
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
permission a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    LockButton -> IO LockButton
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LockButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_lock_button_get_permission" gtk_lock_button_get_permission :: 
    Ptr LockButton ->                       -- button : TInterface (Name {namespace = "Gtk", name = "LockButton"})
    IO (Ptr Gio.Permission.Permission)

-- | Obtains the @GPermission@ object that controls /@button@/.
lockButtonGetPermission ::
    (B.CallStack.HasCallStack, MonadIO m, IsLockButton a) =>
    a
    -- ^ /@button@/: a @GtkLockButton@
    -> m (Maybe Gio.Permission.Permission)
    -- ^ __Returns:__ the @GPermission@ of /@button@/
lockButtonGetPermission :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLockButton a) =>
a -> m (Maybe Permission)
lockButtonGetPermission a
button = IO (Maybe Permission) -> m (Maybe Permission)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Permission) -> m (Maybe Permission))
-> IO (Maybe Permission) -> m (Maybe Permission)
forall a b. (a -> b) -> a -> b
$ do
    Ptr LockButton
button' <- a -> IO (Ptr LockButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Permission
result <- Ptr LockButton -> IO (Ptr Permission)
gtk_lock_button_get_permission Ptr LockButton
button'
    Maybe Permission
maybeResult <- Ptr Permission
-> (Ptr Permission -> IO Permission) -> IO (Maybe Permission)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Permission
result ((Ptr Permission -> IO Permission) -> IO (Maybe Permission))
-> (Ptr Permission -> IO Permission) -> IO (Maybe Permission)
forall a b. (a -> b) -> a -> b
$ \Ptr Permission
result' -> do
        Permission
result'' <- ((ManagedPtr Permission -> Permission)
-> Ptr Permission -> IO Permission
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Permission -> Permission
Gio.Permission.Permission) Ptr Permission
result'
        Permission -> IO Permission
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Permission
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Maybe Permission -> IO (Maybe Permission)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Permission
maybeResult

#if defined(ENABLE_OVERLOADING)
data LockButtonGetPermissionMethodInfo
instance (signature ~ (m (Maybe Gio.Permission.Permission)), MonadIO m, IsLockButton a) => O.OverloadedMethod LockButtonGetPermissionMethodInfo a signature where
    overloadedMethod = lockButtonGetPermission

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


#endif

-- method LockButton::set_permission
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "LockButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkLockButton`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "permission"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Permission" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GPermission` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_lock_button_set_permission" gtk_lock_button_set_permission :: 
    Ptr LockButton ->                       -- button : TInterface (Name {namespace = "Gtk", name = "LockButton"})
    Ptr Gio.Permission.Permission ->        -- permission : TInterface (Name {namespace = "Gio", name = "Permission"})
    IO ()

-- | Sets the @GPermission@ object that controls /@button@/.
lockButtonSetPermission ::
    (B.CallStack.HasCallStack, MonadIO m, IsLockButton a, Gio.Permission.IsPermission b) =>
    a
    -- ^ /@button@/: a @GtkLockButton@
    -> Maybe (b)
    -- ^ /@permission@/: a @GPermission@ object
    -> m ()
lockButtonSetPermission :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsLockButton a, IsPermission b) =>
a -> Maybe b -> m ()
lockButtonSetPermission a
button Maybe b
permission = 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 LockButton
button' <- a -> IO (Ptr LockButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Permission
maybePermission <- case Maybe b
permission of
        Maybe b
Nothing -> Ptr Permission -> IO (Ptr Permission)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Permission
forall a. Ptr a
nullPtr
        Just b
jPermission -> do
            Ptr Permission
jPermission' <- b -> IO (Ptr Permission)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jPermission
            Ptr Permission -> IO (Ptr Permission)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Permission
jPermission'
    Ptr LockButton -> Ptr Permission -> IO ()
gtk_lock_button_set_permission Ptr LockButton
button' Ptr Permission
maybePermission
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
permission b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LockButtonSetPermissionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsLockButton a, Gio.Permission.IsPermission b) => O.OverloadedMethod LockButtonSetPermissionMethodInfo a signature where
    overloadedMethod = lockButtonSetPermission

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


#endif