{-# LINE 1 "Data/GI/Base/Properties.hsc" #-}
{-# LANGUAGE ScopedTypeVariables, TypeApplications #-}
module Data.GI.Base.Properties
( setObjectPropertyIsGValueInstance
, setObjectPropertyString
, setObjectPropertyStringArray
, setObjectPropertyPtr
, setObjectPropertyInt
, setObjectPropertyUInt
, setObjectPropertyLong
, setObjectPropertyULong
, setObjectPropertyInt32
, setObjectPropertyUInt32
, setObjectPropertyInt64
, setObjectPropertyUInt64
, setObjectPropertyFloat
, setObjectPropertyDouble
, setObjectPropertyBool
, setObjectPropertyGType
, setObjectPropertyObject
, setObjectPropertyBoxed
, setObjectPropertyEnum
, setObjectPropertyFlags
, setObjectPropertyClosure
, setObjectPropertyVariant
, setObjectPropertyByteArray
, setObjectPropertyPtrGList
, setObjectPropertyHash
, setObjectPropertyCallback
, setObjectPropertyGError
, setObjectPropertyGValue
, setObjectPropertyParamSpec
, getObjectPropertyIsGValueInstance
, getObjectPropertyString
, getObjectPropertyStringArray
, getObjectPropertyPtr
, getObjectPropertyInt
, getObjectPropertyUInt
, getObjectPropertyLong
, getObjectPropertyULong
, getObjectPropertyInt32
, getObjectPropertyUInt32
, getObjectPropertyInt64
, getObjectPropertyUInt64
, getObjectPropertyFloat
, getObjectPropertyDouble
, getObjectPropertyBool
, getObjectPropertyGType
, getObjectPropertyObject
, getObjectPropertyBoxed
, getObjectPropertyEnum
, getObjectPropertyFlags
, getObjectPropertyClosure
, getObjectPropertyVariant
, getObjectPropertyByteArray
, getObjectPropertyPtrGList
, getObjectPropertyHash
, getObjectPropertyCallback
, getObjectPropertyGError
, getObjectPropertyGValue
, getObjectPropertyParamSpec
, constructObjectPropertyIsGValueInstance
, constructObjectPropertyString
, constructObjectPropertyStringArray
, constructObjectPropertyPtr
, constructObjectPropertyInt
, constructObjectPropertyUInt
, constructObjectPropertyLong
, constructObjectPropertyULong
, constructObjectPropertyInt32
, constructObjectPropertyUInt32
, constructObjectPropertyInt64
, constructObjectPropertyUInt64
, constructObjectPropertyFloat
, constructObjectPropertyDouble
, constructObjectPropertyBool
, constructObjectPropertyGType
, constructObjectPropertyObject
, constructObjectPropertyBoxed
, constructObjectPropertyEnum
, constructObjectPropertyFlags
, constructObjectPropertyClosure
, constructObjectPropertyVariant
, constructObjectPropertyByteArray
, constructObjectPropertyPtrGList
, constructObjectPropertyHash
, constructObjectPropertyCallback
, constructObjectPropertyGError
, constructObjectPropertyGValue
, constructObjectPropertyParamSpec
) where
{-# LINE 98 "Data/GI/Base/Properties.hsc" #-}
import Control.Monad ((>=>))
import qualified Data.ByteString.Char8 as B
import Data.Text (Text)
import Data.GI.Base.BasicTypes
import Data.GI.Base.BasicConversions
import Data.GI.Base.ManagedPtr
import Data.GI.Base.GError (GError(..))
import Data.GI.Base.GValue
import Data.GI.Base.GType
import Data.GI.Base.GClosure (GClosure(..))
import Data.GI.Base.GVariant (newGVariantFromPtr)
import Data.GI.Base.Utils (freeMem, convertIfNonNull)
import Foreign (Ptr, FunPtr, Int32, Word32, Int64, Word64, nullPtr,
castFunPtrToPtr, castPtrToFunPtr)
import Foreign.C (CString, withCString)
import Foreign.C.Types (CInt, CUInt, CLong, CULong)
foreign import ccall "g_object_set_property" g_object_set_property ::
Ptr a -> CString -> Ptr GValue -> IO ()
gobjectSetProperty :: GObject a => a -> String -> GValue -> IO ()
gobjectSetProperty :: forall a. GObject a => a -> String -> GValue -> IO ()
gobjectSetProperty a
obj String
propName GValue
gvalue =
a -> (Ptr a -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr a
obj ((Ptr a -> IO ()) -> IO ()) -> (Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr a
objPtr ->
String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
propName ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPropName ->
GValue -> (Ptr GValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GValue
gvalue ((Ptr GValue -> IO ()) -> IO ()) -> (Ptr GValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GValue
gvalueptr ->
Ptr a -> CString -> Ptr GValue -> IO ()
forall a. Ptr a -> CString -> Ptr GValue -> IO ()
g_object_set_property Ptr a
objPtr CString
cPropName Ptr GValue
gvalueptr
setObjectProperty :: GObject a => a -> String -> b ->
(Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty :: forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName b
propValue Ptr GValue -> b -> IO ()
setter (GType CGType
gtype) = do
GValue
gvalue <- GType -> (Ptr GValue -> b -> IO ()) -> b -> IO GValue
forall a. GType -> (Ptr GValue -> a -> IO ()) -> a -> IO GValue
buildGValue (CGType -> GType
GType CGType
gtype) Ptr GValue -> b -> IO ()
setter b
propValue
a -> String -> GValue -> IO ()
forall a. GObject a => a -> String -> GValue -> IO ()
gobjectSetProperty a
obj String
propName GValue
gvalue
foreign import ccall "g_object_get_property" g_object_get_property ::
Ptr a -> CString -> Ptr GValue -> IO ()
gobjectGetProperty :: GObject a => a -> String -> GType -> IO GValue
gobjectGetProperty :: forall a. GObject a => a -> String -> GType -> IO GValue
gobjectGetProperty a
obj String
propName GType
gtype = do
GValue
gvalue <- GType -> IO GValue
newGValue GType
gtype
a -> (Ptr a -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr a
obj ((Ptr a -> IO ()) -> IO ()) -> (Ptr a -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr a
objPtr ->
String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withCString String
propName ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
cPropName ->
GValue -> (Ptr GValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GValue
gvalue ((Ptr GValue -> IO ()) -> IO ()) -> (Ptr GValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GValue
gvalueptr ->
Ptr a -> CString -> Ptr GValue -> IO ()
forall a. Ptr a -> CString -> Ptr GValue -> IO ()
g_object_get_property Ptr a
objPtr CString
cPropName Ptr GValue
gvalueptr
GValue -> IO GValue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
gvalue
getObjectProperty :: GObject a => a -> String ->
(Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty :: forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName Ptr GValue -> IO b
getter GType
gtype = do
GValue
gv <- a -> String -> GType -> IO GValue
forall a. GObject a => a -> String -> GType -> IO GValue
gobjectGetProperty a
obj String
propName GType
gtype
GValue -> (Ptr GValue -> IO b) -> IO b
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GValue
gv Ptr GValue -> IO b
getter
constructObjectProperty :: String -> b -> (Ptr GValue -> b -> IO ()) ->
GType -> IO (GValueConstruct o)
constructObjectProperty :: forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName b
propValue Ptr GValue -> b -> IO ()
setter GType
gtype = do
GValue
gvalue <- GType -> (Ptr GValue -> b -> IO ()) -> b -> IO GValue
forall a. GType -> (Ptr GValue -> a -> IO ()) -> a -> IO GValue
buildGValue GType
gtype Ptr GValue -> b -> IO ()
setter b
propValue
GValueConstruct o -> IO (GValueConstruct o)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> GValue -> GValueConstruct o
forall o. String -> GValue -> GValueConstruct o
GValueConstruct String
propName GValue
gvalue)
setObjectPropertyIsGValueInstance :: (GObject a, IsGValue b) =>
a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance :: forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance a
obj String
propName b
maybeVal = do
GValue
gvalue <- b -> IO GValue
forall a (m :: * -> *). (IsGValue a, MonadIO m) => a -> m GValue
toGValue b
maybeVal
a -> String -> GValue -> IO ()
forall a. GObject a => a -> String -> GValue -> IO ()
gobjectSetProperty a
obj String
propName GValue
gvalue
constructObjectPropertyIsGValueInstance :: IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance :: forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance String
propName b
maybeVal = do
GValue
gvalue <- b -> IO GValue
forall a (m :: * -> *). (IsGValue a, MonadIO m) => a -> m GValue
toGValue b
maybeVal
GValueConstruct o -> IO (GValueConstruct o)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> GValue -> GValueConstruct o
forall o. String -> GValue -> GValueConstruct o
GValueConstruct String
propName GValue
gvalue)
getObjectPropertyIsGValueInstance :: forall a b. (GObject a, IsGValue b) =>
a -> String -> IO b
getObjectPropertyIsGValueInstance :: forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance a
obj String
propName = do
GType
gtype <- forall a. IsGValue a => IO GType
gvalueGType_ @b
GValue
gv <- a -> String -> GType -> IO GValue
forall a. GObject a => a -> String -> GType -> IO GValue
gobjectGetProperty a
obj String
propName GType
gtype
GValue -> IO b
forall a (m :: * -> *). (IsGValue a, MonadIO m) => GValue -> m a
fromGValue GValue
gv
setObjectPropertyString :: GObject a =>
a -> String -> Maybe Text -> IO ()
setObjectPropertyString :: forall a. GObject a => a -> String -> Maybe Text -> IO ()
setObjectPropertyString = a -> String -> Maybe Text -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyString :: String -> Maybe Text ->
IO (GValueConstruct o)
constructObjectPropertyString :: forall o. String -> Maybe Text -> IO (GValueConstruct o)
constructObjectPropertyString = String -> Maybe Text -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyString :: GObject a =>
a -> String -> IO (Maybe Text)
getObjectPropertyString :: forall a. GObject a => a -> String -> IO (Maybe Text)
getObjectPropertyString = a -> String -> IO (Maybe Text)
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyPtr :: GObject a =>
a -> String -> Ptr b -> IO ()
setObjectPropertyPtr :: forall a b. GObject a => a -> String -> Ptr b -> IO ()
setObjectPropertyPtr = a -> String -> Ptr b -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyPtr :: String -> Ptr b ->
IO (GValueConstruct o)
constructObjectPropertyPtr :: forall b o. String -> Ptr b -> IO (GValueConstruct o)
constructObjectPropertyPtr = String -> Ptr b -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyPtr :: GObject a =>
a -> String -> IO (Ptr b)
getObjectPropertyPtr :: forall a b. GObject a => a -> String -> IO (Ptr b)
getObjectPropertyPtr = a -> String -> IO (Ptr b)
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyInt :: GObject a =>
a -> String -> CInt -> IO ()
setObjectPropertyInt :: forall a. GObject a => a -> String -> CInt -> IO ()
setObjectPropertyInt = a -> String -> CInt -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyInt :: String -> CInt ->
IO (GValueConstruct o)
constructObjectPropertyInt :: forall o. String -> CInt -> IO (GValueConstruct o)
constructObjectPropertyInt = String -> CInt -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyInt :: GObject a => a -> String -> IO CInt
getObjectPropertyInt :: forall a. GObject a => a -> String -> IO CInt
getObjectPropertyInt = a -> String -> IO CInt
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyUInt :: GObject a =>
a -> String -> CUInt -> IO ()
setObjectPropertyUInt :: forall a. GObject a => a -> String -> CUInt -> IO ()
setObjectPropertyUInt = a -> String -> CUInt -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyUInt :: String -> CUInt ->
IO (GValueConstruct o)
constructObjectPropertyUInt :: forall o. String -> CUInt -> IO (GValueConstruct o)
constructObjectPropertyUInt = String -> CUInt -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyUInt :: GObject a => a -> String -> IO CUInt
getObjectPropertyUInt :: forall a. GObject a => a -> String -> IO CUInt
getObjectPropertyUInt = a -> String -> IO CUInt
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyLong :: GObject a =>
a -> String -> CLong -> IO ()
setObjectPropertyLong :: forall a. GObject a => a -> String -> CLong -> IO ()
setObjectPropertyLong = a -> String -> CLong -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyLong :: String -> CLong ->
IO (GValueConstruct o)
constructObjectPropertyLong :: forall o. String -> CLong -> IO (GValueConstruct o)
constructObjectPropertyLong = String -> CLong -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyLong :: GObject a => a -> String -> IO CLong
getObjectPropertyLong :: forall a. GObject a => a -> String -> IO CLong
getObjectPropertyLong = a -> String -> IO CLong
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyULong :: GObject a =>
a -> String -> CULong -> IO ()
setObjectPropertyULong :: forall a. GObject a => a -> String -> CULong -> IO ()
setObjectPropertyULong = a -> String -> CULong -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyULong :: String -> CULong ->
IO (GValueConstruct o)
constructObjectPropertyULong :: forall o. String -> CULong -> IO (GValueConstruct o)
constructObjectPropertyULong = String -> CULong -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyULong :: GObject a => a -> String -> IO CULong
getObjectPropertyULong :: forall a. GObject a => a -> String -> IO CULong
getObjectPropertyULong = a -> String -> IO CULong
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyInt32 :: GObject a =>
a -> String -> Int32 -> IO ()
setObjectPropertyInt32 :: forall a. GObject a => a -> String -> Int32 -> IO ()
setObjectPropertyInt32 = a -> String -> Int32 -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyInt32 :: String -> Int32 ->
IO (GValueConstruct o)
constructObjectPropertyInt32 :: forall o. String -> Int32 -> IO (GValueConstruct o)
constructObjectPropertyInt32 = String -> Int32 -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyInt32 :: GObject a => a -> String -> IO Int32
getObjectPropertyInt32 :: forall a. GObject a => a -> String -> IO Int32
getObjectPropertyInt32 = a -> String -> IO Int32
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyUInt32 :: GObject a =>
a -> String -> Word32 -> IO ()
setObjectPropertyUInt32 :: forall a. GObject a => a -> String -> Word32 -> IO ()
setObjectPropertyUInt32 = a -> String -> Word32 -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyUInt32 :: String -> Word32 ->
IO (GValueConstruct o)
constructObjectPropertyUInt32 :: forall o. String -> Word32 -> IO (GValueConstruct o)
constructObjectPropertyUInt32 = String -> Word32 -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyUInt32 :: GObject a => a -> String -> IO Word32
getObjectPropertyUInt32 :: forall a. GObject a => a -> String -> IO Word32
getObjectPropertyUInt32 = a -> String -> IO Word32
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyInt64 :: GObject a =>
a -> String -> Int64 -> IO ()
setObjectPropertyInt64 :: forall a. GObject a => a -> String -> Int64 -> IO ()
setObjectPropertyInt64 = a -> String -> Int64 -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyInt64 :: String -> Int64 ->
IO (GValueConstruct o)
constructObjectPropertyInt64 :: forall o. String -> Int64 -> IO (GValueConstruct o)
constructObjectPropertyInt64 = String -> Int64 -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyInt64 :: GObject a => a -> String -> IO Int64
getObjectPropertyInt64 :: forall a. GObject a => a -> String -> IO Int64
getObjectPropertyInt64 = a -> String -> IO Int64
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyUInt64 :: GObject a =>
a -> String -> Word64 -> IO ()
setObjectPropertyUInt64 :: forall a. GObject a => a -> String -> CGType -> IO ()
setObjectPropertyUInt64 = a -> String -> CGType -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyUInt64 :: String -> Word64 ->
IO (GValueConstruct o)
constructObjectPropertyUInt64 :: forall o. String -> CGType -> IO (GValueConstruct o)
constructObjectPropertyUInt64 = String -> CGType -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyUInt64 :: GObject a => a -> String -> IO Word64
getObjectPropertyUInt64 :: forall a. GObject a => a -> String -> IO CGType
getObjectPropertyUInt64 = a -> String -> IO CGType
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyFloat :: GObject a =>
a -> String -> Float -> IO ()
setObjectPropertyFloat :: forall a. GObject a => a -> String -> Float -> IO ()
setObjectPropertyFloat = a -> String -> Float -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyFloat :: String -> Float ->
IO (GValueConstruct o)
constructObjectPropertyFloat :: forall o. String -> Float -> IO (GValueConstruct o)
constructObjectPropertyFloat = String -> Float -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyFloat :: GObject a =>
a -> String -> IO Float
getObjectPropertyFloat :: forall a. GObject a => a -> String -> IO Float
getObjectPropertyFloat = a -> String -> IO Float
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyDouble :: GObject a =>
a -> String -> Double -> IO ()
setObjectPropertyDouble :: forall a. GObject a => a -> String -> Double -> IO ()
setObjectPropertyDouble = a -> String -> Double -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyDouble :: String -> Double ->
IO (GValueConstruct o)
constructObjectPropertyDouble :: forall o. String -> Double -> IO (GValueConstruct o)
constructObjectPropertyDouble = String -> Double -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyDouble :: GObject a =>
a -> String -> IO Double
getObjectPropertyDouble :: forall a. GObject a => a -> String -> IO Double
getObjectPropertyDouble = a -> String -> IO Double
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyBool :: GObject a =>
a -> String -> Bool -> IO ()
setObjectPropertyBool :: forall a. GObject a => a -> String -> Bool -> IO ()
setObjectPropertyBool = a -> String -> Bool -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyBool :: String -> Bool -> IO (GValueConstruct o)
constructObjectPropertyBool :: forall o. String -> Bool -> IO (GValueConstruct o)
constructObjectPropertyBool = String -> Bool -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyBool :: GObject a => a -> String -> IO Bool
getObjectPropertyBool :: forall a. GObject a => a -> String -> IO Bool
getObjectPropertyBool = a -> String -> IO Bool
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyGType :: GObject a =>
a -> String -> GType -> IO ()
setObjectPropertyGType :: forall a. GObject a => a -> String -> GType -> IO ()
setObjectPropertyGType = a -> String -> GType -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance
constructObjectPropertyGType :: String -> GType -> IO (GValueConstruct o)
constructObjectPropertyGType :: forall o. String -> GType -> IO (GValueConstruct o)
constructObjectPropertyGType = String -> GType -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyGType :: GObject a => a -> String -> IO GType
getObjectPropertyGType :: forall a. GObject a => a -> String -> IO GType
getObjectPropertyGType = a -> String -> IO GType
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyObject :: forall a b. (GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyObject :: forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyObject a
obj String
propName Maybe b
maybeObject = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
Maybe b -> (Ptr b -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe b
maybeObject ((Ptr b -> IO ()) -> IO ()) -> (Ptr b -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr b
objectPtr ->
a
-> String
-> Ptr b
-> (Ptr GValue -> Ptr b -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr b
objectPtr Ptr GValue -> Ptr b -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
set_object GType
gtype
constructObjectPropertyObject :: forall a o. GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyObject :: forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyObject String
propName Maybe a
maybeObject = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @a
Maybe a
-> (Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe a
maybeObject ((Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o))
-> (Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ \Ptr a
objectPtr ->
String
-> Ptr a
-> (Ptr GValue -> Ptr a -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr a
objectPtr Ptr GValue -> Ptr a -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
set_object GType
gtype
getObjectPropertyObject :: forall a b. (GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyObject :: forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyObject a
obj String
propName ManagedPtr b -> b
constructor = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
a
-> String -> (Ptr GValue -> IO (Maybe b)) -> GType -> IO (Maybe b)
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName
(\Ptr GValue
val -> (Ptr GValue -> IO (Ptr b)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
get_object Ptr GValue
val :: IO (Ptr b))
IO (Ptr b) -> (Ptr b -> IO (Maybe b)) -> IO (Maybe b)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Ptr b -> (Ptr b -> IO b) -> IO (Maybe b))
-> (Ptr b -> IO b) -> Ptr b -> IO (Maybe b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr b -> (Ptr b -> IO b) -> IO (Maybe b)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull ((ManagedPtr b -> b) -> Ptr b -> IO b
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr b -> b
constructor))
GType
gtype
setObjectPropertyBoxed :: forall a b. (GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyBoxed :: forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyBoxed a
obj String
propName Maybe b
maybeBoxed = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
Maybe b -> (Ptr b -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe b
maybeBoxed ((Ptr b -> IO ()) -> IO ()) -> (Ptr b -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr b
boxedPtr ->
a
-> String
-> Ptr b
-> (Ptr GValue -> Ptr b -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr b
boxedPtr Ptr GValue -> Ptr b -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtype
constructObjectPropertyBoxed :: forall a o. (GBoxed a) =>
String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyBoxed :: forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyBoxed String
propName Maybe a
maybeBoxed = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @a
Maybe a
-> (Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe a
maybeBoxed ((Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o))
-> (Ptr a -> IO (GValueConstruct o)) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ \Ptr a
boxedPtr ->
String
-> Ptr a
-> (Ptr GValue -> Ptr a -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr a
boxedPtr Ptr GValue -> Ptr a -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtype
getObjectPropertyBoxed :: forall a b. (GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyBoxed :: forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyBoxed a
obj String
propName ManagedPtr b -> b
constructor = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
a
-> String -> (Ptr GValue -> IO (Maybe b)) -> GType -> IO (Maybe b)
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName (Ptr GValue -> IO (Ptr b)
forall b. Ptr GValue -> IO (Ptr b)
get_boxed (Ptr GValue -> IO (Ptr b))
-> (Ptr b -> IO (Maybe b)) -> Ptr GValue -> IO (Maybe b)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
(Ptr b -> (Ptr b -> IO b) -> IO (Maybe b))
-> (Ptr b -> IO b) -> Ptr b -> IO (Maybe b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr b -> (Ptr b -> IO b) -> IO (Maybe b)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull ((ManagedPtr b -> b) -> Ptr b -> IO b
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr b -> b
constructor))
GType
gtype
setObjectPropertyStringArray :: GObject a =>
a -> String -> Maybe [Text] -> IO ()
setObjectPropertyStringArray :: forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
setObjectPropertyStringArray a
obj String
propName Maybe [Text]
Nothing =
a
-> String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr Any
forall a. Ptr a
nullPtr Ptr GValue -> Ptr Any -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeStrv
setObjectPropertyStringArray a
obj String
propName (Just [Text]
strv) = do
Ptr CString
cStrv <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
strv
a
-> String
-> Ptr CString
-> (Ptr GValue -> Ptr CString -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr CString
cStrv Ptr GValue -> Ptr CString -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeStrv
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
cStrv
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
cStrv
constructObjectPropertyStringArray :: String -> Maybe [Text] ->
IO (GValueConstruct o)
constructObjectPropertyStringArray :: forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
constructObjectPropertyStringArray String
propName Maybe [Text]
Nothing =
String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr Any
forall a. Ptr a
nullPtr Ptr GValue -> Ptr Any -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeStrv
constructObjectPropertyStringArray String
propName (Just [Text]
strv) = do
Ptr CString
cStrv <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
strv
GValueConstruct o
result <- String
-> Ptr CString
-> (Ptr GValue -> Ptr CString -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr CString
cStrv Ptr GValue -> Ptr CString -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeStrv
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
cStrv
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
cStrv
GValueConstruct o -> IO (GValueConstruct o)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValueConstruct o
result
getObjectPropertyStringArray :: GObject a => a -> String -> IO (Maybe [Text])
getObjectPropertyStringArray :: forall a. GObject a => a -> String -> IO (Maybe [Text])
getObjectPropertyStringArray a
obj String
propName =
a
-> String
-> (Ptr GValue -> IO (Maybe [Text]))
-> GType
-> IO (Maybe [Text])
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName
(Ptr GValue -> IO (Ptr CString)
forall b. Ptr GValue -> IO (Ptr b)
get_boxed (Ptr GValue -> IO (Ptr CString))
-> (Ptr CString -> IO (Maybe [Text]))
-> Ptr GValue
-> IO (Maybe [Text])
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
(Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> Ptr CString -> IO (Maybe [Text])
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray)
GType
gtypeStrv
setObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
setObjectPropertyEnum :: forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
setObjectPropertyEnum a
obj String
propName b
enum = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
let cEnum :: CUInt
cEnum = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (b -> Int) -> b -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Int
forall a. Enum a => a -> Int
fromEnum) b
enum
a
-> String
-> CUInt
-> (Ptr GValue -> CUInt -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName CUInt
cEnum Ptr GValue -> CUInt -> IO ()
set_enum GType
gtype
constructObjectPropertyEnum :: forall a o. (Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
constructObjectPropertyEnum :: forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
constructObjectPropertyEnum String
propName a
enum = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @a
let cEnum :: CUInt
cEnum = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (a -> Int) -> a -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Enum a => a -> Int
fromEnum) a
enum
String
-> CUInt
-> (Ptr GValue -> CUInt -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName CUInt
cEnum Ptr GValue -> CUInt -> IO ()
set_enum GType
gtype
getObjectPropertyEnum :: forall a b. (GObject a,
Enum b, BoxedEnum b) =>
a -> String -> IO b
getObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
getObjectPropertyEnum a
obj String
propName = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName
(\Ptr GValue
val -> Int -> b
forall a. Enum a => Int -> a
toEnum (Int -> b) -> (CUInt -> Int) -> CUInt -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUInt -> b) -> IO CUInt -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr GValue -> IO CUInt
get_enum Ptr GValue
val)
GType
gtype
setObjectPropertyFlags :: forall a b. (IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
setObjectPropertyFlags :: forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
setObjectPropertyFlags a
obj String
propName [b]
flags = do
let cFlags :: CUInt
cFlags = [b] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [b]
flags
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
a
-> String
-> CUInt
-> (Ptr GValue -> CUInt -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName CUInt
cFlags Ptr GValue -> CUInt -> IO ()
set_flags GType
gtype
constructObjectPropertyFlags :: forall a o. (IsGFlag a, BoxedFlags a)
=> String -> [a] -> IO (GValueConstruct o)
constructObjectPropertyFlags :: forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
constructObjectPropertyFlags String
propName [a]
flags = do
let cFlags :: CUInt
cFlags = [a] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [a]
flags
GType
gtype <- forall a. TypedObject a => IO GType
glibType @a
String
-> CUInt
-> (Ptr GValue -> CUInt -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName CUInt
cFlags Ptr GValue -> CUInt -> IO ()
set_flags GType
gtype
getObjectPropertyFlags :: forall a b. (GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
getObjectPropertyFlags :: forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
getObjectPropertyFlags a
obj String
propName = do
GType
gtype <- forall a. TypedObject a => IO GType
glibType @b
a -> String -> (Ptr GValue -> IO [b]) -> GType -> IO [b]
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName
(\Ptr GValue
val -> CUInt -> [b]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags (CUInt -> [b]) -> IO CUInt -> IO [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr GValue -> IO CUInt
get_flags Ptr GValue
val)
GType
gtype
setObjectPropertyClosure :: forall a b. GObject a =>
a -> String -> Maybe (GClosure b) -> IO ()
setObjectPropertyClosure :: forall a b. GObject a => a -> String -> Maybe (GClosure b) -> IO ()
setObjectPropertyClosure = a -> String -> Maybe (GClosure b) -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyBoxed
constructObjectPropertyClosure :: String -> Maybe (GClosure a) -> IO (GValueConstruct o)
constructObjectPropertyClosure :: forall a o. String -> Maybe (GClosure a) -> IO (GValueConstruct o)
constructObjectPropertyClosure = String -> Maybe (GClosure a) -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyBoxed
getObjectPropertyClosure :: forall a b. GObject a =>
a -> String -> IO (Maybe (GClosure b))
getObjectPropertyClosure :: forall a b. GObject a => a -> String -> IO (Maybe (GClosure b))
getObjectPropertyClosure a
obj String
propName =
a
-> String
-> (ManagedPtr (GClosure b) -> GClosure b)
-> IO (Maybe (GClosure b))
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyBoxed a
obj String
propName ManagedPtr (GClosure b) -> GClosure b
forall a. ManagedPtr (GClosure a) -> GClosure a
GClosure
setObjectPropertyVariant :: GObject a =>
a -> String -> Maybe GVariant -> IO ()
setObjectPropertyVariant :: forall a. GObject a => a -> String -> Maybe GVariant -> IO ()
setObjectPropertyVariant a
obj String
propName Maybe GVariant
maybeVariant =
Maybe GVariant -> (Ptr GVariant -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe GVariant
maybeVariant ((Ptr GVariant -> IO ()) -> IO ())
-> (Ptr GVariant -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GVariant
variantPtr ->
a
-> String
-> Ptr GVariant
-> (Ptr GValue -> Ptr GVariant -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr GVariant
variantPtr Ptr GValue -> Ptr GVariant -> IO ()
set_variant GType
gtypeVariant
constructObjectPropertyVariant :: String -> Maybe GVariant
-> IO (GValueConstruct o)
constructObjectPropertyVariant :: forall o. String -> Maybe GVariant -> IO (GValueConstruct o)
constructObjectPropertyVariant String
propName Maybe GVariant
maybeVariant =
Maybe GVariant
-> (Ptr GVariant -> IO (GValueConstruct o))
-> IO (GValueConstruct o)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
Maybe a -> (Ptr a -> IO c) -> IO c
maybeWithManagedPtr Maybe GVariant
maybeVariant ((Ptr GVariant -> IO (GValueConstruct o))
-> IO (GValueConstruct o))
-> (Ptr GVariant -> IO (GValueConstruct o))
-> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ \Ptr GVariant
objPtr ->
String
-> Ptr GVariant
-> (Ptr GValue -> Ptr GVariant -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr GVariant
objPtr Ptr GValue -> Ptr GVariant -> IO ()
set_variant GType
gtypeVariant
getObjectPropertyVariant :: GObject a => a -> String ->
IO (Maybe GVariant)
getObjectPropertyVariant :: forall a. GObject a => a -> String -> IO (Maybe GVariant)
getObjectPropertyVariant a
obj String
propName =
a
-> String
-> (Ptr GValue -> IO (Maybe GVariant))
-> GType
-> IO (Maybe GVariant)
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName (Ptr GValue -> IO (Ptr GVariant)
get_variant (Ptr GValue -> IO (Ptr GVariant))
-> (Ptr GVariant -> IO (Maybe GVariant))
-> Ptr GValue
-> IO (Maybe GVariant)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
(Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant)
-> Ptr GVariant
-> IO (Maybe GVariant)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant -> IO GVariant
newGVariantFromPtr)
GType
gtypeVariant
setObjectPropertyByteArray :: GObject a =>
a -> String -> Maybe B.ByteString -> IO ()
setObjectPropertyByteArray :: forall a. GObject a => a -> String -> Maybe ByteString -> IO ()
setObjectPropertyByteArray a
obj String
propName Maybe ByteString
Nothing =
a
-> String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr Any
forall a. Ptr a
nullPtr Ptr GValue -> Ptr Any -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeByteArray
setObjectPropertyByteArray a
obj String
propName (Just ByteString
bytes) = do
Ptr GByteArray
packed <- ByteString -> IO (Ptr GByteArray)
packGByteArray ByteString
bytes
a
-> String
-> Ptr GByteArray
-> (Ptr GValue -> Ptr GByteArray -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr GByteArray
packed Ptr GValue -> Ptr GByteArray -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeByteArray
Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
packed
constructObjectPropertyByteArray :: String -> Maybe B.ByteString ->
IO (GValueConstruct o)
constructObjectPropertyByteArray :: forall o. String -> Maybe ByteString -> IO (GValueConstruct o)
constructObjectPropertyByteArray String
propName Maybe ByteString
Nothing =
String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr Any
forall a. Ptr a
nullPtr Ptr GValue -> Ptr Any -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeByteArray
constructObjectPropertyByteArray String
propName (Just ByteString
bytes) = do
Ptr GByteArray
packed <- ByteString -> IO (Ptr GByteArray)
packGByteArray ByteString
bytes
GValueConstruct o
result <- String
-> Ptr GByteArray
-> (Ptr GValue -> Ptr GByteArray -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr GByteArray
packed Ptr GValue -> Ptr GByteArray -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypeByteArray
Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
packed
GValueConstruct o -> IO (GValueConstruct o)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValueConstruct o
result
getObjectPropertyByteArray :: GObject a =>
a -> String -> IO (Maybe B.ByteString)
getObjectPropertyByteArray :: forall a. GObject a => a -> String -> IO (Maybe ByteString)
getObjectPropertyByteArray a
obj String
propName =
a
-> String
-> (Ptr GValue -> IO (Maybe ByteString))
-> GType
-> IO (Maybe ByteString)
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName (Ptr GValue -> IO (Ptr GByteArray)
forall b. Ptr GValue -> IO (Ptr b)
get_boxed (Ptr GValue -> IO (Ptr GByteArray))
-> (Ptr GByteArray -> IO (Maybe ByteString))
-> Ptr GValue
-> IO (Maybe ByteString)
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
(Ptr GByteArray
-> (Ptr GByteArray -> IO ByteString) -> IO (Maybe ByteString))
-> (Ptr GByteArray -> IO ByteString)
-> Ptr GByteArray
-> IO (Maybe ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr GByteArray
-> (Ptr GByteArray -> IO ByteString) -> IO (Maybe ByteString)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GByteArray -> IO ByteString
unpackGByteArray)
GType
gtypeByteArray
setObjectPropertyPtrGList :: GObject a =>
a -> String -> [Ptr b] -> IO ()
setObjectPropertyPtrGList :: forall a b. GObject a => a -> String -> [Ptr b] -> IO ()
setObjectPropertyPtrGList a
obj String
propName [Ptr b]
ptrs = do
Ptr (GList (Ptr b))
packed <- [Ptr b] -> IO (Ptr (GList (Ptr b)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr b]
ptrs
a
-> String
-> Ptr (GList (Ptr b))
-> (Ptr GValue -> Ptr (GList (Ptr b)) -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName Ptr (GList (Ptr b))
packed Ptr GValue -> Ptr (GList (Ptr b)) -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypePointer
Ptr (GList (Ptr b)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr b))
packed
constructObjectPropertyPtrGList :: String -> [Ptr a] ->
IO (GValueConstruct o)
constructObjectPropertyPtrGList :: forall a o. String -> [Ptr a] -> IO (GValueConstruct o)
constructObjectPropertyPtrGList String
propName [Ptr a]
ptrs = do
Ptr (GList (Ptr a))
packed <- [Ptr a] -> IO (Ptr (GList (Ptr a)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr a]
ptrs
GValueConstruct o
result <- String
-> Ptr (GList (Ptr a))
-> (Ptr GValue -> Ptr (GList (Ptr a)) -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName Ptr (GList (Ptr a))
packed Ptr GValue -> Ptr (GList (Ptr a)) -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
set_boxed GType
gtypePointer
Ptr (GList (Ptr a)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr a))
packed
GValueConstruct o -> IO (GValueConstruct o)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValueConstruct o
result
getObjectPropertyPtrGList :: GObject a =>
a -> String -> IO [Ptr b]
getObjectPropertyPtrGList :: forall a b. GObject a => a -> String -> IO [Ptr b]
getObjectPropertyPtrGList a
obj String
propName =
a -> String -> (Ptr GValue -> IO [Ptr b]) -> GType -> IO [Ptr b]
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName (Ptr GValue -> IO (Ptr (GList (Ptr b)))
forall a. IsGValue a => Ptr GValue -> IO a
gvalueGet_ (Ptr GValue -> IO (Ptr (GList (Ptr b))))
-> (Ptr (GList (Ptr b)) -> IO [Ptr b]) -> Ptr GValue -> IO [Ptr b]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Ptr (GList (Ptr b)) -> IO [Ptr b]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList) GType
gtypePointer
setObjectPropertyHash :: GObject a => a -> String -> b -> IO ()
setObjectPropertyHash :: forall a b. GObject a => a -> String -> b -> IO ()
setObjectPropertyHash =
String -> a -> String -> b -> IO ()
forall a. HasCallStack => String -> a
error (String -> a -> String -> b -> IO ())
-> String -> a -> String -> b -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Setting GHashTable properties not supported yet."
constructObjectPropertyHash :: String -> b -> IO (GValueConstruct o)
constructObjectPropertyHash :: forall b o. String -> b -> IO (GValueConstruct o)
constructObjectPropertyHash =
String -> String -> b -> IO (GValueConstruct o)
forall a. HasCallStack => String -> a
error (String -> String -> b -> IO (GValueConstruct o))
-> String -> String -> b -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String
"Constructing GHashTable properties not supported yet."
getObjectPropertyHash :: GObject a => a -> String -> IO b
getObjectPropertyHash :: forall a b. GObject a => a -> String -> IO b
getObjectPropertyHash =
String -> a -> String -> IO b
forall a. HasCallStack => String -> a
error (String -> a -> String -> IO b) -> String -> a -> String -> IO b
forall a b. (a -> b) -> a -> b
$ String
"Getting GHashTable properties not supported yet."
setObjectPropertyCallback :: GObject a => a -> String -> FunPtr b -> IO ()
setObjectPropertyCallback :: forall a b. GObject a => a -> String -> FunPtr b -> IO ()
setObjectPropertyCallback a
obj String
propName FunPtr b
funPtr =
a
-> String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO ()
forall a b.
GObject a =>
a -> String -> b -> (Ptr GValue -> b -> IO ()) -> GType -> IO ()
setObjectProperty a
obj String
propName (FunPtr b -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr b
funPtr) Ptr GValue -> Ptr Any -> IO ()
forall a. IsGValue a => Ptr GValue -> a -> IO ()
gvalueSet_ GType
gtypePointer
constructObjectPropertyCallback :: String -> FunPtr b -> IO (GValueConstruct o)
constructObjectPropertyCallback :: forall b o. String -> FunPtr b -> IO (GValueConstruct o)
constructObjectPropertyCallback String
propName FunPtr b
funPtr =
String
-> Ptr Any
-> (Ptr GValue -> Ptr Any -> IO ())
-> GType
-> IO (GValueConstruct o)
forall b o.
String
-> b
-> (Ptr GValue -> b -> IO ())
-> GType
-> IO (GValueConstruct o)
constructObjectProperty String
propName (FunPtr b -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr b
funPtr) Ptr GValue -> Ptr Any -> IO ()
forall a. IsGValue a => Ptr GValue -> a -> IO ()
gvalueSet_ GType
gtypePointer
getObjectPropertyCallback :: GObject a => a -> String ->
(FunPtr b -> c) -> IO (Maybe c)
getObjectPropertyCallback :: forall a b c.
GObject a =>
a -> String -> (FunPtr b -> c) -> IO (Maybe c)
getObjectPropertyCallback a
obj String
propName FunPtr b -> c
wrapper = do
Ptr Any
ptr <- a
-> String -> (Ptr GValue -> IO (Ptr Any)) -> GType -> IO (Ptr Any)
forall a b.
GObject a =>
a -> String -> (Ptr GValue -> IO b) -> GType -> IO b
getObjectProperty a
obj String
propName Ptr GValue -> IO (Ptr Any)
forall a. IsGValue a => Ptr GValue -> IO a
gvalueGet_ GType
gtypePointer
if Ptr Any
ptr Ptr Any -> Ptr Any -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Any
forall a. Ptr a
nullPtr
then Maybe c -> IO (Maybe c)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe c -> IO (Maybe c))
-> (FunPtr b -> Maybe c) -> FunPtr b -> IO (Maybe c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Maybe c
forall a. a -> Maybe a
Just (c -> Maybe c) -> (FunPtr b -> c) -> FunPtr b -> Maybe c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunPtr b -> c
wrapper (FunPtr b -> IO (Maybe c)) -> FunPtr b -> IO (Maybe c)
forall a b. (a -> b) -> a -> b
$ Ptr Any -> FunPtr b
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
ptr
else Maybe c -> IO (Maybe c)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe c
forall a. Maybe a
Nothing
setObjectPropertyGError :: forall a. GObject a =>
a -> String -> Maybe GError -> IO ()
setObjectPropertyGError :: forall a. GObject a => a -> String -> Maybe GError -> IO ()
setObjectPropertyGError = a -> String -> Maybe GError -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyBoxed
constructObjectPropertyGError :: String -> Maybe GError -> IO (GValueConstruct o)
constructObjectPropertyGError :: forall o. String -> Maybe GError -> IO (GValueConstruct o)
constructObjectPropertyGError = String -> Maybe GError -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyBoxed
getObjectPropertyGError :: forall a. GObject a =>
a -> String -> IO (Maybe GError)
getObjectPropertyGError :: forall a. GObject a => a -> String -> IO (Maybe GError)
getObjectPropertyGError a
obj String
propName =
a -> String -> (ManagedPtr GError -> GError) -> IO (Maybe GError)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyBoxed a
obj String
propName ManagedPtr GError -> GError
GError
setObjectPropertyGValue :: forall a. GObject a =>
a -> String -> Maybe GValue -> IO ()
setObjectPropertyGValue :: forall a. GObject a => a -> String -> Maybe GValue -> IO ()
setObjectPropertyGValue = a -> String -> Maybe GValue -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
setObjectPropertyBoxed
constructObjectPropertyGValue :: String -> Maybe GValue -> IO (GValueConstruct o)
constructObjectPropertyGValue :: forall o. String -> Maybe GValue -> IO (GValueConstruct o)
constructObjectPropertyGValue = String -> Maybe GValue -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
constructObjectPropertyBoxed
getObjectPropertyGValue :: forall a. GObject a =>
a -> String -> IO (Maybe GValue)
getObjectPropertyGValue :: forall a. GObject a => a -> String -> IO (Maybe GValue)
getObjectPropertyGValue a
obj String
propName =
a -> String -> (ManagedPtr GValue -> GValue) -> IO (Maybe GValue)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
getObjectPropertyBoxed a
obj String
propName ManagedPtr GValue -> GValue
GValue
constructObjectPropertyParamSpec :: String -> Maybe GParamSpec ->
IO (GValueConstruct o)
constructObjectPropertyParamSpec :: forall o. String -> Maybe GParamSpec -> IO (GValueConstruct o)
constructObjectPropertyParamSpec = String -> Maybe GParamSpec -> IO (GValueConstruct o)
forall b o. IsGValue b => String -> b -> IO (GValueConstruct o)
constructObjectPropertyIsGValueInstance
getObjectPropertyParamSpec :: GObject a => a -> String -> IO (Maybe GParamSpec)
getObjectPropertyParamSpec :: forall a. GObject a => a -> String -> IO (Maybe GParamSpec)
getObjectPropertyParamSpec = a -> String -> IO (Maybe GParamSpec)
forall a b. (GObject a, IsGValue b) => a -> String -> IO b
getObjectPropertyIsGValueInstance
setObjectPropertyParamSpec :: GObject a =>
a -> String -> Maybe GParamSpec -> IO ()
setObjectPropertyParamSpec :: forall a. GObject a => a -> String -> Maybe GParamSpec -> IO ()
setObjectPropertyParamSpec = a -> String -> Maybe GParamSpec -> IO ()
forall a b. (GObject a, IsGValue b) => a -> String -> b -> IO ()
setObjectPropertyIsGValueInstance