Maintainer | gtk2hs-users@lists.sourceforge.net |
---|---|
Stability | provisional |
Portability | portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell98 |
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, GlibString string) => String -> gobj -> string -> IO ()
- objectGetPropertyString :: (GObjectClass gobj, GlibString string) => String -> gobj -> IO string
- objectSetPropertyMaybeString :: (GObjectClass gobj, GlibString string) => String -> gobj -> Maybe string -> IO ()
- objectGetPropertyMaybeString :: (GObjectClass gobj, GlibString string) => String -> gobj -> IO (Maybe string)
- objectSetPropertyFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> string -> IO ()
- objectGetPropertyFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> IO string
- objectSetPropertyMaybeFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> Maybe string -> IO ()
- objectGetPropertyMaybeFilePath :: (GObjectClass gobj, GlibFilePath string) => 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
- readAttrFromUIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int
- writeAttrFromUIntProperty :: GObjectClass gobj => String -> WriteAttr gobj Int
- newAttrFromCharProperty :: GObjectClass gobj => String -> Attr gobj Char
- readAttrFromCharProperty :: GObjectClass gobj => String -> ReadAttr gobj Char
- newAttrFromBoolProperty :: GObjectClass gobj => String -> Attr gobj Bool
- readAttrFromBoolProperty :: GObjectClass gobj => String -> ReadAttr gobj Bool
- newAttrFromFloatProperty :: GObjectClass gobj => String -> Attr gobj Float
- readAttrFromFloatProperty :: GObjectClass gobj => String -> ReadAttr gobj Float
- newAttrFromDoubleProperty :: GObjectClass gobj => String -> Attr gobj Double
- readAttrFromDoubleProperty :: GObjectClass gobj => String -> ReadAttr 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]
- readAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> GType -> ReadAttr gobj [flag]
- newAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> Attr gobj string
- readAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> ReadAttr gobj string
- writeAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> WriteAttr gobj string
- newAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> Attr gobj (Maybe string)
- readAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> ReadAttr gobj (Maybe string)
- writeAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> WriteAttr gobj (Maybe string)
- newAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> Attr gobj string
- readAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> ReadAttr gobj string
- writeAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> WriteAttr gobj string
- newAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> Attr gobj (Maybe string)
- readAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> ReadAttr gobj (Maybe string)
- writeAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> WriteAttr gobj (Maybe string)
- newAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> Attr gobj boxed
- readAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> String -> GType -> ReadAttr 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
- readAttrFromBoxedStorableProperty :: (GObjectClass gobj, Storable boxed) => String -> GType -> ReadAttr gobj boxed
- newAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj gobj' gobj''
- readAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> ReadAttr gobj gobj'
- writeAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj gobj'
- newAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj (Maybe gobj') (Maybe gobj'')
- readAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> ReadAttr gobj (Maybe gobj')
- writeAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj (Maybe 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 () Source #
objectGetPropertyInt :: GObjectClass gobj => String -> gobj -> IO Int Source #
objectSetPropertyUInt :: GObjectClass gobj => String -> gobj -> Int -> IO () Source #
objectGetPropertyUInt :: GObjectClass gobj => String -> gobj -> IO Int Source #
objectSetPropertyInt64 :: GObjectClass gobj => String -> gobj -> Int64 -> IO () Source #
objectGetPropertyInt64 :: GObjectClass gobj => String -> gobj -> IO Int64 Source #
objectSetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> Word64 -> IO () Source #
objectGetPropertyUInt64 :: GObjectClass gobj => String -> gobj -> IO Word64 Source #
objectSetPropertyChar :: GObjectClass gobj => String -> gobj -> Char -> IO () Source #
objectGetPropertyChar :: GObjectClass gobj => String -> gobj -> IO Char Source #
objectSetPropertyBool :: GObjectClass gobj => String -> gobj -> Bool -> IO () Source #
objectGetPropertyBool :: GObjectClass gobj => String -> gobj -> IO Bool Source #
objectSetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> enum -> IO () Source #
objectGetPropertyEnum :: (GObjectClass gobj, Enum enum) => GType -> String -> gobj -> IO enum Source #
objectSetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> [flag] -> IO () Source #
objectGetPropertyFlags :: (GObjectClass gobj, Flags flag) => GType -> String -> gobj -> IO [flag] Source #
objectSetPropertyFloat :: GObjectClass gobj => String -> gobj -> Float -> IO () Source #
objectGetPropertyFloat :: GObjectClass gobj => String -> gobj -> IO Float Source #
objectSetPropertyDouble :: GObjectClass gobj => String -> gobj -> Double -> IO () Source #
objectGetPropertyDouble :: GObjectClass gobj => String -> gobj -> IO Double Source #
objectSetPropertyString :: (GObjectClass gobj, GlibString string) => String -> gobj -> string -> IO () Source #
objectGetPropertyString :: (GObjectClass gobj, GlibString string) => String -> gobj -> IO string Source #
objectSetPropertyMaybeString :: (GObjectClass gobj, GlibString string) => String -> gobj -> Maybe string -> IO () Source #
objectGetPropertyMaybeString :: (GObjectClass gobj, GlibString string) => String -> gobj -> IO (Maybe string) Source #
objectSetPropertyFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> string -> IO () Source #
objectGetPropertyFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> IO string Source #
objectSetPropertyMaybeFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> Maybe string -> IO () Source #
objectGetPropertyMaybeFilePath :: (GObjectClass gobj, GlibFilePath string) => String -> gobj -> IO (Maybe string) Source #
objectSetPropertyBoxedOpaque :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> GType -> String -> gobj -> boxed -> IO () Source #
objectGetPropertyBoxedOpaque :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> GType -> String -> gobj -> IO boxed Source #
objectSetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> boxed -> IO () Source #
objectGetPropertyBoxedStorable :: (GObjectClass gobj, Storable boxed) => GType -> String -> gobj -> IO boxed Source #
objectSetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> gobj' -> IO () Source #
objectGetPropertyGObject :: (GObjectClass gobj, GObjectClass gobj') => GType -> String -> gobj -> IO gobj' Source #
constructors for attributes backed by GObject properties
newAttrFromIntProperty :: GObjectClass gobj => String -> Attr gobj Int Source #
readAttrFromIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int Source #
newAttrFromUIntProperty :: GObjectClass gobj => String -> Attr gobj Int Source #
readAttrFromUIntProperty :: GObjectClass gobj => String -> ReadAttr gobj Int Source #
writeAttrFromUIntProperty :: GObjectClass gobj => String -> WriteAttr gobj Int Source #
newAttrFromCharProperty :: GObjectClass gobj => String -> Attr gobj Char Source #
readAttrFromCharProperty :: GObjectClass gobj => String -> ReadAttr gobj Char Source #
newAttrFromBoolProperty :: GObjectClass gobj => String -> Attr gobj Bool Source #
readAttrFromBoolProperty :: GObjectClass gobj => String -> ReadAttr gobj Bool Source #
newAttrFromFloatProperty :: GObjectClass gobj => String -> Attr gobj Float Source #
readAttrFromFloatProperty :: GObjectClass gobj => String -> ReadAttr gobj Float Source #
newAttrFromDoubleProperty :: GObjectClass gobj => String -> Attr gobj Double Source #
readAttrFromDoubleProperty :: GObjectClass gobj => String -> ReadAttr gobj Double Source #
newAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> Attr gobj enum Source #
readAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> ReadAttr gobj enum Source #
writeAttrFromEnumProperty :: (GObjectClass gobj, Enum enum) => String -> GType -> WriteAttr gobj enum Source #
newAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> GType -> Attr gobj [flag] Source #
readAttrFromFlagsProperty :: (GObjectClass gobj, Flags flag) => String -> GType -> ReadAttr gobj [flag] Source #
newAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> Attr gobj string Source #
readAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> ReadAttr gobj string Source #
writeAttrFromStringProperty :: (GObjectClass gobj, GlibString string) => String -> WriteAttr gobj string Source #
newAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> Attr gobj (Maybe string) Source #
readAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> ReadAttr gobj (Maybe string) Source #
writeAttrFromMaybeStringProperty :: (GObjectClass gobj, GlibString string) => String -> WriteAttr gobj (Maybe string) Source #
newAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> Attr gobj string Source #
readAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> ReadAttr gobj string Source #
writeAttrFromFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> WriteAttr gobj string Source #
newAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> Attr gobj (Maybe string) Source #
readAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> ReadAttr gobj (Maybe string) Source #
writeAttrFromMaybeFilePathProperty :: (GObjectClass gobj, GlibFilePath string) => String -> WriteAttr gobj (Maybe string) Source #
newAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> Attr gobj boxed Source #
readAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (Ptr boxed -> IO boxed) -> String -> GType -> ReadAttr gobj boxed Source #
writeAttrFromBoxedOpaqueProperty :: GObjectClass gobj => (boxed -> (Ptr boxed -> IO ()) -> IO ()) -> String -> GType -> WriteAttr gobj boxed Source #
newAttrFromBoxedStorableProperty :: (GObjectClass gobj, Storable boxed) => String -> GType -> Attr gobj boxed Source #
readAttrFromBoxedStorableProperty :: (GObjectClass gobj, Storable boxed) => String -> GType -> ReadAttr gobj boxed Source #
newAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj gobj' gobj'' Source #
readAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> ReadAttr gobj gobj' Source #
writeAttrFromObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj gobj' Source #
newAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj', GObjectClass gobj'') => String -> GType -> ReadWriteAttr gobj (Maybe gobj') (Maybe gobj'') Source #
readAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> ReadAttr gobj (Maybe gobj') Source #
writeAttrFromMaybeObjectProperty :: (GObjectClass gobj, GObjectClass gobj') => String -> GType -> WriteAttr gobj (Maybe gobj') Source #
objectGetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> IO a) -> String -> gobj -> IO a Source #
objectSetPropertyInternal :: GObjectClass gobj => GType -> (GValue -> a -> IO ()) -> String -> gobj -> a -> IO () Source #