haskell-gi-base-0.26.3: Foundation for libraries generated by haskell-gi
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.GI.Base.GVariant

Description

This module contains some helper functions for dealing with GVariant values. The simplest way of dealing with them is by using the IsGVariant typeclass:

str <- fromGVariant variant :: IO (Maybe Text)

assuming that the variant is expected to contain a string in UTF8 encoding. The code becomes even shorter if the type checker can determine the return type for you:

readStringVariant :: GVariant -> IO Text
readStringVariant variant =
  fromGVariant variant >>= \case
     Nothing  -> error "Variant was not a string"
     Just str -> return str

Alternatively, you can use manually the gvariantFrom* and gvariantTo* family of functions.

Synopsis

Documentation

class IsGVariant a where Source #

The typeclass for types that can be automatically marshalled into GVariant using toGVariant and fromGVariant.

Methods

toGVariant :: a -> IO GVariant Source #

Convert a value of the given type into a GVariant.

fromGVariant :: GVariant -> IO (Maybe a) Source #

Try to decode a GVariant into a target type. If the conversion fails we return Nothing. The type that was expected can be obtained by calling toGVariantFormatString, and the actual type as understood by the GVariant code can be obtained by calling gvariantToTypeString.

toGVariantFormatString :: a -> Text Source #

The expected format string for this type (the argument is ignored).

Instances

Instances details
IsGVariant Int16 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Int32 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Int64 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Word16 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Word32 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Word64 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Word8 Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant ByteString Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant GVariant Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant GVariantHandle Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant GVariantObjectPath Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant GVariantSignature Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Text Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant () Source #

The empty tuple GVariant, mostly useful for type checking.

Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Bool Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant Double Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant a => IsGVariant (GVariantSinglet a) Source #

One element tuples.

Instance details

Defined in Data.GI.Base.GVariant

IsGVariant a => IsGVariant (Maybe a) Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant a => IsGVariant [a] Source # 
Instance details

Defined in Data.GI.Base.GVariant

(IsGVariant a, IsGVariantBasicType a, IsGVariant b) => IsGVariant (Map a b) Source # 
Instance details

Defined in Data.GI.Base.GVariant

(IsGVariant a, IsGVariantBasicType a, IsGVariant b) => IsGVariant (GVariantDictEntry a b) Source # 
Instance details

Defined in Data.GI.Base.GVariant

(IsGVariant a, IsGVariant b) => IsGVariant (a, b) Source # 
Instance details

Defined in Data.GI.Base.GVariant

(IsGVariant a, IsGVariant b, IsGVariant c) => IsGVariant (a, b, c) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Methods

toGVariant :: (a, b, c) -> IO GVariant Source #

fromGVariant :: GVariant -> IO (Maybe (a, b, c)) Source #

toGVariantFormatString :: (a, b, c) -> Text Source #

(IsGVariant a, IsGVariant b, IsGVariant c, IsGVariant d) => IsGVariant (a, b, c, d) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Methods

toGVariant :: (a, b, c, d) -> IO GVariant Source #

fromGVariant :: GVariant -> IO (Maybe (a, b, c, d)) Source #

toGVariantFormatString :: (a, b, c, d) -> Text Source #

(IsGVariant a, IsGVariant b, IsGVariant c, IsGVariant d, IsGVariant e) => IsGVariant (a, b, c, d, e) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Methods

toGVariant :: (a, b, c, d, e) -> IO GVariant Source #

fromGVariant :: GVariant -> IO (Maybe (a, b, c, d, e)) Source #

toGVariantFormatString :: (a, b, c, d, e) -> Text Source #

class Ord a => IsGVariantBasicType a Source #

The typeclass for basic type GVariant types, i.e. those that are not containers.

noGVariant :: Maybe GVariant Source #

An alias for Nothing :: Maybe GVariant to save some typing.

gvariantGetTypeString :: GVariant -> IO Text Source #

Get the expected type of a GVariant, in GVariant notation. See https://developer.gnome.org/glib/stable/glib-GVariantType.html for the meaning of the resulting format string.

Type wrappers

Some GVariant types are isomorphic to Haskell types, but they carry some extra information. For example, there is a tuple singlet type, which is isomorphic to a single Haskell value with the added bit of information that it is wrapped in a tuple container. In order to use these values you can use the following wrappers, which allow the IsGVariant instance to disambiguate the requested type properly.

newtype GVariantSinglet a Source #

Haskell has no notion of one element tuples, but GVariants do, so the following allows for marshalling one element tuples properly using fromGVariant and toGVariant. For instance, to construct a single element tuple containing a string, you could do

toGVariant (GVariantSinglet "Test")

Constructors

GVariantSinglet a 

Instances

Instances details
Show a => Show (GVariantSinglet a) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Eq a => Eq (GVariantSinglet a) Source # 
Instance details

Defined in Data.GI.Base.GVariant

IsGVariant a => IsGVariant (GVariantSinglet a) Source #

One element tuples.

Instance details

Defined in Data.GI.Base.GVariant

data GVariantDictEntry key value Source #

A DictEntry GVariant is isomorphic to a two-tuple. Wrapping the values into a GVariantDictentry allows the IsGVariant instance to do the right thing.

Constructors

GVariantDictEntry key value 

Instances

Instances details
(Show key, Show value) => Show (GVariantDictEntry key value) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Methods

showsPrec :: Int -> GVariantDictEntry key value -> ShowS #

show :: GVariantDictEntry key value -> String #

showList :: [GVariantDictEntry key value] -> ShowS #

(Eq key, Eq value) => Eq (GVariantDictEntry key value) Source # 
Instance details

Defined in Data.GI.Base.GVariant

Methods

(==) :: GVariantDictEntry key value -> GVariantDictEntry key value -> Bool #

(/=) :: GVariantDictEntry key value -> GVariantDictEntry key value -> Bool #

(IsGVariant a, IsGVariantBasicType a, IsGVariant b) => IsGVariant (GVariantDictEntry a b) Source # 
Instance details

Defined in Data.GI.Base.GVariant

data GVariantObjectPath Source #

An object representing a DBus object path, which is a particular type of GVariant too. (Just a string with some specific requirements.) In order to construct/deconstruct a GVariantObjectPath one can use newGVariantObjectPath and gvariantObjectPathToText.

newGVariantObjectPath :: Text -> Maybe GVariantObjectPath Source #

Try to construct a DBus object path. If the passed string is not a valid object path Nothing will be returned.

data GVariantSignature Source #

An object representing a DBus signature, which is a particular type of GVariant too. (Just a string with some specific requirements.) In order to construct/deconstruct a GVariantSignature one can use newGVariantSignature and gvariantSignatureToText.

newGVariantSignature :: Text -> Maybe GVariantSignature Source #

Try to construct a DBus object path. If the passed string is not a valid DBus signature Nothing will be returned.

Manual memory management

wrapGVariantPtr :: Ptr GVariant -> IO GVariant Source #

Take ownership of a passed in Ptr (typically created just for us, so if it is floating we sink it).

newGVariantFromPtr :: Ptr GVariant -> IO GVariant Source #

Construct a Haskell wrapper for the given GVariant, without assuming ownership.

unrefGVariant :: GVariant -> IO () Source #

Remove a reference to the given GVariant.

disownGVariant :: GVariant -> IO (Ptr GVariant) Source #

Disown a GVariant, i.e. do not unref the underlying object when the Haskell object is garbage collected.

Manual conversions

Basic types

The use of these should be fairly self-explanatory. If you want to convert a Haskell type into a GVariant, use gvariantTo*. If you want to convert a GVariant into a Haskell type, use gvariantFrom*. The conversion can fail if the GVariant is not of the expected type (if you want to convert a GVariant containing a Int16 into a Text value, say), in which case Nothing will be returned.

gvariantToHandle :: GVariant -> IO (Maybe Int32) Source #

Extract the DBus handle (an Int32) inside a GVariant.

gvariantFromHandle :: Int32 -> IO GVariant Source #

Convert a DBus handle (an Int32) into a GVariant.

gvariantToText :: GVariant -> IO (Maybe Text) Source #

Decode an UTF-8 encoded string GVariant into Text.

gvariantFromText :: Text -> IO GVariant Source #

Encode a Text into an UTF-8 encoded string GVariant.

gvariantToObjectPath :: GVariant -> IO (Maybe Text) Source #

Extract a GVariantObjectPath from a GVariant, represented as its underlying Text representation.

gvariantFromObjectPath :: GVariantObjectPath -> IO GVariant Source #

Construct a GVariant containing an object path. In order to build a GVariantObjectPath value see newGVariantObjectPath.

gvariantToSignature :: GVariant -> IO (Maybe Text) Source #

Extract a GVariantSignature from a GVariant, represented as Text.

gvariantFromSignature :: GVariantSignature -> IO GVariant Source #

Construct a GVariant containing an DBus signature. In order to build a GVariantSignature value see newGVariantSignature.

Container type conversions

gvariantToGVariant :: GVariant -> IO (Maybe GVariant) Source #

Unbox a GVariant contained inside another GVariant.

gvariantToBytestring :: GVariant -> IO (Maybe ByteString) Source #

Extract a zero terminated list of bytes into a ByteString.

gvariantFromMaybe :: forall a. IsGVariant a => Maybe a -> IO GVariant Source #

Convert a Maybe value into a corresponding GVariant of maybe type.

gvariantToMaybe :: forall a. IsGVariant a => GVariant -> IO (Maybe (Maybe a)) Source #

Try to decode a maybe GVariant into the corresponding Maybe type. If the conversion is successful this returns Just x, where x itself is of Maybe type. So, in particular, Just Nothing indicates a successful call, and means that the GVariant of maybe type was empty.

gvariantFromDictEntry :: (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => key -> value -> IO GVariant Source #

Construct a GVariant of type DictEntry from the given key and value. The key must be a basic GVariant type, i.e. not a container. This is determined by whether it belongs to the IsGVariantBasicType typeclass. On the other hand value is an arbitrary GVariant, and in particular it can be a container type.

gvariantToDictEntry :: forall key value. (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => GVariant -> IO (Maybe (key, value)) Source #

Unpack a DictEntry variant into key and value, which are returned as a two element tuple in case of success.

gvariantFromMap :: (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => Map key value -> IO GVariant Source #

Pack a Map into a GVariant for dictionary type, which is just an array of GVariantDictEntry.

gvariantToMap :: forall key value. (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => GVariant -> IO (Maybe (Map key value)) Source #

Unpack a GVariant into a Map. Notice that this assumes that all the elements in the GVariant array of GVariantDictEntry are of the same type, which is not necessary for a generic GVariant, so this is somewhat restrictive. For the general case it is necessary to use gvariantToList plus gvariantToDictEntry directly.

gvariantFromList :: forall a. IsGVariant a => [a] -> IO GVariant Source #

Given a list of elements construct a GVariant array containing them.

gvariantToList :: forall a. IsGVariant a => GVariant -> IO (Maybe [a]) Source #

Unpack a GVariant array into its elements.

gvariantFromTuple :: [GVariant] -> IO GVariant Source #

Given a list of GVariant, construct a GVariant tuple containing the elements in the list.

gvariantToTuple :: GVariant -> IO (Maybe [GVariant]) Source #

Extract the children of a GVariant tuple into a list.