{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.PasswordEntry.PasswordEntry' is entry that has been tailored for entering secrets.
-- It does not show its contents in clear text, does not allow to copy it
-- to the clipboard, and it shows a warning when Caps Lock is engaged. If
-- the underlying platform allows it, GtkPasswordEntry will also place the
-- text in a non-pageable memory area, to avoid it being written out to
-- disk by the operating system.
-- 
-- Optionally, it can offer a way to reveal the contents in clear text.
-- 
-- GtkPasswordEntry provides only minimal API and should be used with the
-- t'GI.Gtk.Interfaces.Editable.Editable' API.
-- 
-- = CSS Nodes
-- 
-- 
-- === /plain code/
-- >
-- >entry.password
-- >╰── text
-- >    ├── image.caps-lock-indicator
-- >    ┊
-- 
-- 
-- GtkPasswordEntry has a single CSS node with name entry that carries
-- a .passwordstyle class. The text Css node below it has a child with
-- name image and style class .caps-lock-indicator for the Caps Lock
-- icon, and possibly other children.
-- 
-- = Accessibility
-- 
-- GtkPasswordEntry uses the @/GTK_ACCESSIBLE_ROLE_TEXT_BOX/@ role.

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

module GI.Gtk.Objects.PasswordEntry
    ( 

-- * Exported types
    PasswordEntry(..)                       ,
    IsPasswordEntry                         ,
    toPasswordEntry                         ,


 -- * 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"), [deleteSelection]("GI.Gtk.Interfaces.Editable#g:method:deleteSelection"), [deleteText]("GI.Gtk.Interfaces.Editable#g:method:deleteText"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [finishDelegate]("GI.Gtk.Interfaces.Editable#g:method:finishDelegate"), [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"), [initDelegate]("GI.Gtk.Interfaces.Editable#g:method:initDelegate"), [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"), [insertText]("GI.Gtk.Interfaces.Editable#g:method:insertText"), [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"), [selectRegion]("GI.Gtk.Interfaces.Editable#g:method:selectRegion"), [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"), [getAlignment]("GI.Gtk.Interfaces.Editable#g:method:getAlignment"), [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"), [getChars]("GI.Gtk.Interfaces.Editable#g:method:getChars"), [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"), [getDelegate]("GI.Gtk.Interfaces.Editable#g:method:getDelegate"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getEditable]("GI.Gtk.Interfaces.Editable#g:method:getEditable"), [getEnableUndo]("GI.Gtk.Interfaces.Editable#g:method:getEnableUndo"), [getExtraMenu]("GI.Gtk.Objects.PasswordEntry#g:method:getExtraMenu"), [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"), [getMaxWidthChars]("GI.Gtk.Interfaces.Editable#g:method:getMaxWidthChars"), [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"), [getPosition]("GI.Gtk.Interfaces.Editable#g:method:getPosition"), [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"), [getSelectionBounds]("GI.Gtk.Interfaces.Editable#g:method:getSelectionBounds"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getShowPeekIcon]("GI.Gtk.Objects.PasswordEntry#g:method:getShowPeekIcon"), [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"), [getText]("GI.Gtk.Interfaces.Editable#g:method:getText"), [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"), [getWidthChars]("GI.Gtk.Interfaces.Editable#g:method:getWidthChars").
-- 
-- ==== Setters
-- [setAlignment]("GI.Gtk.Interfaces.Editable#g:method:setAlignment"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setEditable]("GI.Gtk.Interfaces.Editable#g:method:setEditable"), [setEnableUndo]("GI.Gtk.Interfaces.Editable#g:method:setEnableUndo"), [setExtraMenu]("GI.Gtk.Objects.PasswordEntry#g:method:setExtraMenu"), [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"), [setMaxWidthChars]("GI.Gtk.Interfaces.Editable#g:method:setMaxWidthChars"), [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"), [setPosition]("GI.Gtk.Interfaces.Editable#g:method:setPosition"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setShowPeekIcon]("GI.Gtk.Objects.PasswordEntry#g:method:setShowPeekIcon"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setText]("GI.Gtk.Interfaces.Editable#g:method:setText"), [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"), [setWidthChars]("GI.Gtk.Interfaces.Editable#g:method:setWidthChars").

#if defined(ENABLE_OVERLOADING)
    ResolvePasswordEntryMethod              ,
#endif

-- ** getExtraMenu #method:getExtraMenu#

#if defined(ENABLE_OVERLOADING)
    PasswordEntryGetExtraMenuMethodInfo     ,
#endif
    passwordEntryGetExtraMenu               ,


-- ** getShowPeekIcon #method:getShowPeekIcon#

#if defined(ENABLE_OVERLOADING)
    PasswordEntryGetShowPeekIconMethodInfo  ,
#endif
    passwordEntryGetShowPeekIcon            ,


-- ** new #method:new#

    passwordEntryNew                        ,


-- ** setExtraMenu #method:setExtraMenu#

#if defined(ENABLE_OVERLOADING)
    PasswordEntrySetExtraMenuMethodInfo     ,
#endif
    passwordEntrySetExtraMenu               ,


-- ** setShowPeekIcon #method:setShowPeekIcon#

#if defined(ENABLE_OVERLOADING)
    PasswordEntrySetShowPeekIconMethodInfo  ,
#endif
    passwordEntrySetShowPeekIcon            ,




 -- * Properties


-- ** activatesDefault #attr:activatesDefault#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    PasswordEntryActivatesDefaultPropertyInfo,
#endif
    constructPasswordEntryActivatesDefault  ,
    getPasswordEntryActivatesDefault        ,
#if defined(ENABLE_OVERLOADING)
    passwordEntryActivatesDefault           ,
#endif
    setPasswordEntryActivatesDefault        ,


-- ** extraMenu #attr:extraMenu#
-- | A menu model whose contents will be appended to
-- the context menu.

#if defined(ENABLE_OVERLOADING)
    PasswordEntryExtraMenuPropertyInfo      ,
#endif
    clearPasswordEntryExtraMenu             ,
    constructPasswordEntryExtraMenu         ,
    getPasswordEntryExtraMenu               ,
#if defined(ENABLE_OVERLOADING)
    passwordEntryExtraMenu                  ,
#endif
    setPasswordEntryExtraMenu               ,


-- ** placeholderText #attr:placeholderText#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    PasswordEntryPlaceholderTextPropertyInfo,
#endif
    clearPasswordEntryPlaceholderText       ,
    constructPasswordEntryPlaceholderText   ,
    getPasswordEntryPlaceholderText         ,
#if defined(ENABLE_OVERLOADING)
    passwordEntryPlaceholderText            ,
#endif
    setPasswordEntryPlaceholderText         ,


-- ** showPeekIcon #attr:showPeekIcon#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    PasswordEntryShowPeekIconPropertyInfo   ,
#endif
    constructPasswordEntryShowPeekIcon      ,
    getPasswordEntryShowPeekIcon            ,
#if defined(ENABLE_OVERLOADING)
    passwordEntryShowPeekIcon               ,
#endif
    setPasswordEntryShowPeekIcon            ,




 -- * Signals


-- ** activate #signal:activate#

    C_PasswordEntryActivateCallback         ,
    PasswordEntryActivateCallback           ,
#if defined(ENABLE_OVERLOADING)
    PasswordEntryActivateSignalInfo         ,
#endif
    afterPasswordEntryActivate              ,
    genClosure_PasswordEntryActivate        ,
    mk_PasswordEntryActivateCallback        ,
    noPasswordEntryActivateCallback         ,
    onPasswordEntryActivate                 ,
    wrap_PasswordEntryActivateCallback      ,




    ) 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.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.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.MenuModel as Gio.MenuModel
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.Interfaces.Editable as Gtk.Editable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_password_entry_get_type"
    c_gtk_password_entry_get_type :: IO B.Types.GType

instance B.Types.TypedObject PasswordEntry where
    glibType :: IO GType
glibType = IO GType
c_gtk_password_entry_get_type

instance B.Types.GObject PasswordEntry

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

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

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

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

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

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

#endif

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

#endif

-- signal PasswordEntry::activate
-- | /No description available in the introspection data./
type PasswordEntryActivateCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `PasswordEntryActivateCallback`@.
noPasswordEntryActivateCallback :: Maybe PasswordEntryActivateCallback
noPasswordEntryActivateCallback :: Maybe (IO ())
noPasswordEntryActivateCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_PasswordEntryActivateCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PasswordEntryActivateCallback`.
foreign import ccall "wrapper"
    mk_PasswordEntryActivateCallback :: C_PasswordEntryActivateCallback -> IO (FunPtr C_PasswordEntryActivateCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_PasswordEntryActivate :: MonadIO m => PasswordEntryActivateCallback -> m (GClosure C_PasswordEntryActivateCallback)
genClosure_PasswordEntryActivate :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_PasswordEntryActivateCallback)
genClosure_PasswordEntryActivate IO ()
cb = IO (GClosure C_PasswordEntryActivateCallback)
-> m (GClosure C_PasswordEntryActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PasswordEntryActivateCallback)
 -> m (GClosure C_PasswordEntryActivateCallback))
-> IO (GClosure C_PasswordEntryActivateCallback)
-> m (GClosure C_PasswordEntryActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PasswordEntryActivateCallback
cb' = IO () -> C_PasswordEntryActivateCallback
wrap_PasswordEntryActivateCallback IO ()
cb
    C_PasswordEntryActivateCallback
-> IO (FunPtr C_PasswordEntryActivateCallback)
mk_PasswordEntryActivateCallback C_PasswordEntryActivateCallback
cb' IO (FunPtr C_PasswordEntryActivateCallback)
-> (FunPtr C_PasswordEntryActivateCallback
    -> IO (GClosure C_PasswordEntryActivateCallback))
-> IO (GClosure C_PasswordEntryActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PasswordEntryActivateCallback
-> IO (GClosure C_PasswordEntryActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `PasswordEntryActivateCallback` into a `C_PasswordEntryActivateCallback`.
wrap_PasswordEntryActivateCallback ::
    PasswordEntryActivateCallback ->
    C_PasswordEntryActivateCallback
wrap_PasswordEntryActivateCallback :: IO () -> C_PasswordEntryActivateCallback
wrap_PasswordEntryActivateCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [activate](#signal:activate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' passwordEntry #activate callback
-- @
-- 
-- 
onPasswordEntryActivate :: (IsPasswordEntry a, MonadIO m) => a -> PasswordEntryActivateCallback -> m SignalHandlerId
onPasswordEntryActivate :: forall a (m :: * -> *).
(IsPasswordEntry a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onPasswordEntryActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PasswordEntryActivateCallback
cb' = IO () -> C_PasswordEntryActivateCallback
wrap_PasswordEntryActivateCallback IO ()
cb
    FunPtr C_PasswordEntryActivateCallback
cb'' <- C_PasswordEntryActivateCallback
-> IO (FunPtr C_PasswordEntryActivateCallback)
mk_PasswordEntryActivateCallback C_PasswordEntryActivateCallback
cb'
    a
-> Text
-> FunPtr C_PasswordEntryActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_PasswordEntryActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [activate](#signal:activate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' passwordEntry #activate callback
-- @
-- 
-- 
afterPasswordEntryActivate :: (IsPasswordEntry a, MonadIO m) => a -> PasswordEntryActivateCallback -> m SignalHandlerId
afterPasswordEntryActivate :: forall a (m :: * -> *).
(IsPasswordEntry a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterPasswordEntryActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PasswordEntryActivateCallback
cb' = IO () -> C_PasswordEntryActivateCallback
wrap_PasswordEntryActivateCallback IO ()
cb
    FunPtr C_PasswordEntryActivateCallback
cb'' <- C_PasswordEntryActivateCallback
-> IO (FunPtr C_PasswordEntryActivateCallback)
mk_PasswordEntryActivateCallback C_PasswordEntryActivateCallback
cb'
    a
-> Text
-> FunPtr C_PasswordEntryActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_PasswordEntryActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PasswordEntryActivateSignalInfo
instance SignalInfo PasswordEntryActivateSignalInfo where
    type HaskellCallbackType PasswordEntryActivateSignalInfo = PasswordEntryActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PasswordEntryActivateCallback cb
        cb'' <- mk_PasswordEntryActivateCallback cb'
        connectSignalFunPtr obj "activate" cb'' connectMode detail

#endif

-- VVV Prop "activates-default"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@activates-default@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' passwordEntry #activatesDefault
-- @
getPasswordEntryActivatesDefault :: (MonadIO m, IsPasswordEntry o) => o -> m Bool
getPasswordEntryActivatesDefault :: forall (m :: * -> *) o.
(MonadIO m, IsPasswordEntry o) =>
o -> m Bool
getPasswordEntryActivatesDefault o
obj = IO Bool -> m Bool
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
"activates-default"

-- | Set the value of the “@activates-default@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' passwordEntry [ #activatesDefault 'Data.GI.Base.Attributes.:=' value ]
-- @
setPasswordEntryActivatesDefault :: (MonadIO m, IsPasswordEntry o) => o -> Bool -> m ()
setPasswordEntryActivatesDefault :: forall (m :: * -> *) o.
(MonadIO m, IsPasswordEntry o) =>
o -> Bool -> m ()
setPasswordEntryActivatesDefault o
obj Bool
val = IO () -> m ()
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"activates-default" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@activates-default@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPasswordEntryActivatesDefault :: (IsPasswordEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPasswordEntryActivatesDefault :: forall o (m :: * -> *).
(IsPasswordEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPasswordEntryActivatesDefault Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"activates-default" Bool
val

#if defined(ENABLE_OVERLOADING)
data PasswordEntryActivatesDefaultPropertyInfo
instance AttrInfo PasswordEntryActivatesDefaultPropertyInfo where
    type AttrAllowedOps PasswordEntryActivatesDefaultPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PasswordEntryActivatesDefaultPropertyInfo = IsPasswordEntry
    type AttrSetTypeConstraint PasswordEntryActivatesDefaultPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PasswordEntryActivatesDefaultPropertyInfo = (~) Bool
    type AttrTransferType PasswordEntryActivatesDefaultPropertyInfo = Bool
    type AttrGetType PasswordEntryActivatesDefaultPropertyInfo = Bool
    type AttrLabel PasswordEntryActivatesDefaultPropertyInfo = "activates-default"
    type AttrOrigin PasswordEntryActivatesDefaultPropertyInfo = PasswordEntry
    attrGet = getPasswordEntryActivatesDefault
    attrSet = setPasswordEntryActivatesDefault
    attrTransfer _ v = do
        return v
    attrConstruct = constructPasswordEntryActivatesDefault
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@extra-menu@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' passwordEntry [ #extraMenu 'Data.GI.Base.Attributes.:=' value ]
-- @
setPasswordEntryExtraMenu :: (MonadIO m, IsPasswordEntry o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
setPasswordEntryExtraMenu :: forall (m :: * -> *) o a.
(MonadIO m, IsPasswordEntry o, IsMenuModel a) =>
o -> a -> m ()
setPasswordEntryExtraMenu o
obj a
val = IO () -> m ()
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
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@extra-menu@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPasswordEntryExtraMenu :: (IsPasswordEntry o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
constructPasswordEntryExtraMenu :: forall o (m :: * -> *) a.
(IsPasswordEntry o, MonadIO m, IsMenuModel a) =>
a -> m (GValueConstruct o)
constructPasswordEntryExtraMenu a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@extra-menu@” 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' #extraMenu
-- @
clearPasswordEntryExtraMenu :: (MonadIO m, IsPasswordEntry o) => o -> m ()
clearPasswordEntryExtraMenu :: forall (m :: * -> *) o. (MonadIO m, IsPasswordEntry o) => o -> m ()
clearPasswordEntryExtraMenu o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)

#if defined(ENABLE_OVERLOADING)
data PasswordEntryExtraMenuPropertyInfo
instance AttrInfo PasswordEntryExtraMenuPropertyInfo where
    type AttrAllowedOps PasswordEntryExtraMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PasswordEntryExtraMenuPropertyInfo = IsPasswordEntry
    type AttrSetTypeConstraint PasswordEntryExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint PasswordEntryExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType PasswordEntryExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType PasswordEntryExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrLabel PasswordEntryExtraMenuPropertyInfo = "extra-menu"
    type AttrOrigin PasswordEntryExtraMenuPropertyInfo = PasswordEntry
    attrGet = getPasswordEntryExtraMenu
    attrSet = setPasswordEntryExtraMenu
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructPasswordEntryExtraMenu
    attrClear = clearPasswordEntryExtraMenu
#endif

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

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

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

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

-- | Set the value of the “@placeholder-text@” 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' #placeholderText
-- @
clearPasswordEntryPlaceholderText :: (MonadIO m, IsPasswordEntry o) => o -> m ()
clearPasswordEntryPlaceholderText :: forall (m :: * -> *) o. (MonadIO m, IsPasswordEntry o) => o -> m ()
clearPasswordEntryPlaceholderText o
obj = IO () -> m ()
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
"placeholder-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data PasswordEntryPlaceholderTextPropertyInfo
instance AttrInfo PasswordEntryPlaceholderTextPropertyInfo where
    type AttrAllowedOps PasswordEntryPlaceholderTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PasswordEntryPlaceholderTextPropertyInfo = IsPasswordEntry
    type AttrSetTypeConstraint PasswordEntryPlaceholderTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PasswordEntryPlaceholderTextPropertyInfo = (~) T.Text
    type AttrTransferType PasswordEntryPlaceholderTextPropertyInfo = T.Text
    type AttrGetType PasswordEntryPlaceholderTextPropertyInfo = (Maybe T.Text)
    type AttrLabel PasswordEntryPlaceholderTextPropertyInfo = "placeholder-text"
    type AttrOrigin PasswordEntryPlaceholderTextPropertyInfo = PasswordEntry
    attrGet = getPasswordEntryPlaceholderText
    attrSet = setPasswordEntryPlaceholderText
    attrTransfer _ v = do
        return v
    attrConstruct = constructPasswordEntryPlaceholderText
    attrClear = clearPasswordEntryPlaceholderText
#endif

-- VVV Prop "show-peek-icon"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@show-peek-icon@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' passwordEntry #showPeekIcon
-- @
getPasswordEntryShowPeekIcon :: (MonadIO m, IsPasswordEntry o) => o -> m Bool
getPasswordEntryShowPeekIcon :: forall (m :: * -> *) o.
(MonadIO m, IsPasswordEntry o) =>
o -> m Bool
getPasswordEntryShowPeekIcon o
obj = IO Bool -> m Bool
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
"show-peek-icon"

-- | Set the value of the “@show-peek-icon@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' passwordEntry [ #showPeekIcon 'Data.GI.Base.Attributes.:=' value ]
-- @
setPasswordEntryShowPeekIcon :: (MonadIO m, IsPasswordEntry o) => o -> Bool -> m ()
setPasswordEntryShowPeekIcon :: forall (m :: * -> *) o.
(MonadIO m, IsPasswordEntry o) =>
o -> Bool -> m ()
setPasswordEntryShowPeekIcon o
obj Bool
val = IO () -> m ()
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"show-peek-icon" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@show-peek-icon@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPasswordEntryShowPeekIcon :: (IsPasswordEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPasswordEntryShowPeekIcon :: forall o (m :: * -> *).
(IsPasswordEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPasswordEntryShowPeekIcon Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"show-peek-icon" Bool
val

#if defined(ENABLE_OVERLOADING)
data PasswordEntryShowPeekIconPropertyInfo
instance AttrInfo PasswordEntryShowPeekIconPropertyInfo where
    type AttrAllowedOps PasswordEntryShowPeekIconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PasswordEntryShowPeekIconPropertyInfo = IsPasswordEntry
    type AttrSetTypeConstraint PasswordEntryShowPeekIconPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PasswordEntryShowPeekIconPropertyInfo = (~) Bool
    type AttrTransferType PasswordEntryShowPeekIconPropertyInfo = Bool
    type AttrGetType PasswordEntryShowPeekIconPropertyInfo = Bool
    type AttrLabel PasswordEntryShowPeekIconPropertyInfo = "show-peek-icon"
    type AttrOrigin PasswordEntryShowPeekIconPropertyInfo = PasswordEntry
    attrGet = getPasswordEntryShowPeekIcon
    attrSet = setPasswordEntryShowPeekIcon
    attrTransfer _ v = do
        return v
    attrConstruct = constructPasswordEntryShowPeekIcon
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PasswordEntry
type instance O.AttributeList PasswordEntry = PasswordEntryAttributeList
type PasswordEntryAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("activatesDefault", PasswordEntryActivatesDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("cursorPosition", Gtk.Editable.EditableCursorPositionPropertyInfo), '("editable", Gtk.Editable.EditableEditablePropertyInfo), '("enableUndo", Gtk.Editable.EditableEnableUndoPropertyInfo), '("extraMenu", PasswordEntryExtraMenuPropertyInfo), '("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), '("maxWidthChars", Gtk.Editable.EditableMaxWidthCharsPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("placeholderText", PasswordEntryPlaceholderTextPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("selectionBound", Gtk.Editable.EditableSelectionBoundPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showPeekIcon", PasswordEntryShowPeekIconPropertyInfo), '("text", Gtk.Editable.EditableTextPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthChars", Gtk.Editable.EditableWidthCharsPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("xalign", Gtk.Editable.EditableXalignPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
passwordEntryActivatesDefault :: AttrLabelProxy "activatesDefault"
passwordEntryActivatesDefault = AttrLabelProxy

passwordEntryExtraMenu :: AttrLabelProxy "extraMenu"
passwordEntryExtraMenu = AttrLabelProxy

passwordEntryPlaceholderText :: AttrLabelProxy "placeholderText"
passwordEntryPlaceholderText = AttrLabelProxy

passwordEntryShowPeekIcon :: AttrLabelProxy "showPeekIcon"
passwordEntryShowPeekIcon = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PasswordEntry = PasswordEntrySignalList
type PasswordEntrySignalList = ('[ '("activate", PasswordEntryActivateSignalInfo), '("changed", Gtk.Editable.EditableChangedSignalInfo), '("deleteText", Gtk.Editable.EditableDeleteTextSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("insertText", Gtk.Editable.EditableInsertTextSignalInfo), '("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 PasswordEntry::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "PasswordEntry" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_password_entry_new" gtk_password_entry_new :: 
    IO (Ptr PasswordEntry)

-- | Creates a t'GI.Gtk.Objects.PasswordEntry.PasswordEntry'.
passwordEntryNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PasswordEntry
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.PasswordEntry.PasswordEntry'
passwordEntryNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m PasswordEntry
passwordEntryNew  = IO PasswordEntry -> m PasswordEntry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PasswordEntry -> m PasswordEntry)
-> IO PasswordEntry -> m PasswordEntry
forall a b. (a -> b) -> a -> b
$ do
    Ptr PasswordEntry
result <- IO (Ptr PasswordEntry)
gtk_password_entry_new
    Text -> Ptr PasswordEntry -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"passwordEntryNew" Ptr PasswordEntry
result
    PasswordEntry
result' <- ((ManagedPtr PasswordEntry -> PasswordEntry)
-> Ptr PasswordEntry -> IO PasswordEntry
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PasswordEntry -> PasswordEntry
PasswordEntry) Ptr PasswordEntry
result
    PasswordEntry -> IO PasswordEntry
forall (m :: * -> *) a. Monad m => a -> m a
return PasswordEntry
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_password_entry_get_extra_menu" gtk_password_entry_get_extra_menu :: 
    Ptr PasswordEntry ->                    -- entry : TInterface (Name {namespace = "Gtk", name = "PasswordEntry"})
    IO (Ptr Gio.MenuModel.MenuModel)

-- | Gets the menu model set with 'GI.Gtk.Objects.PasswordEntry.passwordEntrySetExtraMenu'.
passwordEntryGetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsPasswordEntry a) =>
    a
    -- ^ /@entry@/: a t'GI.Gtk.Objects.Text.Text'
    -> m Gio.MenuModel.MenuModel
    -- ^ __Returns:__ (nullable): the menu model
passwordEntryGetExtraMenu :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPasswordEntry a) =>
a -> m MenuModel
passwordEntryGetExtraMenu a
entry = IO MenuModel -> m MenuModel
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuModel -> m MenuModel) -> IO MenuModel -> m MenuModel
forall a b. (a -> b) -> a -> b
$ do
    Ptr PasswordEntry
entry' <- a -> IO (Ptr PasswordEntry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr MenuModel
result <- Ptr PasswordEntry -> IO (Ptr MenuModel)
gtk_password_entry_get_extra_menu Ptr PasswordEntry
entry'
    Text -> Ptr MenuModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"passwordEntryGetExtraMenu" Ptr MenuModel
result
    MenuModel
result' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    MenuModel -> IO MenuModel
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result'

#if defined(ENABLE_OVERLOADING)
data PasswordEntryGetExtraMenuMethodInfo
instance (signature ~ (m Gio.MenuModel.MenuModel), MonadIO m, IsPasswordEntry a) => O.OverloadedMethod PasswordEntryGetExtraMenuMethodInfo a signature where
    overloadedMethod = passwordEntryGetExtraMenu

instance O.OverloadedMethodInfo PasswordEntryGetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PasswordEntry.passwordEntryGetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PasswordEntry.html#v:passwordEntryGetExtraMenu"
        }


#endif

-- method PasswordEntry::get_show_peek_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PasswordEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPasswordEntry"
--                 , 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_password_entry_get_show_peek_icon" gtk_password_entry_get_show_peek_icon :: 
    Ptr PasswordEntry ->                    -- entry : TInterface (Name {namespace = "Gtk", name = "PasswordEntry"})
    IO CInt

-- | Returns whether the entry is showing a clickable icon
-- to reveal the contents of the entry in clear text.
passwordEntryGetShowPeekIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsPasswordEntry a) =>
    a
    -- ^ /@entry@/: a t'GI.Gtk.Objects.PasswordEntry.PasswordEntry'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if an icon is shown
passwordEntryGetShowPeekIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPasswordEntry a) =>
a -> m Bool
passwordEntryGetShowPeekIcon a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PasswordEntry
entry' <- a -> IO (Ptr PasswordEntry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr PasswordEntry -> IO CInt
gtk_password_entry_get_show_peek_icon Ptr PasswordEntry
entry'
    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
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PasswordEntryGetShowPeekIconMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPasswordEntry a) => O.OverloadedMethod PasswordEntryGetShowPeekIconMethodInfo a signature where
    overloadedMethod = passwordEntryGetShowPeekIcon

instance O.OverloadedMethodInfo PasswordEntryGetShowPeekIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PasswordEntry.passwordEntryGetShowPeekIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PasswordEntry.html#v:passwordEntryGetShowPeekIcon"
        }


#endif

-- method PasswordEntry::set_extra_menu
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PasswordEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPasswordEntry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MenuModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMenuModel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_password_entry_set_extra_menu" gtk_password_entry_set_extra_menu :: 
    Ptr PasswordEntry ->                    -- entry : TInterface (Name {namespace = "Gtk", name = "PasswordEntry"})
    Ptr Gio.MenuModel.MenuModel ->          -- model : TInterface (Name {namespace = "Gio", name = "MenuModel"})
    IO ()

-- | Sets a menu model to add when constructing
-- the context menu for /@entry@/.
passwordEntrySetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsPasswordEntry a, Gio.MenuModel.IsMenuModel b) =>
    a
    -- ^ /@entry@/: a t'GI.Gtk.Objects.PasswordEntry.PasswordEntry'
    -> Maybe (b)
    -- ^ /@model@/: a t'GI.Gio.Objects.MenuModel.MenuModel'
    -> m ()
passwordEntrySetExtraMenu :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPasswordEntry a, IsMenuModel b) =>
a -> Maybe b -> m ()
passwordEntrySetExtraMenu a
entry Maybe b
model = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PasswordEntry
entry' <- a -> IO (Ptr PasswordEntry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr PasswordEntry -> Ptr MenuModel -> IO ()
gtk_password_entry_set_extra_menu Ptr PasswordEntry
entry' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PasswordEntrySetExtraMenuMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsPasswordEntry a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod PasswordEntrySetExtraMenuMethodInfo a signature where
    overloadedMethod = passwordEntrySetExtraMenu

instance O.OverloadedMethodInfo PasswordEntrySetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PasswordEntry.passwordEntrySetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PasswordEntry.html#v:passwordEntrySetExtraMenu"
        }


#endif

-- method PasswordEntry::set_show_peek_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PasswordEntry" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPasswordEntry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "show_peek_icon"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to show the peek icon"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_password_entry_set_show_peek_icon" gtk_password_entry_set_show_peek_icon :: 
    Ptr PasswordEntry ->                    -- entry : TInterface (Name {namespace = "Gtk", name = "PasswordEntry"})
    CInt ->                                 -- show_peek_icon : TBasicType TBoolean
    IO ()

-- | Sets whether the entry should have a clickable icon
-- to show the contents of the entry in clear text.
-- 
-- Setting this to 'P.False' also hides the text again.
passwordEntrySetShowPeekIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsPasswordEntry a) =>
    a
    -- ^ /@entry@/: a t'GI.Gtk.Objects.PasswordEntry.PasswordEntry'
    -> Bool
    -- ^ /@showPeekIcon@/: whether to show the peek icon
    -> m ()
passwordEntrySetShowPeekIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPasswordEntry a) =>
a -> Bool -> m ()
passwordEntrySetShowPeekIcon a
entry Bool
showPeekIcon = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PasswordEntry
entry' <- a -> IO (Ptr PasswordEntry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let showPeekIcon' :: CInt
showPeekIcon' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
showPeekIcon
    Ptr PasswordEntry -> CInt -> IO ()
gtk_password_entry_set_show_peek_icon Ptr PasswordEntry
entry' CInt
showPeekIcon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PasswordEntrySetShowPeekIconMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPasswordEntry a) => O.OverloadedMethod PasswordEntrySetShowPeekIconMethodInfo a signature where
    overloadedMethod = passwordEntrySetShowPeekIcon

instance O.OverloadedMethodInfo PasswordEntrySetShowPeekIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PasswordEntry.passwordEntrySetShowPeekIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PasswordEntry.html#v:passwordEntrySetShowPeekIcon"
        }


#endif