| Safe Haskell | None |
|---|
DBus.Types
- data ObjectPath = ObjectPath {
- opAbsolute :: Bool
- opParts :: [Text]
- newtype Signature = Signature {
- fromSignature :: [DBusType]
- objectPath :: Text -> ObjectPath
- objectPathToText :: ObjectPath -> Text
- stripObjectPrefix :: ObjectPath -> ObjectPath -> Maybe ObjectPath
- isPathPrefix :: ObjectPath -> ObjectPath -> Bool
- isRoot :: ObjectPath -> Bool
- isEmpty :: ObjectPath -> Bool
- data DBusSimpleType
- = TypeByte
- | TypeBoolean
- | TypeInt16
- | TypeUInt16
- | TypeInt32
- | TypeUInt32
- | TypeInt64
- | TypeUInt64
- | TypeDouble
- | TypeUnixFD
- | TypeString
- | TypeObjectPath
- | TypeSignature
- ppSimpleType :: DBusSimpleType -> String
- data DBusType
- ppType :: DBusType -> String
- data Parity
- type family ArgsOf x :: Parity
- data MethodDescription parity where
- :-> :: Text -> MethodDescription n -> MethodDescription (Arg n)
- Result :: Text -> MethodDescription Null
- type SDBusSimpleType z = Sing z
- type SDBusType z = Sing z
- type SParity z = Sing z
- data DBusStruct where
- StructSingleton :: DBusValue a -> DBusStruct `[a]`
- StructCons :: DBusValue a -> DBusStruct as -> DBusStruct (a : as)
- data SomeDBusStruct where
- SDBS :: SingI ts => DBusStruct ts -> SomeDBusStruct
- showStruct :: Sing a -> DBusStruct a -> String
- data DBusValue where
- DBVByte :: Word8 -> DBusValue (DBusSimpleType TypeByte)
- DBVBool :: Bool -> DBusValue (DBusSimpleType TypeBoolean)
- DBVInt16 :: Int16 -> DBusValue (DBusSimpleType TypeInt16)
- DBVUInt16 :: Word16 -> DBusValue (DBusSimpleType TypeUInt16)
- DBVInt32 :: Int32 -> DBusValue (DBusSimpleType TypeInt32)
- DBVUInt32 :: Word32 -> DBusValue (DBusSimpleType TypeUInt32)
- DBVInt64 :: Int64 -> DBusValue (DBusSimpleType TypeInt64)
- DBVUInt64 :: Word64 -> DBusValue (DBusSimpleType TypeUInt64)
- DBVDouble :: Double -> DBusValue (DBusSimpleType TypeDouble)
- DBVUnixFD :: Word32 -> DBusValue (DBusSimpleType TypeUnixFD)
- DBVString :: Text -> DBusValue (DBusSimpleType TypeString)
- DBVObjectPath :: ObjectPath -> DBusValue (DBusSimpleType TypeObjectPath)
- DBVSignature :: [DBusType] -> DBusValue (DBusSimpleType TypeSignature)
- DBVVariant :: SingI t => DBusValue t -> DBusValue TypeVariant
- DBVArray :: [DBusValue a] -> DBusValue (TypeArray a)
- DBVByteArray :: ByteString -> DBusValue (TypeArray (DBusSimpleType TypeByte))
- DBVStruct :: DBusStruct ts -> DBusValue (TypeStruct ts)
- DBVDict :: [(DBusValue (DBusSimpleType k), DBusValue v)] -> DBusValue (TypeDict k v)
- DBVUnit :: DBusValue TypeUnit
- castDBV :: (SingI s, SingI t) => DBusValue s -> Maybe (DBusValue t)
- data SomeDBusValue where
- DBV :: SingI t => DBusValue t -> SomeDBusValue
- dbusValue :: SingI t => SomeDBusValue -> Maybe (DBusValue t)
- dbusSValue :: SingI t => SomeDBusValue -> Maybe (DBusValue (DBusSimpleType t))
- fromVariant :: SingI t => DBusValue TypeVariant -> Maybe (DBusValue t)
- typeOf :: SingI t => DBusValue t -> DBusType
- class Representable a where
- data MethodWrapper av rv where
- MReturn :: SingI t => IO (DBusValue t) -> MethodWrapper `[]` t
- MAsk :: SingI t => (DBusValue t -> MethodWrapper avs rv) -> MethodWrapper (t : avs) rv
- type family ArgParity x :: Parity
- data Method where
- Method :: (SingI avs, SingI t) => MethodWrapper avs t -> Text -> MethodDescription (ArgParity avs) -> Method
- data Annotation = Annotation {}
- data Interface = Interface {}
- data Object = Object {}
- data MsgError = MsgError {}
- data Connection = Connection {
- primConnection :: ()
- answerSlots :: TVar (Map Word32 (TMVar (Either MsgError SomeDBusValue)))
- mainLoop :: ThreadId
- data MethodError
- type Serial = Word32
- type Slot = Either [SomeDBusValue] SomeDBusValue -> STM ()
- type AnswerSlots = Map Serial Slot
- data DBusConnection = DBusConnection {
- dBusCreateSerial :: STM Serial
- dBusAnswerSlots :: TVar AnswerSlots
- dBusWriteLock :: TMVar (Builder -> IO ())
- dBusConnectionName :: Text
- connectionAliveRef :: TVar Bool
Documentation
data ObjectPath Source
Constructors
| ObjectPath | |
Fields
| |
Constructors
| Signature | |
Fields
| |
objectPath :: Text -> ObjectPathSource
Parse an object path. Contrary to the standard, empty path parts are ignored
isPathPrefix :: ObjectPath -> ObjectPath -> BoolSource
isRoot :: ObjectPath -> BoolSource
isEmpty :: ObjectPath -> BoolSource
data DBusSimpleType Source
Constructors
| TypeByte | |
| TypeBoolean | |
| TypeInt16 | |
| TypeUInt16 | |
| TypeInt32 | |
| TypeUInt32 | |
| TypeInt64 | |
| TypeUInt64 | |
| TypeDouble | |
| TypeUnixFD | |
| TypeString | |
| TypeObjectPath | |
| TypeSignature |
Instances
| Eq DBusSimpleType | |
| Data DBusSimpleType | |
| Read DBusSimpleType | |
| Show DBusSimpleType | |
| Typeable DBusSimpleType | |
| SingI DBusSimpleType TypeSignature | |
| SingI DBusSimpleType TypeObjectPath | |
| SingI DBusSimpleType TypeString | |
| SingI DBusSimpleType TypeUnixFD | |
| SingI DBusSimpleType TypeDouble | |
| SingI DBusSimpleType TypeUInt64 | |
| SingI DBusSimpleType TypeInt64 | |
| SingI DBusSimpleType TypeUInt32 | |
| SingI DBusSimpleType TypeInt32 | |
| SingI DBusSimpleType TypeUInt16 | |
| SingI DBusSimpleType TypeInt16 | |
| SingI DBusSimpleType TypeBoolean | |
| SingI DBusSimpleType TypeByte | |
| SingKind DBusSimpleType (KProxy DBusSimpleType) | |
| SEq DBusSimpleType (KProxy DBusSimpleType) |
Constructors
| DBusSimpleType DBusSimpleType | |
| TypeArray DBusType | |
| TypeStruct [DBusType] | |
| TypeDict DBusSimpleType DBusType | |
| TypeVariant | |
| TypeDictEntry DBusSimpleType DBusType | |
| TypeUnit |
Instances
| Eq DBusType | |
| Data DBusType | |
| Read DBusType | |
| Show DBusType | |
| Typeable DBusType | |
| SingI DBusType TypeUnit | |
| SingI DBusType TypeVariant | |
| SingKind DBusType (KProxy DBusType) | |
| SingI [DBusType] n0 => SingI DBusType (TypeStruct n0) | |
| SingI DBusType n0 => SingI DBusType (TypeArray n0) | |
| SingI DBusSimpleType n0 => SingI DBusType (DBusSimpleType n0) | |
| SEq DBusType (KProxy DBusType) | |
| (SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDictEntry n0 n1) | |
| (SingI DBusSimpleType n0, SingI DBusType n1) => SingI DBusType (TypeDict n0 n1) |
data MethodDescription parity whereSource
Constructors
| :-> :: Text -> MethodDescription n -> MethodDescription (Arg n) | |
| Result :: Text -> MethodDescription Null |
type SDBusSimpleType 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 |
showStruct :: Sing a -> DBusStruct a -> StringSource
Constructors
dbusValue :: SingI t => SomeDBusValue -> Maybe (DBusValue t)Source
dbusSValue :: SingI t => SomeDBusValue -> Maybe (DBusValue (DBusSimpleType t))Source
fromVariant :: SingI t => DBusValue TypeVariant -> Maybe (DBusValue t)Source
Extract a DBusValue from a Variant iff the type matches or return nothing
class Representable a whereSource
Instances
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 |
Constructors
| Method :: (SingI avs, SingI t) => MethodWrapper avs t -> Text -> MethodDescription (ArgParity avs) -> Method |
Constructors
| Interface | |
Fields
| |
Constructors
| Object | |
Fields | |
data Connection Source
Constructors
| Connection | |
Fields
| |
data MethodError Source
Constructors
| MethodErrorMessage [SomeDBusValue] | |
| MethodSignatureMissmatch SomeDBusValue |
Instances
type Slot = Either [SomeDBusValue] SomeDBusValue -> STM ()Source
type AnswerSlots = Map Serial SlotSource
data DBusConnection Source
Constructors
| DBusConnection | |
Fields
| |