{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.SymbolicPaintable
(
SymbolicPaintable(..) ,
IsSymbolicPaintable ,
toSymbolicPaintable ,
#if defined(ENABLE_OVERLOADING)
ResolveSymbolicPaintableMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SymbolicPaintableSnapshotSymbolicMethodInfo,
#endif
symbolicPaintableSnapshotSymbolic ,
) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
#endif
newtype SymbolicPaintable = SymbolicPaintable (SP.ManagedPtr SymbolicPaintable)
deriving (SymbolicPaintable -> SymbolicPaintable -> Bool
(SymbolicPaintable -> SymbolicPaintable -> Bool)
-> (SymbolicPaintable -> SymbolicPaintable -> Bool)
-> Eq SymbolicPaintable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymbolicPaintable -> SymbolicPaintable -> Bool
== :: SymbolicPaintable -> SymbolicPaintable -> Bool
$c/= :: SymbolicPaintable -> SymbolicPaintable -> Bool
/= :: SymbolicPaintable -> SymbolicPaintable -> Bool
Eq)
instance SP.ManagedPtrNewtype SymbolicPaintable where
toManagedPtr :: SymbolicPaintable -> ManagedPtr SymbolicPaintable
toManagedPtr (SymbolicPaintable ManagedPtr SymbolicPaintable
p) = ManagedPtr SymbolicPaintable
p
foreign import ccall "gtk_symbolic_paintable_get_type"
c_gtk_symbolic_paintable_get_type :: IO B.Types.GType
instance B.Types.TypedObject SymbolicPaintable where
glibType :: IO GType
glibType = IO GType
c_gtk_symbolic_paintable_get_type
instance B.Types.GObject SymbolicPaintable
class (SP.GObject o, O.IsDescendantOf SymbolicPaintable o) => IsSymbolicPaintable o
instance (SP.GObject o, O.IsDescendantOf SymbolicPaintable o) => IsSymbolicPaintable o
instance O.HasParentTypes SymbolicPaintable
type instance O.ParentTypes SymbolicPaintable = '[Gdk.Paintable.Paintable, GObject.Object.Object]
toSymbolicPaintable :: (MIO.MonadIO m, IsSymbolicPaintable o) => o -> m SymbolicPaintable
toSymbolicPaintable :: forall (m :: * -> *) o.
(MonadIO m, IsSymbolicPaintable o) =>
o -> m SymbolicPaintable
toSymbolicPaintable = IO SymbolicPaintable -> m SymbolicPaintable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SymbolicPaintable -> m SymbolicPaintable)
-> (o -> IO SymbolicPaintable) -> o -> m SymbolicPaintable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SymbolicPaintable -> SymbolicPaintable)
-> o -> IO SymbolicPaintable
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SymbolicPaintable -> SymbolicPaintable
SymbolicPaintable
instance B.GValue.IsGValue (Maybe SymbolicPaintable) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_symbolic_paintable_get_type
gvalueSet_ :: Ptr GValue -> Maybe SymbolicPaintable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SymbolicPaintable
P.Nothing = Ptr GValue -> Ptr SymbolicPaintable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SymbolicPaintable
forall a. Ptr a
FP.nullPtr :: FP.Ptr SymbolicPaintable)
gvalueSet_ Ptr GValue
gv (P.Just SymbolicPaintable
obj) = SymbolicPaintable -> (Ptr SymbolicPaintable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SymbolicPaintable
obj (Ptr GValue -> Ptr SymbolicPaintable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SymbolicPaintable)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr SymbolicPaintable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SymbolicPaintable)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject SymbolicPaintable ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SymbolicPaintable
type instance O.AttributeList SymbolicPaintable = SymbolicPaintableAttributeList
type SymbolicPaintableAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSymbolicPaintableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSymbolicPaintableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSymbolicPaintableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSymbolicPaintableMethod "computeConcreteSize" o = Gdk.Paintable.PaintableComputeConcreteSizeMethodInfo
ResolveSymbolicPaintableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSymbolicPaintableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSymbolicPaintableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSymbolicPaintableMethod "invalidateContents" o = Gdk.Paintable.PaintableInvalidateContentsMethodInfo
ResolveSymbolicPaintableMethod "invalidateSize" o = Gdk.Paintable.PaintableInvalidateSizeMethodInfo
ResolveSymbolicPaintableMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSymbolicPaintableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSymbolicPaintableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSymbolicPaintableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSymbolicPaintableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSymbolicPaintableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSymbolicPaintableMethod "snapshot" o = Gdk.Paintable.PaintableSnapshotMethodInfo
ResolveSymbolicPaintableMethod "snapshotSymbolic" o = SymbolicPaintableSnapshotSymbolicMethodInfo
ResolveSymbolicPaintableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSymbolicPaintableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSymbolicPaintableMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSymbolicPaintableMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSymbolicPaintableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSymbolicPaintableMethod "getCurrentImage" o = Gdk.Paintable.PaintableGetCurrentImageMethodInfo
ResolveSymbolicPaintableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSymbolicPaintableMethod "getFlags" o = Gdk.Paintable.PaintableGetFlagsMethodInfo
ResolveSymbolicPaintableMethod "getIntrinsicAspectRatio" o = Gdk.Paintable.PaintableGetIntrinsicAspectRatioMethodInfo
ResolveSymbolicPaintableMethod "getIntrinsicHeight" o = Gdk.Paintable.PaintableGetIntrinsicHeightMethodInfo
ResolveSymbolicPaintableMethod "getIntrinsicWidth" o = Gdk.Paintable.PaintableGetIntrinsicWidthMethodInfo
ResolveSymbolicPaintableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSymbolicPaintableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSymbolicPaintableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSymbolicPaintableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSymbolicPaintableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSymbolicPaintableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSymbolicPaintableMethod t SymbolicPaintable, O.OverloadedMethod info SymbolicPaintable p) => OL.IsLabel t (SymbolicPaintable -> 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 ~ ResolveSymbolicPaintableMethod t SymbolicPaintable, O.OverloadedMethod info SymbolicPaintable p, R.HasField t SymbolicPaintable p) => R.HasField t SymbolicPaintable p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSymbolicPaintableMethod t SymbolicPaintable, O.OverloadedMethodInfo info SymbolicPaintable) => OL.IsLabel t (O.MethodProxy info SymbolicPaintable) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gtk_symbolic_paintable_snapshot_symbolic" gtk_symbolic_paintable_snapshot_symbolic ::
Ptr SymbolicPaintable ->
Ptr Gdk.Snapshot.Snapshot ->
CDouble ->
CDouble ->
Ptr Gdk.RGBA.RGBA ->
FCT.CSize ->
IO ()
symbolicPaintableSnapshotSymbolic ::
(B.CallStack.HasCallStack, MonadIO m, IsSymbolicPaintable a, Gdk.Snapshot.IsSnapshot b) =>
a
-> b
-> Double
-> Double
-> [Gdk.RGBA.RGBA]
-> m ()
symbolicPaintableSnapshotSymbolic :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSymbolicPaintable a, IsSnapshot b) =>
a -> b -> Double -> Double -> [RGBA] -> m ()
symbolicPaintableSnapshotSymbolic a
paintable b
snapshot Double
width Double
height [RGBA]
colors = 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
let nColors :: CSize
nColors = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ [RGBA] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [RGBA]
colors
paintable' <- a -> IO (Ptr SymbolicPaintable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
paintable
snapshot' <- unsafeManagedPtrCastPtr snapshot
let width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
colors' <- mapM unsafeManagedPtrGetPtr colors
colors'' <- packBlockArray 16 colors'
gtk_symbolic_paintable_snapshot_symbolic paintable' snapshot' width' height' colors'' nColors
touchManagedPtr paintable
touchManagedPtr snapshot
mapM_ touchManagedPtr colors
freeMem colors''
return ()
#if defined(ENABLE_OVERLOADING)
data SymbolicPaintableSnapshotSymbolicMethodInfo
instance (signature ~ (b -> Double -> Double -> [Gdk.RGBA.RGBA] -> m ()), MonadIO m, IsSymbolicPaintable a, Gdk.Snapshot.IsSnapshot b) => O.OverloadedMethod SymbolicPaintableSnapshotSymbolicMethodInfo a signature where
overloadedMethod = symbolicPaintableSnapshotSymbolic
instance O.OverloadedMethodInfo SymbolicPaintableSnapshotSymbolicMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SymbolicPaintable.symbolicPaintableSnapshotSymbolic",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SymbolicPaintable.html#v:symbolicPaintableSnapshotSymbolic"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SymbolicPaintable = SymbolicPaintableSignalList
type SymbolicPaintableSignalList = ('[ '("invalidateContents", Gdk.Paintable.PaintableInvalidateContentsSignalInfo), '("invalidateSize", Gdk.Paintable.PaintableInvalidateSizeSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif