|
System.Glib.Properties | Portability | portable (depends on GHC) | Stability | provisional | Maintainer | gtk2hs-users@lists.sourceforge.net |
|
|
|
|
|
Description |
Functions for getting and setting GObject properties
|
|
Synopsis |
|
objectSetPropertyInt :: GObjectClass gobj => String -> gobj -> Int -> IO () | | objectGetPropertyInt :: GObjectClass gobj => String -> gobj -> IO Int | | objectSetPropertyUInt :: GObjectClass gobj => String -> gobj -> Int -> IO () | | objectGetPropertyUInt :: GObjectClass gobj => String -> gobj -> IO Int | | objectSetPropertyInt64 :: GObjectClass gobj => String -> gobj -> Int64 -> IO () | | objectGetPropertyInt64 :: GObjectClass gobj => String -> gobj -> IO Int64 | | objectSetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> Word64 -> IO () | | objectGetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> IO Word64 | | objectSetPropertyChar :: GObjectClass gobj => String -> gobj -> Char -> IO () | | objectGetPropertyChar :: GObjectClass gobj => String -> gobj -> IO Char | | objectSetPropertyBool :: GObjectClass gobj => String -> gobj -> Bool -> IO () | | objectGetPropertyBool :: GObjectClass gobj => String -> gobj -> IO Bool | | objectSetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> enum -> IO () | | objectGetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> IO enum | | objectSetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> [flag] -> IO () | | objectGetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> IO [flag] | | objectSetPropertyFloat :: GObjectClass gobj => String -> gobj -> Float -> IO () | | objectGetPropertyFloat :: GObjectClass gobj => String -> gobj -> IO Float | | objectSetPropertyDouble :: GObjectClass gobj => String -> gobj -> Double -> IO () | | objectGetPropertyDouble :: GObjectClass gobj => String -> gobj -> IO Double | | objectSetPropertyString :: GObjectClass gobj => String -> gobj -> String -> IO () | | objectGetPropertyString :: GObjectClass gobj => String -> gobj -> IO String | | objectSetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> Maybe String -> IO () | | objectGetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> IO (Maybe String) | | objectSetPropertyBoxedOpaque :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> GType -> String -> gobj -> boxed -> IO () | | objectGetPropertyBoxedOpaque :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> GType -> String -> gobj -> IO boxed | | objectSetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> boxed -> IO () | | objectGetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> IO boxed | | objectSetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> gobj' -> IO () | | objectGetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> IO gobj' | | newAttrFromIntProperty :: GObjectClass gobj => String -> Attr gobj Int | | readAttrFromIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int | | newAttrFromUIntProperty :: GObjectClass gobj => String -> Attr gobj Int | | newAttrFromCharProperty :: GObjectClass gobj => String -> Attr gobj Char | | writeAttrFromUIntProperty :: GObjectClass gobj => String -> WriteAttr gobj Int | | newAttrFromBoolProperty :: GObjectClass gobj => String -> Attr gobj Bool | | readAttrFromBoolProperty :: GObjectClass gobj => String -> ReadAttr gobj Bool | | newAttrFromFloatProperty :: GObjectClass gobj => String -> Attr gobj Float | | newAttrFromDoubleProperty :: GObjectClass gobj => String -> Attr gobj Double | | newAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> Attr gobj enum | | readAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> ReadAttr gobj enum | | writeAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> WriteAttr gobj enum | | newAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> GType -> Attr gobj [flag] | | newAttrFromStringProperty :: GObjectClass gobj => String -> Attr gobj String | | readAttrFromStringProperty :: GObjectClass gobj => String -> ReadAttr gobj String | | writeAttrFromStringProperty :: GObjectClass gobj => String -> WriteAttr gobj String | | writeAttrFromMaybeStringProperty :: GObjectClass gobj => String -> WriteAttr gobj (Maybe String) | | newAttrFromMaybeStringProperty :: GObjectClass gobj => String -> Attr gobj (Maybe String) | | newAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> Attr gobj boxed | | writeAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> WriteAttr gobj boxed | | newAttrFromBoxedStorableProperty :: (GObjectClass gobj, Storable boxed) => String -> GType -> Attr gobj boxed | | newAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj gobj' gobj'' | | writeAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj gobj' | | objectGetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> IO a) -> String -> gobj -> IO a | | objectSetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> a -> IO ()) -> String -> gobj -> a -> IO () |
|
|
|
per-type functions for getting and setting GObject properties
|
|
objectSetPropertyInt :: GObjectClass gobj => String -> gobj -> Int -> IO () |
|
objectGetPropertyInt :: GObjectClass gobj => String -> gobj -> IO Int |
|
objectSetPropertyUInt :: GObjectClass gobj => String -> gobj -> Int -> IO () |
|
objectGetPropertyUInt :: GObjectClass gobj => String -> gobj -> IO Int |
|
objectSetPropertyInt64 :: GObjectClass gobj => String -> gobj -> Int64 -> IO () |
|
objectGetPropertyInt64 :: GObjectClass gobj => String -> gobj -> IO Int64 |
|
objectSetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> Word64 -> IO () |
|
objectGetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> IO Word64 |
|
objectSetPropertyChar :: GObjectClass gobj => String -> gobj -> Char -> IO () |
|
objectGetPropertyChar :: GObjectClass gobj => String -> gobj -> IO Char |
|
objectSetPropertyBool :: GObjectClass gobj => String -> gobj -> Bool -> IO () |
|
objectGetPropertyBool :: GObjectClass gobj => String -> gobj -> IO Bool |
|
objectSetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> enum -> IO () |
|
objectGetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> IO enum |
|
objectSetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> [flag] -> IO () |
|
objectGetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> IO [flag] |
|
objectSetPropertyFloat :: GObjectClass gobj => String -> gobj -> Float -> IO () |
|
objectGetPropertyFloat :: GObjectClass gobj => String -> gobj -> IO Float |
|
objectSetPropertyDouble :: GObjectClass gobj => String -> gobj -> Double -> IO () |
|
objectGetPropertyDouble :: GObjectClass gobj => String -> gobj -> IO Double |
|
objectSetPropertyString :: GObjectClass gobj => String -> gobj -> String -> IO () |
|
objectGetPropertyString :: GObjectClass gobj => String -> gobj -> IO String |
|
objectSetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> Maybe String -> IO () |
|
objectGetPropertyMaybeString :: GObjectClass gobj => String -> gobj -> IO (Maybe String) |
|
objectSetPropertyBoxedOpaque :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> GType -> String -> gobj -> boxed -> IO () |
|
objectGetPropertyBoxedOpaque :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> GType -> String -> gobj -> IO boxed |
|
objectSetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> boxed -> IO () |
|
objectGetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> IO boxed |
|
objectSetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> gobj' -> IO () |
|
objectGetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> IO gobj' |
|
constructors for attributes backed by GObject properties
|
|
newAttrFromIntProperty :: GObjectClass gobj => String -> Attr gobj Int |
|
readAttrFromIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int |
|
newAttrFromUIntProperty :: GObjectClass gobj => String -> Attr gobj Int |
|
newAttrFromCharProperty :: GObjectClass gobj => String -> Attr gobj Char |
|
writeAttrFromUIntProperty :: GObjectClass gobj => String -> WriteAttr gobj Int |
|
newAttrFromBoolProperty :: GObjectClass gobj => String -> Attr gobj Bool |
|
readAttrFromBoolProperty :: GObjectClass gobj => String -> ReadAttr gobj Bool |
|
newAttrFromFloatProperty :: GObjectClass gobj => String -> Attr gobj Float |
|
newAttrFromDoubleProperty :: GObjectClass gobj => String -> Attr gobj Double |
|
newAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> Attr gobj enum |
|
readAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> ReadAttr gobj enum |
|
writeAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> WriteAttr gobj enum |
|
newAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> GType -> Attr gobj [flag] |
|
newAttrFromStringProperty :: GObjectClass gobj => String -> Attr gobj String |
|
readAttrFromStringProperty :: GObjectClass gobj => String -> ReadAttr gobj String |
|
writeAttrFromStringProperty :: GObjectClass gobj => String -> WriteAttr gobj String |
|
writeAttrFromMaybeStringProperty :: GObjectClass gobj => String -> WriteAttr gobj (Maybe String) |
|
newAttrFromMaybeStringProperty :: GObjectClass gobj => String -> Attr gobj (Maybe String) |
|
newAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> Attr gobj boxed |
|
writeAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> WriteAttr gobj boxed |
|
newAttrFromBoxedStorableProperty :: (GObjectClass gobj, Storable boxed) => String -> GType -> Attr gobj boxed |
|
newAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj gobj' gobj'' |
|
writeAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj gobj' |
|
objectGetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> IO a) -> String -> gobj -> IO a |
|
objectSetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> a -> IO ()) -> String -> gobj -> a -> IO () |
|
Produced by Haddock version 0.8 |