{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Interfaces.Icon.Icon' is a very minimal interface for icons. It provides functions
-- for checking the equality of two icons, hashing of icons and
-- serializing an icon to and from strings.
-- 
-- t'GI.Gio.Interfaces.Icon.Icon' does not provide the actual pixmap for the icon as this is out
-- of GIO\'s scope, however implementations of t'GI.Gio.Interfaces.Icon.Icon' may contain the name
-- of an icon (see t'GI.Gio.Objects.ThemedIcon.ThemedIcon'), or the path to an icon (see t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon').
-- 
-- To obtain a hash of a t'GI.Gio.Interfaces.Icon.Icon', see 'GI.Gio.Functions.iconHash'.
-- 
-- To check if two @/GIcons/@ are equal, see 'GI.Gio.Interfaces.Icon.iconEqual'.
-- 
-- For serializing a t'GI.Gio.Interfaces.Icon.Icon', use 'GI.Gio.Interfaces.Icon.iconSerialize' and
-- 'GI.Gio.Functions.iconDeserialize'.
-- 
-- If you want to consume t'GI.Gio.Interfaces.Icon.Icon' (for example, in a toolkit) you must
-- be prepared to handle at least the three following cases:
-- t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon', t'GI.Gio.Objects.ThemedIcon.ThemedIcon' and t'GI.Gio.Objects.EmblemedIcon.EmblemedIcon'.  It may also make
-- sense to have fast-paths for other cases (like handling @/GdkPixbuf/@
-- directly, for example) but all compliant t'GI.Gio.Interfaces.Icon.Icon' implementations
-- outside of GIO must implement t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon'.
-- 
-- If your application or library provides one or more t'GI.Gio.Interfaces.Icon.Icon'
-- implementations you need to ensure that your new implementation also
-- implements t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon'.  Additionally, you must provide an
-- implementation of 'GI.Gio.Interfaces.Icon.iconSerialize' that gives a result that is
-- understood by 'GI.Gio.Functions.iconDeserialize', yielding one of the built-in icon
-- types.

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

module GI.Gio.Interfaces.Icon
    ( 

-- * Exported types
    Icon(..)                                ,
    IsIcon                                  ,
    toIcon                                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [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"), [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"), [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)
    ResolveIconMethod                       ,
#endif

-- ** deserialize #method:deserialize#

    iconDeserialize                         ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    IconEqualMethodInfo                     ,
#endif
    iconEqual                               ,


-- ** hash #method:hash#

    iconHash                                ,


-- ** newForString #method:newForString#

    iconNewForString                        ,


-- ** serialize #method:serialize#

#if defined(ENABLE_OVERLOADING)
    IconSerializeMethodInfo                 ,
#endif
    iconSerialize                           ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    IconToStringMethodInfo                  ,
#endif
    iconToString                            ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "g_icon_get_type"
    c_g_icon_get_type :: IO B.Types.GType

instance B.Types.TypedObject Icon where
    glibType :: IO GType
glibType = IO GType
c_g_icon_get_type

instance B.Types.GObject Icon

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Icon
type instance O.AttributeList Icon = IconAttributeList
type IconAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

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

#endif

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

#endif

-- method Icon::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon1"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the first #GIcon."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon2"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the second #GIcon."
--                 , 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 "g_icon_equal" g_icon_equal :: 
    Ptr Icon ->                             -- icon1 : TInterface (Name {namespace = "Gio", name = "Icon"})
    Ptr Icon ->                             -- icon2 : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO CInt

-- | Checks if two icons are equal.
iconEqual ::
    (B.CallStack.HasCallStack, MonadIO m, IsIcon a, IsIcon b) =>
    a
    -- ^ /@icon1@/: pointer to the first t'GI.Gio.Interfaces.Icon.Icon'.
    -> Maybe (b)
    -- ^ /@icon2@/: pointer to the second t'GI.Gio.Interfaces.Icon.Icon'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@icon1@/ is equal to /@icon2@/. 'P.False' otherwise.
iconEqual :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIcon a, IsIcon b) =>
a -> Maybe b -> m Bool
iconEqual a
icon1 Maybe b
icon2 = 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 Icon
icon1' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon1
    Ptr Icon
maybeIcon2 <- case Maybe b
icon2 of
        Maybe b
Nothing -> Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
        Just b
jIcon2 -> do
            Ptr Icon
jIcon2' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIcon2
            Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon2'
    CInt
result <- Ptr Icon -> Ptr Icon -> IO CInt
g_icon_equal Ptr Icon
icon1' Ptr Icon
maybeIcon2
    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
icon1
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
icon2 b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IconEqualMethodInfo
instance (signature ~ (Maybe (b) -> m Bool), MonadIO m, IsIcon a, IsIcon b) => O.OverloadedMethod IconEqualMethodInfo a signature where
    overloadedMethod = iconEqual

instance O.OverloadedMethodInfo IconEqualMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Icon.iconEqual",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Icon.html#v:iconEqual"
        }


#endif

-- method Icon::serialize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_icon_serialize" g_icon_serialize :: 
    Ptr Icon ->                             -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO (Ptr GVariant)

-- | Serializes a t'GI.Gio.Interfaces.Icon.Icon' into a t'GVariant'. An equivalent t'GI.Gio.Interfaces.Icon.Icon' can be retrieved
-- back by calling 'GI.Gio.Functions.iconDeserialize' on the returned value.
-- As serialization will avoid using raw icon data when possible, it only
-- makes sense to transfer the t'GVariant' between processes on the same machine,
-- (as opposed to over the network), and within the same file system namespace.
-- 
-- /Since: 2.38/
iconSerialize ::
    (B.CallStack.HasCallStack, MonadIO m, IsIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'
    -> m GVariant
    -- ^ __Returns:__ a t'GVariant', or 'P.Nothing' when serialization fails. The t'GVariant' will not be floating.
iconSerialize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIcon a) =>
a -> m GVariant
iconSerialize a
icon = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr Icon
icon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr GVariant
result <- Ptr Icon -> IO (Ptr GVariant)
g_icon_serialize Ptr Icon
icon'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSerialize" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data IconSerializeMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsIcon a) => O.OverloadedMethod IconSerializeMethodInfo a signature where
    overloadedMethod = iconSerialize

instance O.OverloadedMethodInfo IconSerializeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Icon.iconSerialize",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Icon.html#v:iconSerialize"
        }


#endif

-- method Icon::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon." , 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 "g_icon_to_string" g_icon_to_string :: 
    Ptr Icon ->                             -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO CString

-- | Generates a textual representation of /@icon@/ that can be used for
-- serialization such as when passing /@icon@/ to a different process or
-- saving it to persistent storage. Use 'GI.Gio.Functions.iconNewForString' to
-- get /@icon@/ back from the returned string.
-- 
-- The encoding of the returned string is proprietary to t'GI.Gio.Interfaces.Icon.Icon' except
-- in the following two cases
-- 
-- * If /@icon@/ is a t'GI.Gio.Objects.FileIcon.FileIcon', the returned string is a native path
-- (such as @\/path\/to\/my icon.png@) without escaping
-- if the t'GI.Gio.Interfaces.File.File' for /@icon@/ is a native file.  If the file is not
-- native, the returned string is the result of 'GI.Gio.Interfaces.File.fileGetUri'
-- (such as @sftp:\/\/path\/to\/my%20icon.png@).
-- * If /@icon@/ is a t'GI.Gio.Objects.ThemedIcon.ThemedIcon' with exactly one name and no fallbacks,
-- the encoding is simply the name (such as @network-server@).
-- 
-- 
-- /Since: 2.20/
iconToString ::
    (B.CallStack.HasCallStack, MonadIO m, IsIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ An allocated NUL-terminated UTF8 string or
    -- 'P.Nothing' if /@icon@/ can\'t be serialized. Use 'GI.GLib.Functions.free' to free.
iconToString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIcon a) =>
a -> m (Maybe Text)
iconToString a
icon = 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 Icon
icon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    CString
result <- Ptr Icon -> IO CString
g_icon_to_string Ptr Icon
icon'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
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
icon
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo IconToStringMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Icon.iconToString",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Icon.html#v:iconToString"
        }


#endif

-- method Icon::deserialize
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariant created with g_icon_serialize()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Icon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_icon_deserialize" g_icon_deserialize :: 
    Ptr GVariant ->                         -- value : TVariant
    IO (Ptr Icon)

-- | Deserializes a t'GI.Gio.Interfaces.Icon.Icon' previously serialized using 'GI.Gio.Interfaces.Icon.iconSerialize'.
-- 
-- /Since: 2.38/
iconDeserialize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GVariant
    -- ^ /@value@/: a t'GVariant' created with 'GI.Gio.Interfaces.Icon.iconSerialize'
    -> m Icon
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Icon.Icon', or 'P.Nothing' when deserialization fails.
iconDeserialize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GVariant -> m Icon
iconDeserialize GVariant
value = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
    Ptr Icon
result <- Ptr GVariant -> IO (Ptr Icon)
g_icon_deserialize Ptr GVariant
value'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconDeserialize" Ptr Icon
result
    Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Icon) Ptr Icon
result
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Icon::hash
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "icon"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#gconstpointer to an icon object."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_icon_hash" g_icon_hash :: 
    Ptr () ->                               -- icon : TBasicType TPtr
    IO Word32

-- | Gets a hash for an icon.
iconHash ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Ptr ()
    -- ^ /@icon@/: @/gconstpointer/@ to an icon object.
    -> m Word32
    -- ^ __Returns:__ a @/guint/@ containing a hash for the /@icon@/, suitable for
    -- use in a t'GI.GLib.Structs.HashTable.HashTable' or similar data structure.
iconHash :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Ptr () -> m Word32
iconHash Ptr ()
icon = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Word32
result <- Ptr () -> IO Word32
g_icon_hash Ptr ()
icon
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method Icon::new_for_string
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "str"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A string obtained via g_icon_to_string()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Icon" })
-- throws : True
-- Skip return : False

foreign import ccall "g_icon_new_for_string" g_icon_new_for_string :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Icon)

-- | Generate a t'GI.Gio.Interfaces.Icon.Icon' instance from /@str@/. This function can fail if
-- /@str@/ is not valid - see 'GI.Gio.Interfaces.Icon.iconToString' for discussion.
-- 
-- If your application or library provides one or more t'GI.Gio.Interfaces.Icon.Icon'
-- implementations you need to ensure that each t'GType' is registered
-- with the type system prior to calling 'GI.Gio.Functions.iconNewForString'.
-- 
-- /Since: 2.20/
iconNewForString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@str@/: A string obtained via 'GI.Gio.Interfaces.Icon.iconToString'.
    -> m Icon
    -- ^ __Returns:__ An object implementing the t'GI.Gio.Interfaces.Icon.Icon'
    --          interface or 'P.Nothing' if /@error@/ is set. /(Can throw 'Data.GI.Base.GError.GError')/
iconNewForString :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Icon
iconNewForString Text
str = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    CString
str' <- Text -> IO CString
textToCString Text
str
    IO Icon -> IO () -> IO Icon
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Icon
result <- (Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon))
-> (Ptr (Ptr GError) -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Icon)
g_icon_new_for_string CString
str'
        Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconNewForString" Ptr Icon
result
        Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Icon) Ptr Icon
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
        Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
     )

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif