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

Safe HaskellNone

DBus.Types

Synopsis

Documentation

objectPath :: Text -> ObjectPathSource

Parse an object path. Contrary to the standard, empty path parts are ignored

data Parity Source

Constructors

Null 
Arg Parity 

Instances

Eq Parity 
Data Parity 
Show Parity 
Typeable Parity 
SingI Parity Null 
SingKind Parity (KProxy Parity) 
SingI Parity n0 => SingI Parity (Arg n0) 
SEq Parity (KProxy Parity) 

type family ArgsOf x :: ParitySource

type SDBusSimpleType z = Sing zSource

type SDBusType z = Sing zSource

type SParity z = Sing zSource

data DBusStruct whereSource

Constructors

StructSingleton :: DBusValue a -> DBusStruct `[a]` 
StructCons :: DBusValue a -> DBusStruct as -> DBusStruct (a : as) 

Instances

Eq (DBusStruct t) 
SingI [DBusType] a => Show (DBusStruct a) 

data SomeDBusStruct whereSource

Constructors

SDBS :: SingI ts => DBusStruct ts -> SomeDBusStruct 

castDBV :: (SingI s, SingI t) => DBusValue s -> Maybe (DBusValue t)Source

data SomeDBusValue whereSource

Constructors

DBV :: SingI t => DBusValue t -> SomeDBusValue 

Instances

fromVariant :: SingI t => DBusValue TypeVariant -> Maybe (DBusValue t)Source

Extract a DBusValue from a Variant iff the type matches or return nothing

typeOf :: SingI t => DBusValue t -> DBusTypeSource

class Representable a whereSource

Associated Types

type RepType a :: DBusTypeSource

Instances

Representable Bool 
Representable Double 
Representable Int16 
Representable Int32 
Representable Int64 
Representable Word8 
Representable Word16 
Representable Word32 
Representable Word64 
Representable () 
Representable ByteString 
Representable Text 
Representable Signature 
Representable ObjectPath 
Representable Endian 
Representable HeaderField 
Representable HeaderFields 
Representable Flags 
Representable MessageType 
Representable MessageHeader 
(Representable a, SingI DBusType (RepType a)) => Representable [a] 
(Representable l, Representable r, SingI DBusType (RepType l), SingI DBusType (RepType r)) => Representable (Either l r) 
(Representable a, Representable b) => Representable (a, b) 
(Ord k, Representable k, ~ DBusType (RepType k) (DBusSimpleType r), Representable v) => Representable (Map k v) 
(Representable a, Representable b, Representable c) => Representable (a, b, c) 
(Representable a, Representable b, Representable c, Representable d) => Representable (a, b, c, d) 
(Representable a, Representable b, Representable c, Representable d, Representable e) => Representable (a, b, c, d, e) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f) => Representable (a, b, c, d, e, f) 
(Representable a, Representable b, Representable c, Representable d, Representable e, Representable f, Representable g) => Representable (a, b, c, d, e, f, g) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 

data MethodWrapper av rv whereSource

Constructors

MReturn :: SingI t => IO (DBusValue t) -> MethodWrapper `[]` t 
MAsk :: SingI t => (DBusValue t -> MethodWrapper avs rv) -> MethodWrapper (t : avs) rv 

type family ArgParity x :: ParitySource

data Method whereSource

Constructors

Method :: (SingI avs, SingI t) => MethodWrapper avs t -> Text -> MethodDescription (ArgParity avs) -> Method 

Instances