{-# 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.Atk.Interfaces.Image.Image' should be implemented by t'GI.Atk.Objects.Object.Object' subtypes on behalf of
-- components which display image\/pixmap information onscreen, and
-- which provide information (other than just widget borders, etc.)
-- via that image content.  For instance, icons, buttons with icons,
-- toolbar elements, and image viewing panes typically should
-- implement t'GI.Atk.Interfaces.Image.Image'.
-- 
-- t'GI.Atk.Interfaces.Image.Image' primarily provides two types of information: coordinate
-- information (useful for screen review mode of screenreaders, and
-- for use by onscreen magnifiers), and descriptive information.  The
-- descriptive information is provided for alternative, text-only
-- presentation of the most significant information present in the
-- image.

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

module GI.Atk.Interfaces.Image
    ( 

-- * Exported types
    Image(..)                               ,
    IsImage                                 ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveImageMethod                      ,
#endif


-- ** getImageDescription #method:getImageDescription#

#if defined(ENABLE_OVERLOADING)
    ImageGetImageDescriptionMethodInfo      ,
#endif
    imageGetImageDescription                ,


-- ** getImageLocale #method:getImageLocale#

#if defined(ENABLE_OVERLOADING)
    ImageGetImageLocaleMethodInfo           ,
#endif
    imageGetImageLocale                     ,


-- ** getImagePosition #method:getImagePosition#

#if defined(ENABLE_OVERLOADING)
    ImageGetImagePositionMethodInfo         ,
#endif
    imageGetImagePosition                   ,


-- ** getImageSize #method:getImageSize#

#if defined(ENABLE_OVERLOADING)
    ImageGetImageSizeMethodInfo             ,
#endif
    imageGetImageSize                       ,


-- ** setImageDescription #method:setImageDescription#

#if defined(ENABLE_OVERLOADING)
    ImageSetImageDescriptionMethodInfo      ,
#endif
    imageSetImageDescription                ,




    ) 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.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 {-# SOURCE #-} qualified GI.Atk.Enums as Atk.Enums

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

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

-- | Type class for types which implement `Image`.
class (ManagedPtrNewtype o, O.IsDescendantOf Image o) => IsImage o
instance (ManagedPtrNewtype o, O.IsDescendantOf Image o) => IsImage o
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr Image where
    boxedPtrCopy :: Image -> IO Image
boxedPtrCopy = Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Image -> IO ()
boxedPtrFree = \Image
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


#if defined(ENABLE_OVERLOADING)
type family ResolveImageMethod (t :: Symbol) (o :: *) :: * where
    ResolveImageMethod "getImageDescription" o = ImageGetImageDescriptionMethodInfo
    ResolveImageMethod "getImageLocale" o = ImageGetImageLocaleMethodInfo
    ResolveImageMethod "getImagePosition" o = ImageGetImagePositionMethodInfo
    ResolveImageMethod "getImageSize" o = ImageGetImageSizeMethodInfo
    ResolveImageMethod "setImageDescription" o = ImageSetImageDescriptionMethodInfo
    ResolveImageMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveImageMethod t Image, O.MethodInfo info Image p) => OL.IsLabel t (Image -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method Image::get_image_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Atk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkImageIface"
--                 , 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 "atk_image_get_image_description" atk_image_get_image_description :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Atk", name = "Image"})
    IO CString

-- | Get a textual description of this image.
imageGetImageDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkImageIface
    -> m T.Text
    -- ^ __Returns:__ a string representing the image description
imageGetImageDescription :: a -> m Text
imageGetImageDescription a
image = IO Text -> m Text
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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
result <- Ptr Image -> IO CString
atk_image_get_image_description Ptr Image
image'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"imageGetImageDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ImageGetImageDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsImage a) => O.MethodInfo ImageGetImageDescriptionMethodInfo a signature where
    overloadedMethod = imageGetImageDescription

#endif

-- method Image::get_image_locale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Atk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #AtkImage" , 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 "atk_image_get_image_locale" atk_image_get_image_locale :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Atk", name = "Image"})
    IO CString

-- | Retrieves the locale identifier associated to the t'GI.Atk.Interfaces.Image.Image'.
-- 
-- /Since: 1.12/
imageGetImageLocale ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: An t'GI.Atk.Interfaces.Image.Image'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a string corresponding to the POSIX
    --   @LC_MESSAGES@ locale used by the image description, or
    --   'P.Nothing' if the image does not specify a locale.
imageGetImageLocale :: a -> m (Maybe Text)
imageGetImageLocale a
image = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
result <- Ptr Image -> IO CString
atk_image_get_image_locale Ptr Image
image'
    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'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ImageGetImageLocaleMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsImage a) => O.MethodInfo ImageGetImageLocaleMethodInfo a signature where
    overloadedMethod = imageGetImageLocale

#endif

-- method Image::get_image_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Atk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkImageIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "address of #gint to put x coordinate position; otherwise, -1 if value cannot be obtained."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "address of #gint to put y coordinate position; otherwise, -1 if value cannot be obtained."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "coord_type"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "CoordType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies whether the coordinates are relative to the screen\nor to the components top level window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_image_get_image_position" atk_image_get_image_position :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Atk", name = "Image"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    CUInt ->                                -- coord_type : TInterface (Name {namespace = "Atk", name = "CoordType"})
    IO ()

-- | Gets the position of the image in the form of a point specifying the
-- images top-left corner.
-- 
-- If the position can not be obtained (e.g. missing support), x and y are set
-- to -1.
imageGetImagePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkImageIface
    -> Atk.Enums.CoordType
    -- ^ /@coordType@/: specifies whether the coordinates are relative to the screen
    -- or to the components top level window
    -> m ((Int32, Int32))
imageGetImagePosition :: a -> CoordType -> m (Int32, Int32)
imageGetImagePosition a
image CoordType
coordType = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    let coordType' :: CUInt
coordType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (CoordType -> Int) -> CoordType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoordType -> Int
forall a. Enum a => a -> Int
fromEnum) CoordType
coordType
    Ptr Image -> Ptr Int32 -> Ptr Int32 -> CUInt -> IO ()
atk_image_get_image_position Ptr Image
image' Ptr Int32
x Ptr Int32
y CUInt
coordType'
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y')

#if defined(ENABLE_OVERLOADING)
data ImageGetImagePositionMethodInfo
instance (signature ~ (Atk.Enums.CoordType -> m ((Int32, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetImagePositionMethodInfo a signature where
    overloadedMethod = imageGetImagePosition

#endif

-- method Image::get_image_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Atk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkImageIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "filled with the image width, or -1 if the value cannot be obtained."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "filled with the image height, or -1 if the value cannot be obtained."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_image_get_image_size" atk_image_get_image_size :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Atk", name = "Image"})
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO ()

-- | Get the width and height in pixels for the specified image.
-- The values of /@width@/ and /@height@/ are returned as -1 if the
-- values cannot be obtained (for instance, if the object is not onscreen).
-- 
-- If the size can not be obtained (e.g. missing support), x and y are set
-- to -1.
imageGetImageSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkImageIface
    -> m ((Int32, Int32))
imageGetImageSize :: a -> m (Int32, Int32)
imageGetImageSize a
image = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Image -> Ptr Int32 -> Ptr Int32 -> IO ()
atk_image_get_image_size Ptr Image
image' Ptr Int32
width Ptr Int32
height
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data ImageGetImageSizeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetImageSizeMethodInfo a signature where
    overloadedMethod = imageGetImageSize

#endif

-- method Image::set_image_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Atk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GObject instance that implements AtkImageIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string description to set for @image"
--                 , 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 "atk_image_set_image_description" atk_image_set_image_description :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Atk", name = "Image"})
    CString ->                              -- description : TBasicType TUTF8
    IO CInt

-- | Sets the textual description for this image.
imageSetImageDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.GObject.Objects.Object.Object' instance that implements AtkImageIface
    -> T.Text
    -- ^ /@description@/: a string description to set for /@image@/
    -> m Bool
    -- ^ __Returns:__ boolean TRUE, or FALSE if operation could
    -- not be completed.
imageSetImageDescription :: a -> Text -> m Bool
imageSetImageDescription a
image Text
description = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
description' <- Text -> IO CString
textToCString Text
description
    CInt
result <- Ptr Image -> CString -> IO CInt
atk_image_set_image_description Ptr Image
image' CString
description'
    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
image
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ImageSetImageDescriptionMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsImage a) => O.MethodInfo ImageSetImageDescriptionMethodInfo a signature where
    overloadedMethod = imageSetImageDescription

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Image = ImageSignalList
type ImageSignalList = ('[ ] :: [(Symbol, *)])

#endif