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

Safe HaskellNone
LanguageHaskell2010

DBus.Types

Synopsis

Documentation

objectPath :: Text -> ObjectPath Source

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

data DBusSimpleType Source

Types that are not composite. These can be the keys of a Dict

Instances

Eq DBusSimpleType Source 
Data DBusSimpleType Source 
Read DBusSimpleType Source 
Show DBusSimpleType Source 
SingI DBusSimpleType TypeByte Source 
SingI DBusSimpleType TypeBoolean Source 
SingI DBusSimpleType TypeInt16 Source 
SingI DBusSimpleType TypeUInt16 Source 
SingI DBusSimpleType TypeInt32 Source 
SingI DBusSimpleType TypeUInt32 Source 
SingI DBusSimpleType TypeInt64 Source 
SingI DBusSimpleType TypeUInt64 Source 
SingI DBusSimpleType TypeDouble Source 
SingI DBusSimpleType TypeUnixFD Source 
SingI DBusSimpleType TypeString Source 
SingI DBusSimpleType TypeObjectPath Source 
SingI DBusSimpleType TypeSignature Source 
SEq DBusSimpleType (KProxy DBusSimpleType) Source 
PEq DBusSimpleType (KProxy DBusSimpleType) Source 
SDecide DBusSimpleType (KProxy DBusSimpleType) Source 
SingKind DBusSimpleType (KProxy DBusSimpleType) Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489534TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489524TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) Let1627489513TSym0 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489534TSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489524TSym1 Source 
data Sing DBusSimpleType where Source 
type (:/=) DBusSimpleType x y = Not ((:==) DBusSimpleType x y) 
type (:==) DBusSimpleType a0 b0 = Equals_1627483970 a0 b0 Source 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 Source 
type Apply DBusType DBusSimpleType Let1627489513TSym0 l0 = Let1627489513TSym1 l0 Source 
type DemoteRep DBusSimpleType (KProxy DBusSimpleType) = DBusSimpleType Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489534TSym0 l0 = Let1627489534TSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489524TSym0 l0 = Let1627489524TSym1 l0 Source 

data DBusType Source

Instances

Eq DBusType Source 
Data DBusType Source 
Read DBusType Source 
Show DBusType Source 
SingI DBusType TypeVariant Source 
SingI DBusType TypeUnit Source 
SEq DBusType (KProxy DBusType) Source 
PEq DBusType (KProxy DBusType) Source 
SDecide DBusType (KProxy DBusType) Source 
SingI DBusSimpleType n0 => SingI DBusType (DBusSimpleType n) Source 
SingI DBusType n0 => SingI DBusType (TypeArray n) Source 
SingI [DBusType] n0 => SingI DBusType (TypeStruct n) Source 
SingKind DBusType (KProxy DBusType) Source 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDict n n) Source 
(SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDictEntry n n) Source 
SuppressUnusedWarnings (TyFun [DBusType] DBusType -> *) TypeStructSym0 Source 
SuppressUnusedWarnings (TyFun DBusType [DBusType] -> *) FlattenRepTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusType DBusType -> *) TypeArraySym0 Source 
SuppressUnusedWarnings (TyFun DBusType DBusType -> *) Let1627489518TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictEntrySym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) TypeDictSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489534TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType (TyFun DBusType DBusType -> *) -> *) Let1627489524TSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) DBusSimpleTypeSym0 Source 
SuppressUnusedWarnings (TyFun DBusSimpleType DBusType -> *) Let1627489513TSym0 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictEntrySym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) TypeDictSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489534TSym1 Source 
SuppressUnusedWarnings (DBusSimpleType -> TyFun DBusType DBusType -> *) Let1627489524TSym1 Source 
data Sing DBusType where Source 
type (:/=) DBusType x y = Not ((:==) DBusType x y) 
type (:==) DBusType a0 b0 = Equals_1627483977 a0 b0 Source 
type Apply DBusType DBusType TypeArraySym0 l0 = TypeArraySym1 l0 Source 
type Apply DBusType DBusType Let1627489518TSym0 l0 = Let1627489518TSym1 l0 Source 
type Apply DBusType DBusSimpleType DBusSimpleTypeSym0 l0 = DBusSimpleTypeSym1 l0 Source 
type Apply DBusType DBusSimpleType Let1627489513TSym0 l0 = Let1627489513TSym1 l0 Source 
type Apply DBusType DBusType (TypeDictEntrySym1 l1) l0 = TypeDictEntrySym2 l1 l0 Source 
type Apply DBusType DBusType (TypeDictSym1 l1) l0 = TypeDictSym2 l1 l0 Source 
type Apply DBusType DBusType (Let1627489534TSym1 l1) l0 = Let1627489534TSym2 l1 l0 Source 
type Apply DBusType DBusType (Let1627489524TSym1 l1) l0 = Let1627489524TSym2 l1 l0 Source 
type DemoteRep DBusType (KProxy DBusType) = DBusType Source 
type Apply DBusType [DBusType] TypeStructSym0 l0 = TypeStructSym1 l0 Source 
type Apply [DBusType] DBusType FlattenRepTypeSym0 l0 = FlattenRepTypeSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictEntrySym0 l0 = TypeDictEntrySym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType TypeDictSym0 l0 = TypeDictSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489534TSym0 l0 = Let1627489534TSym1 l0 Source 
type Apply (TyFun DBusType DBusType -> *) DBusSimpleType Let1627489524TSym0 l0 = Let1627489524TSym1 l0 Source 

type SDBusType = (Sing :: DBusType -> *) Source

type ArgSym1 t = Arg t Source

data ArgSym0 l Source

Constructors

forall arg . (KindOf (Apply ArgSym0 arg) ~ KindOf (ArgSym1 arg)) => ArgSym0KindInference 

type SParity = (Sing :: Parity -> *) Source

type family Let1627489513T wild_1627489505 Source

Equations

Let1627489513T wild_1627489505 = Apply DBusSimpleTypeSym0 wild_1627489505 

type family Let1627489518T wild_1627489503 Source

Equations

Let1627489518T wild_1627489503 = Apply TypeArraySym0 wild_1627489503 

type family Let1627489524T wild_1627489499 wild_1627489501 Source

Equations

Let1627489524T wild_1627489499 wild_1627489501 = Apply (Apply TypeDictSym0 wild_1627489499) wild_1627489501 

type family Let1627489534T wild_1627489495 wild_1627489497 Source

Equations

Let1627489534T wild_1627489495 wild_1627489497 = Apply (Apply TypeDictEntrySym0 wild_1627489495) wild_1627489497 

type family FlattenRepType a :: [DBusType] Source

Equations

FlattenRepType TypeUnit = `[]` 
FlattenRepType (TypeStruct ts) = ts 
FlattenRepType (DBusSimpleType wild_1627489505) = Apply (Apply (:$) (Let1627489513TSym1 wild_1627489505)) `[]` 
FlattenRepType (TypeArray wild_1627489503) = Apply (Apply (:$) (Let1627489518TSym1 wild_1627489503)) `[]` 
FlattenRepType (TypeDict wild_1627489499 wild_1627489501) = Apply (Apply (:$) (Let1627489524TSym2 wild_1627489499 wild_1627489501)) `[]` 
FlattenRepType (TypeDictEntry wild_1627489495 wild_1627489497) = Apply (Apply (:$) (Let1627489534TSym2 wild_1627489495 wild_1627489497)) `[]` 
FlattenRepType TypeVariant = Apply (Apply (:$) Let1627489542TSym0) `[]` 

data SomeSignal where Source

Constructors

SomeSignal :: SingI a => Signal a -> SomeSignal 

type family ArgsOf x :: Parity Source

Equations

ArgsOf (IO x) = Null 
ArgsOf (MethodHandlerT IO x) = Null 
ArgsOf (a -> b) = Arg (ArgsOf b) 

type family ArgParity x :: Parity Source

Equations

ArgParity `[]` = Null 
ArgParity (x : xs) = Arg (ArgParity xs) 

data DBusStruct :: [DBusType] -> * where Source

Constructors

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

Instances

data SomeDBusStruct where Source

Constructors

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

data DBusValue :: DBusType -> * where Source

Instances

data SomeDBusValue where Source

Constructors

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

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

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

class SingI (RepType a) => Representable a where Source

Class of types that can be represented in the D-Bus type system.

The toRep and fromRep functions form a Prism and should follow the "obvious" laws:

  • fromRep (toRep x) == Just x
  • fmap toRep (fromRep x) =<= Just x

(where x =<= y iff x is Nothing or x == y)

All DBusValues represent themselves and instances for the following "canonical" pairs are provided

Haskell type => D-Bus type

  • WordX and IntX => UIntX and IntX respectively (for X in {16, 32, 64})
  • Bool => Boolean
  • Word8 => Byte
  • Double => Double
  • Text => String
  • ObjectPath => ObjectPath
  • DBusType => Signature
  • [a] => Array of a (for Representable a)
  • ByteString => Array of Byte
  • Tuples up to length 20 => Structs of equal length where each of the members is itself Representable
  • Map => Dict where the keys can be represented by a DBusSimpleType

An instance for String is impossible because it conflicts with the instance for lists (use Text instead)

Also note that no Representable instances are provided for Int, Integer and Float.

You can automatically derive an instance for your own Types with makeRepresentable

Associated Types

type RepType a :: DBusType Source

The DBusType that represents this type

Methods

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

Conversion from Haskell to D-Bus types

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

Conversion from D-Bus to Haskell types.

data MethodWrapper av rv where Source

Constructors

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

data Method where Source

Constructors

Method :: (SingI avs, SingI ts) => MethodWrapper avs ts -> Text -> ArgumentDescription (ArgParity avs) -> ArgumentDescription (ArgParity ts) -> Method 

data SomeProperty where Source

Constructors

SomeProperty :: forall t. SingI t => Property t -> SomeProperty 

newtype Object Source

Constructors

Object 

Instances

newtype Objects Source

Constructors

Objects 

Instances

data Match a Source

Constructors

Match a 
MatchAny 

Instances

Show a => Show (Match a) Source 

checkMatch :: Eq a => Match a -> Match a -> Bool Source

data SomeMethodDescription where Source

Constructors

SMD :: (SingI args, SingI rets) => MethodDescription args rets -> SomeMethodDescription