{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Interfaces.Image
(
Image(..) ,
noImage ,
IsImage ,
#if defined(ENABLE_OVERLOADING)
ResolveImageMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ImageGetImageDescriptionMethodInfo ,
#endif
imageGetImageDescription ,
#if defined(ENABLE_OVERLOADING)
ImageGetImageLocaleMethodInfo ,
#endif
imageGetImageLocale ,
#if defined(ENABLE_OVERLOADING)
ImageGetImagePositionMethodInfo ,
#endif
imageGetImagePosition ,
#if defined(ENABLE_OVERLOADING)
ImageGetImageSizeMethodInfo ,
#endif
imageGetImageSize ,
#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.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 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
newtype Image = Image (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)
noImage :: Maybe Image
noImage :: Maybe Image
noImage = Maybe Image
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Image = ImageSignalList
type ImageSignalList = ('[ ] :: [(Symbol, *)])
#endif
class (ManagedPtrNewtype o, O.IsDescendantOf Image o) => IsImage o
instance (ManagedPtrNewtype o, O.IsDescendantOf Image o) => IsImage o
instance WrappedPtr Image where
wrappedPtrCalloc :: IO (Ptr Image)
wrappedPtrCalloc = Ptr Image -> IO (Ptr Image)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Image
forall a. Ptr a
nullPtr
wrappedPtrCopy :: Image -> IO Image
wrappedPtrCopy = Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return
wrappedPtrFree :: Maybe (GDestroyNotify Image)
wrappedPtrFree = Maybe (GDestroyNotify Image)
forall a. Maybe a
Nothing
#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
foreign import ccall "atk_image_get_image_description" atk_image_get_image_description ::
Ptr Image ->
IO CString
imageGetImageDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
a
-> m T.Text
imageGetImageDescription :: a -> m Text
imageGetImageDescription image :: 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 "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
foreign import ccall "atk_image_get_image_locale" atk_image_get_image_locale ::
Ptr Image ->
IO CString
imageGetImageLocale ::
(B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
a
-> m (Maybe T.Text)
imageGetImageLocale :: a -> m (Maybe Text)
imageGetImageLocale image :: 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
$ \result' :: 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
foreign import ccall "atk_image_get_image_position" atk_image_get_image_position ::
Ptr Image ->
Ptr Int32 ->
Ptr Int32 ->
CUInt ->
IO ()
imageGetImagePosition ::
(B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
a
-> Atk.Enums.CoordType
-> m ((Int32, Int32))
imageGetImagePosition :: a -> CoordType -> m (Int32, Int32)
imageGetImagePosition image :: a
image coordType :: 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
foreign import ccall "atk_image_get_image_size" atk_image_get_image_size ::
Ptr Image ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
imageGetImageSize ::
(B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
a
-> m ((Int32, Int32))
imageGetImageSize :: a -> m (Int32, Int32)
imageGetImageSize image :: 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
foreign import ccall "atk_image_set_image_description" atk_image_set_image_description ::
Ptr Image ->
CString ->
IO CInt
imageSetImageDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
a
-> T.Text
-> m Bool
imageSetImageDescription :: a -> Text -> m Bool
imageSetImageDescription image :: a
image description :: 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
/= 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