| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.GI.Base.GValue
Synopsis
- newtype GValue = GValue (ManagedPtr GValue)
 - class IsGValue a where
 - data GValueConstruct o = GValueConstruct String GValue
 - newGValue :: GType -> IO GValue
 - buildGValue :: GType -> (GValue -> a -> IO ()) -> a -> IO GValue
 - noGValue :: Maybe GValue
 - set_string :: GValue -> Maybe Text -> IO ()
 - get_string :: GValue -> IO (Maybe Text)
 - set_pointer :: GValue -> Ptr a -> IO ()
 - get_pointer :: GValue -> IO (Ptr b)
 - set_int :: GValue -> CInt -> IO ()
 - get_int :: GValue -> IO CInt
 - set_uint :: GValue -> CUInt -> IO ()
 - get_uint :: GValue -> IO CUInt
 - set_long :: GValue -> CLong -> IO ()
 - get_long :: GValue -> IO CLong
 - set_ulong :: GValue -> CULong -> IO ()
 - get_ulong :: GValue -> IO CULong
 - set_int32 :: GValue -> Int32 -> IO ()
 - get_int32 :: GValue -> IO Int32
 - set_uint32 :: GValue -> Word32 -> IO ()
 - get_uint32 :: GValue -> IO Word32
 - set_int64 :: GValue -> Int64 -> IO ()
 - get_int64 :: GValue -> IO Int64
 - set_uint64 :: GValue -> Word64 -> IO ()
 - get_uint64 :: GValue -> IO Word64
 - set_float :: GValue -> Float -> IO ()
 - get_float :: GValue -> IO Float
 - set_double :: GValue -> Double -> IO ()
 - get_double :: GValue -> IO Double
 - set_boolean :: GValue -> Bool -> IO ()
 - get_boolean :: GValue -> IO Bool
 - set_gtype :: GValue -> GType -> IO ()
 - get_gtype :: GValue -> IO GType
 - set_object :: GObject a => GValue -> Ptr a -> IO ()
 - get_object :: GObject b => GValue -> IO (Ptr b)
 - set_boxed :: GValue -> Ptr a -> IO ()
 - get_boxed :: GValue -> IO (Ptr b)
 - set_variant :: GValue -> Ptr GVariant -> IO ()
 - get_variant :: GValue -> IO (Ptr GVariant)
 - set_enum :: GValue -> CUInt -> IO ()
 - get_enum :: GValue -> IO CUInt
 - set_flags :: GValue -> CUInt -> IO ()
 - get_flags :: GValue -> IO CUInt
 - set_stablePtr :: GValue -> StablePtr a -> IO ()
 - get_stablePtr :: GValue -> IO (StablePtr a)
 - take_stablePtr :: Ptr GValue -> StablePtr a -> IO ()
 
Constructing GValues
Haskell-side representation of a GValue.
Constructors
| GValue (ManagedPtr GValue) | 
class IsGValue a where Source #
A convenience class for marshaling back and forth between Haskell
 values and GValues.
Instances
data GValueConstruct o Source #
A type holding a GValue with an associated label. It is
 parameterized by a phantom type encoding the target type for the
 GValue (useful when constructing properties).
Constructors
| GValueConstruct String GValue | 
buildGValue :: GType -> (GValue -> a -> IO ()) -> a -> IO GValue Source #
A convenience function for building a new GValue and setting the initial value.
Setters and getters
take_stablePtr :: Ptr GValue -> StablePtr a -> IO () Source #
Like set_stablePtr, but the GValue takes ownership of the StablePtr