Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- setObjectPropertyIsGValueInstance :: (GObject a, IsGValue b) => a -> String -> b -> IO ()
- setObjectPropertyString :: GObject a => a -> String -> Maybe Text -> IO ()
- setObjectPropertyStringArray :: GObject a => a -> String -> Maybe [Text] -> IO ()
- setObjectPropertyPtr :: GObject a => a -> String -> Ptr b -> IO ()
- setObjectPropertyInt :: GObject a => a -> String -> CInt -> IO ()
- setObjectPropertyUInt :: GObject a => a -> String -> CUInt -> IO ()
- setObjectPropertyLong :: GObject a => a -> String -> CLong -> IO ()
- setObjectPropertyULong :: GObject a => a -> String -> CULong -> IO ()
- setObjectPropertyInt32 :: GObject a => a -> String -> Int32 -> IO ()
- setObjectPropertyUInt32 :: GObject a => a -> String -> Word32 -> IO ()
- setObjectPropertyInt64 :: GObject a => a -> String -> Int64 -> IO ()
- setObjectPropertyUInt64 :: GObject a => a -> String -> Word64 -> IO ()
- setObjectPropertyFloat :: GObject a => a -> String -> Float -> IO ()
- setObjectPropertyDouble :: GObject a => a -> String -> Double -> IO ()
- setObjectPropertyBool :: GObject a => a -> String -> Bool -> IO ()
- setObjectPropertyGType :: GObject a => a -> String -> GType -> IO ()
- setObjectPropertyObject :: forall a b. (GObject a, GObject b) => a -> String -> Maybe b -> IO ()
- setObjectPropertyBoxed :: forall a b. (GObject a, GBoxed b) => a -> String -> Maybe b -> IO ()
- setObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> b -> IO ()
- setObjectPropertyFlags :: forall a b. (IsGFlag b, BoxedFlags b, GObject a) => a -> String -> [b] -> IO ()
- setObjectPropertyClosure :: forall a b. GObject a => a -> String -> Maybe (GClosure b) -> IO ()
- setObjectPropertyVariant :: GObject a => a -> String -> Maybe GVariant -> IO ()
- setObjectPropertyByteArray :: GObject a => a -> String -> Maybe ByteString -> IO ()
- setObjectPropertyPtrGList :: GObject a => a -> String -> [Ptr b] -> IO ()
- setObjectPropertyHash :: GObject a => a -> String -> b -> IO ()
- setObjectPropertyCallback :: GObject a => a -> String -> FunPtr b -> IO ()
- setObjectPropertyGError :: forall a. GObject a => a -> String -> Maybe GError -> IO ()
- setObjectPropertyGValue :: forall a. GObject a => a -> String -> Maybe GValue -> IO ()
- getObjectPropertyIsGValueInstance :: forall a b. (GObject a, IsGValue b) => a -> String -> IO b
- getObjectPropertyString :: GObject a => a -> String -> IO (Maybe Text)
- getObjectPropertyStringArray :: GObject a => a -> String -> IO (Maybe [Text])
- getObjectPropertyPtr :: GObject a => a -> String -> IO (Ptr b)
- getObjectPropertyInt :: GObject a => a -> String -> IO CInt
- getObjectPropertyUInt :: GObject a => a -> String -> IO CUInt
- getObjectPropertyLong :: GObject a => a -> String -> IO CLong
- getObjectPropertyULong :: GObject a => a -> String -> IO CULong
- getObjectPropertyInt32 :: GObject a => a -> String -> IO Int32
- getObjectPropertyUInt32 :: GObject a => a -> String -> IO Word32
- getObjectPropertyInt64 :: GObject a => a -> String -> IO Int64
- getObjectPropertyUInt64 :: GObject a => a -> String -> IO Word64
- getObjectPropertyFloat :: GObject a => a -> String -> IO Float
- getObjectPropertyDouble :: GObject a => a -> String -> IO Double
- getObjectPropertyBool :: GObject a => a -> String -> IO Bool
- getObjectPropertyGType :: GObject a => a -> String -> IO GType
- getObjectPropertyObject :: forall a b. (GObject a, GObject 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)
- getObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
- getObjectPropertyFlags :: forall a b. (GObject a, IsGFlag b, BoxedFlags b) => a -> String -> IO [b]
- getObjectPropertyClosure :: forall a b. GObject a => a -> String -> IO (Maybe (GClosure b))
- getObjectPropertyVariant :: GObject a => a -> String -> IO (Maybe GVariant)
- getObjectPropertyByteArray :: GObject a => a -> String -> IO (Maybe ByteString)
- getObjectPropertyPtrGList :: GObject a => a -> String -> IO [Ptr b]
- getObjectPropertyHash :: GObject a => a -> String -> IO b
- getObjectPropertyCallback :: GObject a => a -> String -> (FunPtr b -> c) -> IO (Maybe c)
- getObjectPropertyGError :: forall a. GObject a => a -> String -> IO (Maybe GError)
- getObjectPropertyGValue :: forall a. GObject a => a -> String -> IO (Maybe GValue)
- constructObjectPropertyIsGValueInstance :: IsGValue b => String -> b -> IO (GValueConstruct o)
- constructObjectPropertyString :: String -> Maybe Text -> IO (GValueConstruct o)
- constructObjectPropertyStringArray :: String -> Maybe [Text] -> IO (GValueConstruct o)
- constructObjectPropertyPtr :: String -> Ptr b -> IO (GValueConstruct o)
- constructObjectPropertyInt :: String -> CInt -> IO (GValueConstruct o)
- constructObjectPropertyUInt :: String -> CUInt -> IO (GValueConstruct o)
- constructObjectPropertyLong :: String -> CLong -> IO (GValueConstruct o)
- constructObjectPropertyULong :: String -> CULong -> IO (GValueConstruct o)
- constructObjectPropertyInt32 :: String -> Int32 -> IO (GValueConstruct o)
- constructObjectPropertyUInt32 :: String -> Word32 -> IO (GValueConstruct o)
- constructObjectPropertyInt64 :: String -> Int64 -> IO (GValueConstruct o)
- constructObjectPropertyUInt64 :: String -> Word64 -> IO (GValueConstruct o)
- constructObjectPropertyFloat :: String -> Float -> IO (GValueConstruct o)
- constructObjectPropertyDouble :: String -> Double -> IO (GValueConstruct o)
- constructObjectPropertyBool :: String -> Bool -> IO (GValueConstruct o)
- constructObjectPropertyGType :: String -> GType -> IO (GValueConstruct o)
- constructObjectPropertyObject :: forall a o. GObject a => String -> Maybe a -> IO (GValueConstruct o)
- constructObjectPropertyBoxed :: forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
- constructObjectPropertyEnum :: forall a o. (Enum a, BoxedEnum a) => String -> a -> IO (GValueConstruct o)
- constructObjectPropertyFlags :: forall a o. (IsGFlag a, BoxedFlags a) => String -> [a] -> IO (GValueConstruct o)
- constructObjectPropertyClosure :: String -> Maybe (GClosure a) -> IO (GValueConstruct o)
- constructObjectPropertyVariant :: String -> Maybe GVariant -> IO (GValueConstruct o)
- constructObjectPropertyByteArray :: String -> Maybe ByteString -> IO (GValueConstruct o)
- constructObjectPropertyPtrGList :: String -> [Ptr a] -> IO (GValueConstruct o)
- constructObjectPropertyHash :: String -> b -> IO (GValueConstruct o)
- constructObjectPropertyCallback :: String -> FunPtr b -> IO (GValueConstruct o)
- constructObjectPropertyGError :: String -> Maybe GError -> IO (GValueConstruct o)
- constructObjectPropertyGValue :: String -> Maybe GValue -> IO (GValueConstruct o)
Documentation
setObjectPropertyIsGValueInstance :: (GObject a, IsGValue b) => a -> String -> b -> IO () Source #
Set a property for a type with a IsGValue
instance.
setObjectPropertyObject :: forall a b. (GObject a, GObject b) => a -> String -> Maybe b -> IO () Source #
setObjectPropertyBoxed :: forall a b. (GObject a, GBoxed b) => a -> String -> Maybe b -> IO () Source #
setObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> b -> IO () Source #
setObjectPropertyFlags :: forall a b. (IsGFlag b, BoxedFlags b, GObject a) => a -> String -> [b] -> IO () Source #
setObjectPropertyClosure :: forall a b. GObject a => a -> String -> Maybe (GClosure b) -> IO () Source #
setObjectPropertyByteArray :: GObject a => a -> String -> Maybe ByteString -> IO () Source #
setObjectPropertyGError :: forall a. GObject a => a -> String -> Maybe GError -> IO () Source #
Set a property of type GError
.
setObjectPropertyGValue :: forall a. GObject a => a -> String -> Maybe GValue -> IO () Source #
Set a property of type GValue
.
getObjectPropertyIsGValueInstance :: forall a b. (GObject a, IsGValue b) => a -> String -> IO b Source #
Get a nullable property for a type with a IsGValue
instance.
getObjectPropertyObject :: forall a b. (GObject a, GObject b) => a -> String -> (ManagedPtr b -> b) -> IO (Maybe b) Source #
getObjectPropertyBoxed :: forall a b. (GObject a, GBoxed b) => a -> String -> (ManagedPtr b -> b) -> IO (Maybe b) Source #
getObjectPropertyEnum :: forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b Source #
getObjectPropertyFlags :: forall a b. (GObject a, IsGFlag b, BoxedFlags b) => a -> String -> IO [b] Source #
getObjectPropertyClosure :: forall a b. GObject a => a -> String -> IO (Maybe (GClosure b)) Source #
getObjectPropertyByteArray :: GObject a => a -> String -> IO (Maybe ByteString) Source #
getObjectPropertyGError :: forall a. GObject a => a -> String -> IO (Maybe GError) Source #
Get the value of a property of type GError
.
getObjectPropertyGValue :: forall a. GObject a => a -> String -> IO (Maybe GValue) Source #
Get the value of a property of type GValue
.
constructObjectPropertyIsGValueInstance :: IsGValue b => String -> b -> IO (GValueConstruct o) Source #
Construct a property for a type with a IsGValue
instance.
constructObjectPropertyString :: String -> Maybe Text -> IO (GValueConstruct o) Source #
constructObjectPropertyStringArray :: String -> Maybe [Text] -> IO (GValueConstruct o) Source #
constructObjectPropertyPtr :: String -> Ptr b -> IO (GValueConstruct o) Source #
constructObjectPropertyInt :: String -> CInt -> IO (GValueConstruct o) Source #
constructObjectPropertyUInt :: String -> CUInt -> IO (GValueConstruct o) Source #
constructObjectPropertyLong :: String -> CLong -> IO (GValueConstruct o) Source #
constructObjectPropertyULong :: String -> CULong -> IO (GValueConstruct o) Source #
constructObjectPropertyInt32 :: String -> Int32 -> IO (GValueConstruct o) Source #
constructObjectPropertyUInt32 :: String -> Word32 -> IO (GValueConstruct o) Source #
constructObjectPropertyInt64 :: String -> Int64 -> IO (GValueConstruct o) Source #
constructObjectPropertyUInt64 :: String -> Word64 -> IO (GValueConstruct o) Source #
constructObjectPropertyFloat :: String -> Float -> IO (GValueConstruct o) Source #
constructObjectPropertyDouble :: String -> Double -> IO (GValueConstruct o) Source #
constructObjectPropertyBool :: String -> Bool -> IO (GValueConstruct o) Source #
constructObjectPropertyGType :: String -> GType -> IO (GValueConstruct o) Source #
constructObjectPropertyObject :: forall a o. GObject a => String -> Maybe a -> IO (GValueConstruct o) Source #
constructObjectPropertyBoxed :: forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o) Source #
constructObjectPropertyEnum :: forall a o. (Enum a, BoxedEnum a) => String -> a -> IO (GValueConstruct o) Source #
constructObjectPropertyFlags :: forall a o. (IsGFlag a, BoxedFlags a) => String -> [a] -> IO (GValueConstruct o) Source #
constructObjectPropertyClosure :: String -> Maybe (GClosure a) -> IO (GValueConstruct o) Source #
constructObjectPropertyVariant :: String -> Maybe GVariant -> IO (GValueConstruct o) Source #
constructObjectPropertyByteArray :: String -> Maybe ByteString -> IO (GValueConstruct o) Source #
constructObjectPropertyPtrGList :: String -> [Ptr a] -> IO (GValueConstruct o) Source #
constructObjectPropertyHash :: String -> b -> IO (GValueConstruct o) Source #
constructObjectPropertyCallback :: String -> FunPtr b -> IO (GValueConstruct o) Source #
constructObjectPropertyGError :: String -> Maybe GError -> IO (GValueConstruct o) Source #
Construct a property of type GError
.
constructObjectPropertyGValue :: String -> Maybe GValue -> IO (GValueConstruct o) Source #
Construct a property of type GValue
.