{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.ThemedIcon.ThemedIcon' is an implementation of t'GI.Gio.Interfaces.Icon.Icon' that supports icon themes.
-- t'GI.Gio.Objects.ThemedIcon.ThemedIcon' contains a list of all of the icons present in an icon
-- theme, so that icons can be looked up quickly. t'GI.Gio.Objects.ThemedIcon.ThemedIcon' does
-- not provide actual pixmaps for icons, just the icon names.
-- Ideally something like @/gtk_icon_theme_choose_icon()/@ should be used to
-- resolve the list of names so that fallback icons work nicely with
-- themes that inherit other themes.

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

module GI.Gio.Objects.ThemedIcon
    ( 

-- * Exported types
    ThemedIcon(..)                          ,
    IsThemedIcon                            ,
    toThemedIcon                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [appendName]("GI.Gio.Objects.ThemedIcon#g:method:appendName"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [equal]("GI.Gio.Interfaces.Icon#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [prependName]("GI.Gio.Objects.ThemedIcon#g:method:prependName"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [serialize]("GI.Gio.Interfaces.Icon#g:method:serialize"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Interfaces.Icon#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getNames]("GI.Gio.Objects.ThemedIcon#g:method:getNames"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveThemedIconMethod                 ,
#endif

-- ** appendName #method:appendName#

#if defined(ENABLE_OVERLOADING)
    ThemedIconAppendNameMethodInfo          ,
#endif
    themedIconAppendName                    ,


-- ** getNames #method:getNames#

#if defined(ENABLE_OVERLOADING)
    ThemedIconGetNamesMethodInfo            ,
#endif
    themedIconGetNames                      ,


-- ** new #method:new#

    themedIconNew                           ,


-- ** newFromNames #method:newFromNames#

    themedIconNewFromNames                  ,


-- ** newWithDefaultFallbacks #method:newWithDefaultFallbacks#

    themedIconNewWithDefaultFallbacks       ,


-- ** prependName #method:prependName#

#if defined(ENABLE_OVERLOADING)
    ThemedIconPrependNameMethodInfo         ,
#endif
    themedIconPrependName                   ,




 -- * Properties


-- ** name #attr:name#
-- | The icon name.

#if defined(ENABLE_OVERLOADING)
    ThemedIconNamePropertyInfo              ,
#endif
    constructThemedIconName                 ,
#if defined(ENABLE_OVERLOADING)
    themedIconName                          ,
#endif


-- ** names #attr:names#
-- | A 'P.Nothing'-terminated array of icon names.

#if defined(ENABLE_OVERLOADING)
    ThemedIconNamesPropertyInfo             ,
#endif
    constructThemedIconNames                ,
    getThemedIconNames                      ,
#if defined(ENABLE_OVERLOADING)
    themedIconNames                         ,
#endif


-- ** useDefaultFallbacks #attr:useDefaultFallbacks#
-- | Whether to use the default fallbacks found by shortening the icon name
-- at \'-\' characters. If the \"names\" array has more than one element,
-- ignores any past the first.
-- 
-- For example, if the icon name was \"gnome-dev-cdrom-audio\", the array
-- would become
-- 
-- === /C code/
-- >
-- >{
-- >  "gnome-dev-cdrom-audio",
-- >  "gnome-dev-cdrom",
-- >  "gnome-dev",
-- >  "gnome",
-- >  NULL
-- >};

#if defined(ENABLE_OVERLOADING)
    ThemedIconUseDefaultFallbacksPropertyInfo,
#endif
    constructThemedIconUseDefaultFallbacks  ,
    getThemedIconUseDefaultFallbacks        ,
#if defined(ENABLE_OVERLOADING)
    themedIconUseDefaultFallbacks           ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon

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

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

foreign import ccall "g_themed_icon_get_type"
    c_g_themed_icon_get_type :: IO B.Types.GType

instance B.Types.TypedObject ThemedIcon where
    glibType :: IO GType
glibType = IO GType
c_g_themed_icon_get_type

instance B.Types.GObject ThemedIcon

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

instance O.HasParentTypes ThemedIcon
type instance O.ParentTypes ThemedIcon = '[GObject.Object.Object, Gio.Icon.Icon]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveThemedIconMethod (t :: Symbol) (o :: *) :: * where
    ResolveThemedIconMethod "appendName" o = ThemedIconAppendNameMethodInfo
    ResolveThemedIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveThemedIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveThemedIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
    ResolveThemedIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveThemedIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveThemedIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveThemedIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveThemedIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveThemedIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveThemedIconMethod "prependName" o = ThemedIconPrependNameMethodInfo
    ResolveThemedIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveThemedIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveThemedIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveThemedIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
    ResolveThemedIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveThemedIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveThemedIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveThemedIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
    ResolveThemedIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveThemedIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveThemedIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveThemedIconMethod "getNames" o = ThemedIconGetNamesMethodInfo
    ResolveThemedIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveThemedIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveThemedIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveThemedIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveThemedIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveThemedIconMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ThemedIconNamePropertyInfo
instance AttrInfo ThemedIconNamePropertyInfo where
    type AttrAllowedOps ThemedIconNamePropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ThemedIconNamePropertyInfo = IsThemedIcon
    type AttrSetTypeConstraint ThemedIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ThemedIconNamePropertyInfo = (~) T.Text
    type AttrTransferType ThemedIconNamePropertyInfo = T.Text
    type AttrGetType ThemedIconNamePropertyInfo = ()
    type AttrLabel ThemedIconNamePropertyInfo = "name"
    type AttrOrigin ThemedIconNamePropertyInfo = ThemedIcon
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructThemedIconName
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#g:attr:name"
        })
#endif

-- VVV Prop "names"
   -- Type: TCArray True (-1) (-1) (TBasicType TUTF8)
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

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

#if defined(ENABLE_OVERLOADING)
data ThemedIconNamesPropertyInfo
instance AttrInfo ThemedIconNamesPropertyInfo where
    type AttrAllowedOps ThemedIconNamesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ThemedIconNamesPropertyInfo = IsThemedIcon
    type AttrSetTypeConstraint ThemedIconNamesPropertyInfo = (~) [T.Text]
    type AttrTransferTypeConstraint ThemedIconNamesPropertyInfo = (~) [T.Text]
    type AttrTransferType ThemedIconNamesPropertyInfo = [T.Text]
    type AttrGetType ThemedIconNamesPropertyInfo = [T.Text]
    type AttrLabel ThemedIconNamesPropertyInfo = "names"
    type AttrOrigin ThemedIconNamesPropertyInfo = ThemedIcon
    attrGet = getThemedIconNames
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructThemedIconNames
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.names"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#g:attr:names"
        })
#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@use-default-fallbacks@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructThemedIconUseDefaultFallbacks :: (IsThemedIcon o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructThemedIconUseDefaultFallbacks :: forall o (m :: * -> *).
(IsThemedIcon o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructThemedIconUseDefaultFallbacks Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-default-fallbacks" Bool
val

#if defined(ENABLE_OVERLOADING)
data ThemedIconUseDefaultFallbacksPropertyInfo
instance AttrInfo ThemedIconUseDefaultFallbacksPropertyInfo where
    type AttrAllowedOps ThemedIconUseDefaultFallbacksPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = IsThemedIcon
    type AttrSetTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ThemedIconUseDefaultFallbacksPropertyInfo = (~) Bool
    type AttrTransferType ThemedIconUseDefaultFallbacksPropertyInfo = Bool
    type AttrGetType ThemedIconUseDefaultFallbacksPropertyInfo = Bool
    type AttrLabel ThemedIconUseDefaultFallbacksPropertyInfo = "use-default-fallbacks"
    type AttrOrigin ThemedIconUseDefaultFallbacksPropertyInfo = ThemedIcon
    attrGet = getThemedIconUseDefaultFallbacks
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructThemedIconUseDefaultFallbacks
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.useDefaultFallbacks"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#g:attr:useDefaultFallbacks"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ThemedIcon
type instance O.AttributeList ThemedIcon = ThemedIconAttributeList
type ThemedIconAttributeList = ('[ '("name", ThemedIconNamePropertyInfo), '("names", ThemedIconNamesPropertyInfo), '("useDefaultFallbacks", ThemedIconUseDefaultFallbacksPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
themedIconName :: AttrLabelProxy "name"
themedIconName = AttrLabelProxy

themedIconNames :: AttrLabelProxy "names"
themedIconNames = AttrLabelProxy

themedIconUseDefaultFallbacks :: AttrLabelProxy "useDefaultFallbacks"
themedIconUseDefaultFallbacks = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ThemedIcon = ThemedIconSignalList
type ThemedIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "g_themed_icon_new" g_themed_icon_new :: 
    CString ->                              -- iconname : TBasicType TUTF8
    IO (Ptr ThemedIcon)

-- | Creates a new themed icon for /@iconname@/.
themedIconNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@iconname@/: a string containing an icon name.
    -> m ThemedIcon
    -- ^ __Returns:__ a new t'GI.Gio.Objects.ThemedIcon.ThemedIcon'.
themedIconNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m ThemedIcon
themedIconNew Text
iconname = IO ThemedIcon -> m ThemedIcon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
    CString
iconname' <- Text -> IO CString
textToCString Text
iconname
    Ptr ThemedIcon
result <- CString -> IO (Ptr ThemedIcon)
g_themed_icon_new CString
iconname'
    Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNew" Ptr ThemedIcon
result
    ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
    ThemedIcon -> IO ThemedIcon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThemedIcon::new_from_names
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "iconnames"
--           , argType = TCArray False (-1) 1 (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of strings containing icon names."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the length of the @iconnames array, or -1 if @iconnames is\n    %NULL-terminated"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "len"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "the length of the @iconnames array, or -1 if @iconnames is\n    %NULL-terminated"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "ThemedIcon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_new_from_names" g_themed_icon_new_from_names :: 
    Ptr CString ->                          -- iconnames : TCArray False (-1) 1 (TBasicType TUTF8)
    Int32 ->                                -- len : TBasicType TInt
    IO (Ptr ThemedIcon)

-- | Creates a new themed icon for /@iconnames@/.
themedIconNewFromNames ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [T.Text]
    -- ^ /@iconnames@/: an array of strings containing icon names.
    -> m ThemedIcon
    -- ^ __Returns:__ a new t'GI.Gio.Objects.ThemedIcon.ThemedIcon'
themedIconNewFromNames :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[Text] -> m ThemedIcon
themedIconNewFromNames [Text]
iconnames = IO ThemedIcon -> m ThemedIcon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
    let len :: Int32
len = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
iconnames
    Ptr CString
iconnames' <- [Text] -> IO (Ptr CString)
packUTF8CArray [Text]
iconnames
    Ptr ThemedIcon
result <- Ptr CString -> Int32 -> IO (Ptr ThemedIcon)
g_themed_icon_new_from_names Ptr CString
iconnames' Int32
len
    Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNewFromNames" Ptr ThemedIcon
result
    ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
    (Int32 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Int32
len) CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconnames'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconnames'
    ThemedIcon -> IO ThemedIcon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThemedIcon::new_with_default_fallbacks
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "iconname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing an icon name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "ThemedIcon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_new_with_default_fallbacks" g_themed_icon_new_with_default_fallbacks :: 
    CString ->                              -- iconname : TBasicType TUTF8
    IO (Ptr ThemedIcon)

-- | Creates a new themed icon for /@iconname@/, and all the names
-- that can be created by shortening /@iconname@/ at \'-\' characters.
-- 
-- In the following example, /@icon1@/ and /@icon2@/ are equivalent:
-- 
-- === /C code/
-- >
-- >const char *names[] = {
-- >  "gnome-dev-cdrom-audio",
-- >  "gnome-dev-cdrom",
-- >  "gnome-dev",
-- >  "gnome"
-- >};
-- >
-- >icon1 = g_themed_icon_new_from_names (names, 4);
-- >icon2 = g_themed_icon_new_with_default_fallbacks ("gnome-dev-cdrom-audio");
themedIconNewWithDefaultFallbacks ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@iconname@/: a string containing an icon name
    -> m ThemedIcon
    -- ^ __Returns:__ a new t'GI.Gio.Objects.ThemedIcon.ThemedIcon'.
themedIconNewWithDefaultFallbacks :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m ThemedIcon
themedIconNewWithDefaultFallbacks Text
iconname = IO ThemedIcon -> m ThemedIcon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemedIcon -> m ThemedIcon) -> IO ThemedIcon -> m ThemedIcon
forall a b. (a -> b) -> a -> b
$ do
    CString
iconname' <- Text -> IO CString
textToCString Text
iconname
    Ptr ThemedIcon
result <- CString -> IO (Ptr ThemedIcon)
g_themed_icon_new_with_default_fallbacks CString
iconname'
    Text -> Ptr ThemedIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconNewWithDefaultFallbacks" Ptr ThemedIcon
result
    ThemedIcon
result' <- ((ManagedPtr ThemedIcon -> ThemedIcon)
-> Ptr ThemedIcon -> IO ThemedIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ThemedIcon -> ThemedIcon
ThemedIcon) Ptr ThemedIcon
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
    ThemedIcon -> IO ThemedIcon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ThemedIcon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ThemedIcon::append_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ThemedIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThemedIcon" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iconname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "name of icon to append to list of icons from within @icon."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_append_name" g_themed_icon_append_name :: 
    Ptr ThemedIcon ->                       -- icon : TInterface (Name {namespace = "Gio", name = "ThemedIcon"})
    CString ->                              -- iconname : TBasicType TUTF8
    IO ()

-- | Append a name to the list of icons from within /@icon@/.
-- 
-- Note that doing so invalidates the hash computed by prior calls
-- to 'GI.Gio.Functions.iconHash'.
themedIconAppendName ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Objects.ThemedIcon.ThemedIcon'
    -> T.Text
    -- ^ /@iconname@/: name of icon to append to list of icons from within /@icon@/.
    -> m ()
themedIconAppendName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsThemedIcon a) =>
a -> Text -> m ()
themedIconAppendName a
icon Text
iconname = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    CString
iconname' <- Text -> IO CString
textToCString Text
iconname
    Ptr ThemedIcon -> CString -> IO ()
g_themed_icon_append_name Ptr ThemedIcon
icon' CString
iconname'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo ThemedIconAppendNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.themedIconAppendName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#v:themedIconAppendName"
        })


#endif

-- method ThemedIcon::get_names
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ThemedIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThemedIcon." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_get_names" g_themed_icon_get_names :: 
    Ptr ThemedIcon ->                       -- icon : TInterface (Name {namespace = "Gio", name = "ThemedIcon"})
    IO (Ptr CString)

-- | Gets the names of icons from within /@icon@/.
themedIconGetNames ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Objects.ThemedIcon.ThemedIcon'.
    -> m [T.Text]
    -- ^ __Returns:__ a list of icon names.
themedIconGetNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsThemedIcon a) =>
a -> m [Text]
themedIconGetNames a
icon = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr CString
result <- Ptr ThemedIcon -> IO (Ptr CString)
g_themed_icon_get_names Ptr ThemedIcon
icon'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"themedIconGetNames" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data ThemedIconGetNamesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsThemedIcon a) => O.OverloadedMethod ThemedIconGetNamesMethodInfo a signature where
    overloadedMethod = themedIconGetNames

instance O.OverloadedMethodInfo ThemedIconGetNamesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.themedIconGetNames",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#v:themedIconGetNames"
        })


#endif

-- method ThemedIcon::prepend_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "ThemedIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GThemedIcon" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iconname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "name of icon to prepend to list of icons from within @icon."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_themed_icon_prepend_name" g_themed_icon_prepend_name :: 
    Ptr ThemedIcon ->                       -- icon : TInterface (Name {namespace = "Gio", name = "ThemedIcon"})
    CString ->                              -- iconname : TBasicType TUTF8
    IO ()

-- | Prepend a name to the list of icons from within /@icon@/.
-- 
-- Note that doing so invalidates the hash computed by prior calls
-- to 'GI.Gio.Functions.iconHash'.
-- 
-- /Since: 2.18/
themedIconPrependName ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemedIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Objects.ThemedIcon.ThemedIcon'
    -> T.Text
    -- ^ /@iconname@/: name of icon to prepend to list of icons from within /@icon@/.
    -> m ()
themedIconPrependName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsThemedIcon a) =>
a -> Text -> m ()
themedIconPrependName a
icon Text
iconname = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemedIcon
icon' <- a -> IO (Ptr ThemedIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    CString
iconname' <- Text -> IO CString
textToCString Text
iconname
    Ptr ThemedIcon -> CString -> IO ()
g_themed_icon_prepend_name Ptr ThemedIcon
icon' CString
iconname'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconname'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo ThemedIconPrependNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.ThemedIcon.themedIconPrependName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-ThemedIcon.html#v:themedIconPrependName"
        })


#endif