{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A widget displaying an image, with a generated fallback.
-- 
-- @AdwAvatar@ is a widget that shows a round avatar.
-- 
-- @AdwAvatar@ generates an avatar with the initials of  the
-- [Avatar:text]("GI.Adw.Objects.Avatar#g:attr:text") on top of a colored background.
-- 
-- The color is picked based on the hash of the [Avatar:text]("GI.Adw.Objects.Avatar#g:attr:text").
-- 
-- If [Avatar:showInitials]("GI.Adw.Objects.Avatar#g:attr:showInitials") is set to @FALSE@,
-- [Avatar:iconName]("GI.Adw.Objects.Avatar#g:attr:iconName") or @avatar-default-symbolic@ is shown instead
-- of the initials.
-- 
-- Use [Avatar:customImage]("GI.Adw.Objects.Avatar#g:attr:customImage") to set a custom image.
-- 
-- == CSS nodes
-- 
-- @AdwAvatar@ has a single CSS node with name @avatar@.
-- 
-- /Since: 1.0/

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

module GI.Adw.Objects.Avatar
    ( 

-- * Exported types
    Avatar(..)                              ,
    IsAvatar                                ,
    toAvatar                                ,


 -- * 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"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [drawToTexture]("GI.Adw.Objects.Avatar#g:method:drawToTexture"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getCustomImage]("GI.Adw.Objects.Avatar#g:method:getCustomImage"), [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"), [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.Adw.Objects.Avatar#g:method:getIconName"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getShowInitials]("GI.Adw.Objects.Avatar#g:method:getShowInitials"), [getSize]("GI.Adw.Objects.Avatar#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.Adw.Objects.Avatar#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").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setCustomImage]("GI.Adw.Objects.Avatar#g:method:setCustomImage"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Adw.Objects.Avatar#g:method:setIconName"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setShowInitials]("GI.Adw.Objects.Avatar#g:method:setShowInitials"), [setSize]("GI.Adw.Objects.Avatar#g:method:setSize"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setText]("GI.Adw.Objects.Avatar#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").

#if defined(ENABLE_OVERLOADING)
    ResolveAvatarMethod                     ,
#endif

-- ** drawToTexture #method:drawToTexture#

#if defined(ENABLE_OVERLOADING)
    AvatarDrawToTextureMethodInfo           ,
#endif
    avatarDrawToTexture                     ,


-- ** getCustomImage #method:getCustomImage#

#if defined(ENABLE_OVERLOADING)
    AvatarGetCustomImageMethodInfo          ,
#endif
    avatarGetCustomImage                    ,


-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    AvatarGetIconNameMethodInfo             ,
#endif
    avatarGetIconName                       ,


-- ** getShowInitials #method:getShowInitials#

#if defined(ENABLE_OVERLOADING)
    AvatarGetShowInitialsMethodInfo         ,
#endif
    avatarGetShowInitials                   ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    AvatarGetSizeMethodInfo                 ,
#endif
    avatarGetSize                           ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    AvatarGetTextMethodInfo                 ,
#endif
    avatarGetText                           ,


-- ** new #method:new#

    avatarNew                               ,


-- ** setCustomImage #method:setCustomImage#

#if defined(ENABLE_OVERLOADING)
    AvatarSetCustomImageMethodInfo          ,
#endif
    avatarSetCustomImage                    ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    AvatarSetIconNameMethodInfo             ,
#endif
    avatarSetIconName                       ,


-- ** setShowInitials #method:setShowInitials#

#if defined(ENABLE_OVERLOADING)
    AvatarSetShowInitialsMethodInfo         ,
#endif
    avatarSetShowInitials                   ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    AvatarSetSizeMethodInfo                 ,
#endif
    avatarSetSize                           ,


-- ** setText #method:setText#

#if defined(ENABLE_OVERLOADING)
    AvatarSetTextMethodInfo                 ,
#endif
    avatarSetText                           ,




 -- * Properties


-- ** customImage #attr:customImage#
-- | A custom image to use instead of initials or icon.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    AvatarCustomImagePropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    avatarCustomImage                       ,
#endif
    clearAvatarCustomImage                  ,
    constructAvatarCustomImage              ,
    getAvatarCustomImage                    ,
    setAvatarCustomImage                    ,


-- ** iconName #attr:iconName#
-- | The name of an icon to use as a fallback.
-- 
-- If no name is set, @avatar-default-symbolic@ will be used.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    AvatarIconNamePropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    avatarIconName                          ,
#endif
    clearAvatarIconName                     ,
    constructAvatarIconName                 ,
    getAvatarIconName                       ,
    setAvatarIconName                       ,


-- ** showInitials #attr:showInitials#
-- | Whether initials are used instead of an icon on the fallback avatar.
-- 
-- See [Avatar:iconName]("GI.Adw.Objects.Avatar#g:attr:iconName") for how to change the fallback icon.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    AvatarShowInitialsPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    avatarShowInitials                      ,
#endif
    constructAvatarShowInitials             ,
    getAvatarShowInitials                   ,
    setAvatarShowInitials                   ,


-- ** size #attr:size#
-- | The size of the avatar.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    AvatarSizePropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    avatarSize                              ,
#endif
    constructAvatarSize                     ,
    getAvatarSize                           ,
    setAvatarSize                           ,


-- ** text #attr:text#
-- | Sets the text used to generate the fallback initials and color.
-- 
-- It\'s only used to generate the color if [Avatar:showInitials]("GI.Adw.Objects.Avatar#g:attr:showInitials")
-- is @FALSE@.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    AvatarTextPropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    avatarText                              ,
#endif
    clearAvatarText                         ,
    constructAvatarText                     ,
    getAvatarText                           ,
    setAvatarText                           ,




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

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

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

foreign import ccall "adw_avatar_get_type"
    c_adw_avatar_get_type :: IO B.Types.GType

instance B.Types.TypedObject Avatar where
    glibType :: IO GType
glibType = IO GType
c_adw_avatar_get_type

instance B.Types.GObject Avatar

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "custom-image"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Paintable"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

-- | Set the value of the “@custom-image@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' avatar [ #customImage 'Data.GI.Base.Attributes.:=' value ]
-- @
setAvatarCustomImage :: (MonadIO m, IsAvatar o, Gdk.Paintable.IsPaintable a) => o -> a -> m ()
setAvatarCustomImage :: forall (m :: * -> *) o a.
(MonadIO m, IsAvatar o, IsPaintable a) =>
o -> a -> m ()
setAvatarCustomImage 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
"custom-image" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

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

-- | Set the value of the “@custom-image@” 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' #customImage
-- @
clearAvatarCustomImage :: (MonadIO m, IsAvatar o) => o -> m ()
clearAvatarCustomImage :: forall (m :: * -> *) o. (MonadIO m, IsAvatar o) => o -> m ()
clearAvatarCustomImage 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 Paintable -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"custom-image" (Maybe Paintable
forall a. Maybe a
Nothing :: Maybe Gdk.Paintable.Paintable)

#if defined(ENABLE_OVERLOADING)
data AvatarCustomImagePropertyInfo
instance AttrInfo AvatarCustomImagePropertyInfo where
    type AttrAllowedOps AvatarCustomImagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AvatarCustomImagePropertyInfo = IsAvatar
    type AttrSetTypeConstraint AvatarCustomImagePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferTypeConstraint AvatarCustomImagePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferType AvatarCustomImagePropertyInfo = Gdk.Paintable.Paintable
    type AttrGetType AvatarCustomImagePropertyInfo = (Maybe Gdk.Paintable.Paintable)
    type AttrLabel AvatarCustomImagePropertyInfo = "custom-image"
    type AttrOrigin AvatarCustomImagePropertyInfo = Avatar
    attrGet = getAvatarCustomImage
    attrSet = setAvatarCustomImage
    attrTransfer _ v = do
        unsafeCastTo Gdk.Paintable.Paintable v
    attrConstruct = constructAvatarCustomImage
    attrClear = clearAvatarCustomImage
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Avatar.customImage"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.1/docs/GI-Adw-Objects-Avatar.html#g:attr:customImage"
        })
#endif

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

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

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

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

-- | Set the value of the “@icon-name@” 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' #iconName
-- @
clearAvatarIconName :: (MonadIO m, IsAvatar o) => o -> m ()
clearAvatarIconName :: forall (m :: * -> *) o. (MonadIO m, IsAvatar o) => o -> m ()
clearAvatarIconName 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
"icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data AvatarIconNamePropertyInfo
instance AttrInfo AvatarIconNamePropertyInfo where
    type AttrAllowedOps AvatarIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AvatarIconNamePropertyInfo = IsAvatar
    type AttrSetTypeConstraint AvatarIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AvatarIconNamePropertyInfo = (~) T.Text
    type AttrTransferType AvatarIconNamePropertyInfo = T.Text
    type AttrGetType AvatarIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel AvatarIconNamePropertyInfo = "icon-name"
    type AttrOrigin AvatarIconNamePropertyInfo = Avatar
    attrGet = getAvatarIconName
    attrSet = setAvatarIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructAvatarIconName
    attrClear = clearAvatarIconName
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Avatar.iconName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.1/docs/GI-Adw-Objects-Avatar.html#g:attr:iconName"
        })
#endif

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

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

-- | Set the value of the “@show-initials@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' avatar [ #showInitials 'Data.GI.Base.Attributes.:=' value ]
-- @
setAvatarShowInitials :: (MonadIO m, IsAvatar o) => o -> Bool -> m ()
setAvatarShowInitials :: forall (m :: * -> *) o.
(MonadIO m, IsAvatar o) =>
o -> Bool -> m ()
setAvatarShowInitials 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-initials" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data AvatarShowInitialsPropertyInfo
instance AttrInfo AvatarShowInitialsPropertyInfo where
    type AttrAllowedOps AvatarShowInitialsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AvatarShowInitialsPropertyInfo = IsAvatar
    type AttrSetTypeConstraint AvatarShowInitialsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint AvatarShowInitialsPropertyInfo = (~) Bool
    type AttrTransferType AvatarShowInitialsPropertyInfo = Bool
    type AttrGetType AvatarShowInitialsPropertyInfo = Bool
    type AttrLabel AvatarShowInitialsPropertyInfo = "show-initials"
    type AttrOrigin AvatarShowInitialsPropertyInfo = Avatar
    attrGet = getAvatarShowInitials
    attrSet = setAvatarShowInitials
    attrTransfer _ v = do
        return v
    attrConstruct = constructAvatarShowInitials
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Avatar.showInitials"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.1/docs/GI-Adw-Objects-Avatar.html#g:attr:showInitials"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data AvatarSizePropertyInfo
instance AttrInfo AvatarSizePropertyInfo where
    type AttrAllowedOps AvatarSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AvatarSizePropertyInfo = IsAvatar
    type AttrSetTypeConstraint AvatarSizePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint AvatarSizePropertyInfo = (~) Int32
    type AttrTransferType AvatarSizePropertyInfo = Int32
    type AttrGetType AvatarSizePropertyInfo = Int32
    type AttrLabel AvatarSizePropertyInfo = "size"
    type AttrOrigin AvatarSizePropertyInfo = Avatar
    attrGet = getAvatarSize
    attrSet = setAvatarSize
    attrTransfer _ v = do
        return v
    attrConstruct = constructAvatarSize
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Avatar.size"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.1/docs/GI-Adw-Objects-Avatar.html#g:attr:size"
        })
#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data AvatarTextPropertyInfo
instance AttrInfo AvatarTextPropertyInfo where
    type AttrAllowedOps AvatarTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AvatarTextPropertyInfo = IsAvatar
    type AttrSetTypeConstraint AvatarTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AvatarTextPropertyInfo = (~) T.Text
    type AttrTransferType AvatarTextPropertyInfo = T.Text
    type AttrGetType AvatarTextPropertyInfo = (Maybe T.Text)
    type AttrLabel AvatarTextPropertyInfo = "text"
    type AttrOrigin AvatarTextPropertyInfo = Avatar
    attrGet = getAvatarText
    attrSet = setAvatarText
    attrTransfer _ v = do
        return v
    attrConstruct = constructAvatarText
    attrClear = clearAvatarText
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Avatar.text"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.1/docs/GI-Adw-Objects-Avatar.html#g:attr:text"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Avatar
type instance O.AttributeList Avatar = AvatarAttributeList
type AvatarAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("customImage", AvatarCustomImagePropertyInfo), '("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), '("iconName", AvatarIconNamePropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showInitials", AvatarShowInitialsPropertyInfo), '("size", AvatarSizePropertyInfo), '("text", AvatarTextPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
avatarCustomImage :: AttrLabelProxy "customImage"
avatarCustomImage = AttrLabelProxy

avatarIconName :: AttrLabelProxy "iconName"
avatarIconName = AttrLabelProxy

avatarShowInitials :: AttrLabelProxy "showInitials"
avatarShowInitials = AttrLabelProxy

avatarSize :: AttrLabelProxy "size"
avatarSize = AttrLabelProxy

avatarText :: AttrLabelProxy "text"
avatarText = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Avatar = AvatarSignalList
type AvatarSignalList = ('[ '("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 Avatar::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The size of the avatar"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text used to get the initials and color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "show_initials"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether to use initials instead of an icon as fallback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Adw" , name = "Avatar" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_avatar_new" adw_avatar_new :: 
    Int32 ->                                -- size : TBasicType TInt
    CString ->                              -- text : TBasicType TUTF8
    CInt ->                                 -- show_initials : TBasicType TBoolean
    IO (Ptr Avatar)

-- | Creates a new @AdwAvatar@.
-- 
-- /Since: 1.0/
avatarNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@size@/: The size of the avatar
    -> Maybe (T.Text)
    -- ^ /@text@/: the text used to get the initials and color
    -> Bool
    -- ^ /@showInitials@/: whether to use initials instead of an icon as fallback
    -> m Avatar
    -- ^ __Returns:__ the newly created @AdwAvatar@
avatarNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32 -> Maybe Text -> Bool -> m Avatar
avatarNew Int32
size Maybe Text
text Bool
showInitials = IO Avatar -> m Avatar
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Avatar -> m Avatar) -> IO Avatar -> m Avatar
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeText <- case Maybe Text
text of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jText -> do
            Ptr CChar
jText' <- Text -> IO (Ptr CChar)
textToCString Text
jText
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jText'
    let showInitials' :: CInt
showInitials' = (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
showInitials
    Ptr Avatar
result <- Int32 -> Ptr CChar -> CInt -> IO (Ptr Avatar)
adw_avatar_new Int32
size Ptr CChar
maybeText CInt
showInitials'
    Text -> Ptr Avatar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"avatarNew" Ptr Avatar
result
    Avatar
result' <- ((ManagedPtr Avatar -> Avatar) -> Ptr Avatar -> IO Avatar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Avatar -> Avatar
Avatar) Ptr Avatar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeText
    Avatar -> IO Avatar
forall (m :: * -> *) a. Monad m => a -> m a
return Avatar
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Avatar::draw_to_texture
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale_factor"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The scale factor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Texture" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_avatar_draw_to_texture" adw_avatar_draw_to_texture :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    Int32 ->                                -- scale_factor : TBasicType TInt
    IO (Ptr Gdk.Texture.Texture)

-- | Renders /@self@/ into a t'GI.Gdk.Objects.Texture.Texture' at /@scaleFactor@/.
-- 
-- This can be used to export the fallback avatar.
-- 
-- /Since: 1.0/
avatarDrawToTexture ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Int32
    -- ^ /@scaleFactor@/: The scale factor
    -> m Gdk.Texture.Texture
    -- ^ __Returns:__ the texture
avatarDrawToTexture :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> Int32 -> m Texture
avatarDrawToTexture a
self Int32
scaleFactor = IO Texture -> m Texture
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Texture -> m Texture) -> IO Texture -> m Texture
forall a b. (a -> b) -> a -> b
$ do
    Ptr Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Texture
result <- Ptr Avatar -> Int32 -> IO (Ptr Texture)
adw_avatar_draw_to_texture Ptr Avatar
self' Int32
scaleFactor
    Text -> Ptr Texture -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"avatarDrawToTexture" Ptr Texture
result
    Texture
result' <- ((ManagedPtr Texture -> Texture) -> Ptr Texture -> IO Texture
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Texture -> Texture
Gdk.Texture.Texture) Ptr Texture
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Texture -> IO Texture
forall (m :: * -> *) a. Monad m => a -> m a
return Texture
result'

#if defined(ENABLE_OVERLOADING)
data AvatarDrawToTextureMethodInfo
instance (signature ~ (Int32 -> m Gdk.Texture.Texture), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarDrawToTextureMethodInfo a signature where
    overloadedMethod = avatarDrawToTexture

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


#endif

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

foreign import ccall "adw_avatar_get_custom_image" adw_avatar_get_custom_image :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    IO (Ptr Gdk.Paintable.Paintable)

-- | Gets the custom image paintable.
-- 
-- /Since: 1.0/
avatarGetCustomImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> m (Maybe Gdk.Paintable.Paintable)
    -- ^ __Returns:__ the custom image
avatarGetCustomImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> m (Maybe Paintable)
avatarGetCustomImage a
self = IO (Maybe Paintable) -> m (Maybe Paintable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Paintable) -> m (Maybe Paintable))
-> IO (Maybe Paintable) -> m (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Paintable
result <- Ptr Avatar -> IO (Ptr Paintable)
adw_avatar_get_custom_image Ptr Avatar
self'
    Maybe Paintable
maybeResult <- Ptr Paintable
-> (Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Paintable
result ((Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable))
-> (Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ \Ptr Paintable
result' -> do
        Paintable
result'' <- ((ManagedPtr Paintable -> Paintable)
-> Ptr Paintable -> IO Paintable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Paintable -> Paintable
Gdk.Paintable.Paintable) Ptr Paintable
result'
        Paintable -> IO Paintable
forall (m :: * -> *) a. Monad m => a -> m a
return Paintable
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Paintable -> IO (Maybe Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Paintable
maybeResult

#if defined(ENABLE_OVERLOADING)
data AvatarGetCustomImageMethodInfo
instance (signature ~ (m (Maybe Gdk.Paintable.Paintable)), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarGetCustomImageMethodInfo a signature where
    overloadedMethod = avatarGetCustomImage

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


#endif

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

foreign import ccall "adw_avatar_get_icon_name" adw_avatar_get_icon_name :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    IO CString

-- | Gets the name of an icon to use as a fallback.
-- 
-- /Since: 1.0/
avatarGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the icon name
avatarGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> m (Maybe Text)
avatarGetIconName a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
result <- Ptr Avatar -> IO (Ptr CChar)
adw_avatar_get_icon_name Ptr Avatar
self'
    Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
        Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

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


#endif

-- method Avatar::get_show_initials
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , 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 "adw_avatar_get_show_initials" adw_avatar_get_show_initials :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    IO CInt

-- | Gets whether initials are used instead of an icon on the fallback avatar.
-- 
-- /Since: 1.0/
avatarGetShowInitials ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> m Bool
    -- ^ __Returns:__ whether initials are used instead of an icon as fallback
avatarGetShowInitials :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> m Bool
avatarGetShowInitials a
self = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Avatar -> IO CInt
adw_avatar_get_show_initials Ptr Avatar
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AvatarGetShowInitialsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarGetShowInitialsMethodInfo a signature where
    overloadedMethod = avatarGetShowInitials

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


#endif

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

foreign import ccall "adw_avatar_get_size" adw_avatar_get_size :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    IO Int32

-- | Gets the size of the avatar.
-- 
-- /Since: 1.0/
avatarGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> m Int32
    -- ^ __Returns:__ the size of the avatar
avatarGetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> m Int32
avatarGetSize a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Avatar -> IO Int32
adw_avatar_get_size Ptr Avatar
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data AvatarGetSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarGetSizeMethodInfo a signature where
    overloadedMethod = avatarGetSize

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


#endif

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

foreign import ccall "adw_avatar_get_text" adw_avatar_get_text :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    IO CString

-- | Gets the text used to generate the fallback initials and color.
-- 
-- /Since: 1.0/
avatarGetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the text used to generate the fallback initials and
    --   color
avatarGetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> m (Maybe Text)
avatarGetText a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
result <- Ptr Avatar -> IO (Ptr CChar)
adw_avatar_get_text Ptr Avatar
self'
    Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
        Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

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


#endif

-- method Avatar::set_custom_image
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "custom_image"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Paintable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a custom image" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_avatar_set_custom_image" adw_avatar_set_custom_image :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    Ptr Gdk.Paintable.Paintable ->          -- custom_image : TInterface (Name {namespace = "Gdk", name = "Paintable"})
    IO ()

-- | Sets the custom image paintable.
-- 
-- /Since: 1.0/
avatarSetCustomImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a, Gdk.Paintable.IsPaintable b) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Maybe (b)
    -- ^ /@customImage@/: a custom image
    -> m ()
avatarSetCustomImage :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAvatar a, IsPaintable b) =>
a -> Maybe b -> m ()
avatarSetCustomImage a
self Maybe b
customImage = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Paintable
maybeCustomImage <- case Maybe b
customImage of
        Maybe b
Nothing -> Ptr Paintable -> IO (Ptr Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Paintable
forall a. Ptr a
nullPtr
        Just b
jCustomImage -> do
            Ptr Paintable
jCustomImage' <- b -> IO (Ptr Paintable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCustomImage
            Ptr Paintable -> IO (Ptr Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Paintable
jCustomImage'
    Ptr Avatar -> Ptr Paintable -> IO ()
adw_avatar_set_custom_image Ptr Avatar
self' Ptr Paintable
maybeCustomImage
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
customImage b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AvatarSetCustomImageMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsAvatar a, Gdk.Paintable.IsPaintable b) => O.OverloadedMethod AvatarSetCustomImageMethodInfo a signature where
    overloadedMethod = avatarSetCustomImage

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


#endif

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

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

-- | Sets the name of an icon to use as a fallback.
-- 
-- If no name is set, @avatar-default-symbolic@ will be used.
-- 
-- /Since: 1.0/
avatarSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Maybe (T.Text)
    -- ^ /@iconName@/: the icon name
    -> m ()
avatarSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> Maybe Text -> m ()
avatarSetIconName a
self Maybe Text
iconName = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
maybeIconName <- case Maybe Text
iconName of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jIconName -> do
            Ptr CChar
jIconName' <- Text -> IO (Ptr CChar)
textToCString Text
jIconName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIconName'
    Ptr Avatar -> Ptr CChar -> IO ()
adw_avatar_set_icon_name Ptr Avatar
self' Ptr CChar
maybeIconName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIconName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method Avatar::set_show_initials
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "show_initials"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether to use initials instead of an icon as fallback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_avatar_set_show_initials" adw_avatar_set_show_initials :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    CInt ->                                 -- show_initials : TBasicType TBoolean
    IO ()

-- | Sets whether to use initials instead of an icon on the fallback avatar.
-- 
-- /Since: 1.0/
avatarSetShowInitials ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Bool
    -- ^ /@showInitials@/: whether to use initials instead of an icon as fallback
    -> m ()
avatarSetShowInitials :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> Bool -> m ()
avatarSetShowInitials a
self Bool
showInitials = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let showInitials' :: CInt
showInitials' = (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
showInitials
    Ptr Avatar -> CInt -> IO ()
adw_avatar_set_show_initials Ptr Avatar
self' CInt
showInitials'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AvatarSetShowInitialsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarSetShowInitialsMethodInfo a signature where
    overloadedMethod = avatarSetShowInitials

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


#endif

-- method Avatar::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The size of the avatar"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_avatar_set_size" adw_avatar_set_size :: 
    Ptr Avatar ->                           -- self : TInterface (Name {namespace = "Adw", name = "Avatar"})
    Int32 ->                                -- size : TBasicType TInt
    IO ()

-- | Sets the size of the avatar.
-- 
-- /Since: 1.0/
avatarSetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Int32
    -- ^ /@size@/: The size of the avatar
    -> m ()
avatarSetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> Int32 -> m ()
avatarSetSize a
self Int32
size = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Avatar -> Int32 -> IO ()
adw_avatar_set_size Ptr Avatar
self' Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AvatarSetSizeMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsAvatar a) => O.OverloadedMethod AvatarSetSizeMethodInfo a signature where
    overloadedMethod = avatarSetSize

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


#endif

-- method Avatar::set_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Avatar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwAvatar`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text used to get the initials and color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets the text used to generate the fallback initials and color.
-- 
-- /Since: 1.0/
avatarSetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsAvatar a) =>
    a
    -- ^ /@self@/: a @AdwAvatar@
    -> Maybe (T.Text)
    -- ^ /@text@/: the text used to get the initials and color
    -> m ()
avatarSetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAvatar a) =>
a -> Maybe Text -> m ()
avatarSetText a
self Maybe Text
text = 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 Avatar
self' <- a -> IO (Ptr Avatar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
maybeText <- case Maybe Text
text of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jText -> do
            Ptr CChar
jText' <- Text -> IO (Ptr CChar)
textToCString Text
jText
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jText'
    Ptr Avatar -> Ptr CChar -> IO ()
adw_avatar_set_text Ptr Avatar
self' Ptr CChar
maybeText
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeText
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif