Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class IsGVariant a where
- toGVariant :: a -> IO GVariant
- fromGVariant :: GVariant -> IO (Maybe a)
- toGVariantFormatString :: a -> Text
- class Ord a => IsGVariantBasicType a
- noGVariant :: Maybe GVariant
- gvariantGetTypeString :: GVariant -> IO Text
- newtype GVariantSinglet a = GVariantSinglet a
- data GVariantDictEntry key value = GVariantDictEntry key value
- newtype GVariantHandle = GVariantHandle Int32
- data GVariantObjectPath
- newGVariantObjectPath :: Text -> Maybe GVariantObjectPath
- gvariantObjectPathToText :: GVariantObjectPath -> Text
- data GVariantSignature
- newGVariantSignature :: Text -> Maybe GVariantSignature
- gvariantSignatureToText :: GVariantSignature -> Text
- wrapGVariantPtr :: Ptr GVariant -> IO GVariant
- newGVariantFromPtr :: Ptr GVariant -> IO GVariant
- unrefGVariant :: GVariant -> IO ()
- disownGVariant :: GVariant -> IO (Ptr GVariant)
- gvariantToBool :: GVariant -> IO (Maybe Bool)
- gvariantFromBool :: Bool -> IO GVariant
- gvariantToWord8 :: GVariant -> IO (Maybe Word8)
- gvariantFromWord8 :: Word8 -> IO GVariant
- gvariantToInt16 :: GVariant -> IO (Maybe Int16)
- gvariantFromInt16 :: Int16 -> IO GVariant
- gvariantToWord16 :: GVariant -> IO (Maybe Word16)
- gvariantFromWord16 :: Word16 -> IO GVariant
- gvariantToInt32 :: GVariant -> IO (Maybe Int32)
- gvariantFromInt32 :: Int32 -> IO GVariant
- gvariantToWord32 :: GVariant -> IO (Maybe Word32)
- gvariantFromWord32 :: Word32 -> IO GVariant
- gvariantToInt64 :: GVariant -> IO (Maybe Int64)
- gvariantFromInt64 :: Int64 -> IO GVariant
- gvariantToWord64 :: GVariant -> IO (Maybe Word64)
- gvariantFromWord64 :: Word64 -> IO GVariant
- gvariantToHandle :: GVariant -> IO (Maybe Int32)
- gvariantFromHandle :: Int32 -> IO GVariant
- gvariantToDouble :: GVariant -> IO (Maybe Double)
- gvariantFromDouble :: Double -> IO GVariant
- gvariantToText :: GVariant -> IO (Maybe Text)
- gvariantFromText :: Text -> IO GVariant
- gvariantToObjectPath :: GVariant -> IO (Maybe Text)
- gvariantFromObjectPath :: GVariantObjectPath -> IO GVariant
- gvariantToSignature :: GVariant -> IO (Maybe Text)
- gvariantFromSignature :: GVariantSignature -> IO GVariant
- gvariantToGVariant :: GVariant -> IO (Maybe GVariant)
- gvariantFromGVariant :: GVariant -> IO GVariant
- gvariantToBytestring :: GVariant -> IO (Maybe ByteString)
- gvariantFromBytestring :: ByteString -> IO GVariant
- gvariantFromMaybe :: forall a. IsGVariant a => Maybe a -> IO GVariant
- gvariantToMaybe :: forall a. IsGVariant a => GVariant -> IO (Maybe (Maybe a))
- gvariantFromDictEntry :: (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => key -> value -> IO GVariant
- gvariantToDictEntry :: forall key value. (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => GVariant -> IO (Maybe (key, value))
- gvariantFromMap :: (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => Map key value -> IO GVariant
- gvariantToMap :: forall key value. (IsGVariant key, IsGVariantBasicType key, IsGVariant value) => GVariant -> IO (Maybe (Map key value))
- gvariantFromList :: forall a. IsGVariant a => [a] -> IO GVariant
- gvariantToList :: forall a. IsGVariant a => GVariant -> IO (Maybe [a])
- gvariantFromTuple :: [GVariant] -> IO GVariant
- gvariantToTuple :: GVariant -> IO (Maybe [GVariant])
Documentation
class IsGVariant a where Source #
The typeclass for types that can be automatically marshalled into
GVariant
using toGVariant
and fromGVariant
.
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
class Ord a => IsGVariantBasicType a Source #
The typeclass for basic type GVariant
types, i.e. those that
are not containers.
Instances
IsGVariantBasicType Bool Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Double Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Int16 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Int32 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Int64 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Word8 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Word16 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Word32 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Word64 Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType Text Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType GVariantSignature Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType GVariantObjectPath Source # | |
Defined in Data.GI.Base.GVariant | |
IsGVariantBasicType GVariantHandle Source # | |
Defined in Data.GI.Base.GVariant |
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")
Instances
Eq a => Eq (GVariantSinglet a) Source # | |
Defined in Data.GI.Base.GVariant (==) :: GVariantSinglet a -> GVariantSinglet a -> Bool # (/=) :: GVariantSinglet a -> GVariantSinglet a -> Bool # | |
Show a => Show (GVariantSinglet a) Source # | |
Defined in Data.GI.Base.GVariant showsPrec :: Int -> GVariantSinglet a -> ShowS # show :: GVariantSinglet a -> String # showList :: [GVariantSinglet a] -> ShowS # | |
IsGVariant a => IsGVariant (GVariantSinglet a) Source # | One element tuples. |
Defined in Data.GI.Base.GVariant toGVariant :: GVariantSinglet a -> IO GVariant Source # fromGVariant :: GVariant -> IO (Maybe (GVariantSinglet a)) Source # toGVariantFormatString :: GVariantSinglet a -> Text Source # |
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.
GVariantDictEntry key value |
Instances
(Eq key, Eq value) => Eq (GVariantDictEntry key value) Source # | |
Defined in Data.GI.Base.GVariant (==) :: GVariantDictEntry key value -> GVariantDictEntry key value -> Bool # (/=) :: GVariantDictEntry key value -> GVariantDictEntry key value -> Bool # | |
(Show key, Show value) => Show (GVariantDictEntry key value) Source # | |
Defined in Data.GI.Base.GVariant showsPrec :: Int -> GVariantDictEntry key value -> ShowS # show :: GVariantDictEntry key value -> String # showList :: [GVariantDictEntry key value] -> ShowS # | |
(IsGVariant a, IsGVariantBasicType a, IsGVariant b) => IsGVariant (GVariantDictEntry a b) Source # | |
Defined in Data.GI.Base.GVariant toGVariant :: GVariantDictEntry a b -> IO GVariant Source # fromGVariant :: GVariant -> IO (Maybe (GVariantDictEntry a b)) Source # toGVariantFormatString :: GVariantDictEntry a b -> Text Source # |
newtype GVariantHandle Source #
Instances
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
.
Instances
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.
gvariantObjectPathToText :: GVariantObjectPath -> Text Source #
Return the Text
representation of a GVariantObjectPath
.
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
.
Instances
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.
gvariantSignatureToText :: GVariantSignature -> Text Source #
Return the Text
representation of a GVariantSignature
.
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.
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.
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
gvariantToBytestring :: GVariant -> IO (Maybe ByteString) Source #
Extract a zero terminated list of bytes into a ByteString
.
gvariantFromBytestring :: ByteString -> IO GVariant Source #
Encode a ByteString
into a list of bytes GVariant
.
gvariantFromMaybe :: forall a. IsGVariant a => Maybe a -> IO GVariant Source #
gvariantToMaybe :: forall a. IsGVariant a => GVariant -> IO (Maybe (Maybe a)) Source #
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.