d-bus-0.1.8: Permissively licensed D-Bus client library

Safe HaskellNone
LanguageHaskell2010

DBus.Representable

Contents

Documentation

type family FromSimpleType (t :: DBusType) :: DBusSimpleType where ... Source #

Equations

FromSimpleType (DBusSimpleType k) = k 

Orphan instances

Representable Bool Source # 
Representable Double Source # 
Representable Int16 Source # 
Representable Int32 Source # 
Representable Int64 Source # 
Representable Word8 Source # 
Representable Word16 Source # 
Representable Word32 Source # 
Representable Word64 Source # 
Representable () Source # 

Associated Types

type RepType () :: DBusType Source #

Methods

toRep :: () -> DBusValue (RepType ()) Source #

fromRep :: DBusValue (RepType ()) -> Maybe () Source #

Representable ByteString Source # 
Representable Text Source # 
Representable ObjectPath Source # 
(Representable a, SingI DBusType (RepType a)) => Representable [a] Source # 

Associated Types

type RepType [a] :: DBusType Source #

Methods

toRep :: [a] -> DBusValue (RepType [a]) Source #

fromRep :: DBusValue (RepType [a]) -> Maybe [a] Source #

SingI DBusType t => Representable (DBusValue t) Source # 
(Representable a, Representable b) => Representable (a, b) Source # 

Associated Types

type RepType (a, b) :: DBusType Source #

Methods

toRep :: (a, b) -> DBusValue (RepType (a, b)) Source #

fromRep :: DBusValue (RepType (a, b)) -> Maybe (a, b) Source #

(Ord k, Representable k, (~) DBusType (RepType k) (DBusSimpleType r), SingI DBusSimpleType r, Representable v) => Representable (Map k v) Source # 

Associated Types

type RepType (Map k v) :: DBusType Source #

Methods

toRep :: Map k v -> DBusValue (RepType (Map k v)) Source #

fromRep :: DBusValue (RepType (Map k v)) -> Maybe (Map k v) Source #

(Representable a, Representable b, Representable c) => Representable (a, b, c) Source # 

Associated Types

type RepType (a, b, c) :: DBusType Source #

Methods

toRep :: (a, b, c) -> DBusValue (RepType (a, b, c)) Source #

fromRep :: DBusValue (RepType (a, b, c)) -> Maybe (a, b, c) Source #

(Representable a, Representable b, Representable c, Representable d) => Representable (a, b, c, d) Source # 

Associated Types

type RepType (a, b, c, d) :: DBusType Source #

Methods

toRep :: (a, b, c, d) -> DBusValue (RepType (a, b, c, d)) Source #

fromRep :: DBusValue (RepType (a, b, c, d)) -> Maybe (a, b, c, d) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e) => Representable (a, b, c, d, e) Source # 

Associated Types

type RepType (a, b, c, d, e) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e) -> DBusValue (RepType (a, b, c, d, e)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e)) -> Maybe (a, b, c, d, e) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f) => Representable (a, b, c, d, e, f) Source # 

Associated Types

type RepType (a, b, c, d, e, f) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f) -> DBusValue (RepType (a, b, c, d, e, f)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f)) -> Maybe (a, b, c, d, e, f) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g) => Representable (a, b, c, d, e, f, g) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g) -> DBusValue (RepType (a, b, c, d, e, f, g)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g)) -> Maybe (a, b, c, d, e, f, g) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h) => Representable (a, b, c, d, e, f, g, h) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h) -> DBusValue (RepType (a, b, c, d, e, f, g, h)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h)) -> Maybe (a, b, c, d, e, f, g, h) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i) => Representable (a, b, c, d, e, f, g, h, i) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i)) -> Maybe (a, b, c, d, e, f, g, h, i) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j) => Representable (a, b, c, d, e, f, g, h, i, j) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j)) -> Maybe (a, b, c, d, e, f, g, h, i, j) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k) => Representable (a, b, c, d, e, f, g, h, i, j, k) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l) => Representable (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r, Representable s) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g, Representable h, Representable i, Representable j, Representable k, Representable l, Representable m, Representable n, Representable o, Representable p, Representable q, Representable r, Representable s, Representable t) => Representable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 

Associated Types

type RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) :: DBusType Source #

Methods

toRep :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) Source #

fromRep :: DBusValue (RepType (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) -> Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #