| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DBus.Internal.Types
Synopsis
- data Type
- showType :: Bool -> Type -> String
- newtype Signature = Signature [Type]
- signatureTypes :: Signature -> [Type]
- formatSignature :: Signature -> String
- typeCode :: Type -> String
- signature :: MonadThrow m => [Type] -> m Signature
- signature_ :: [Type] -> Signature
- parseSignature :: MonadThrow m => String -> m Signature
- parseSignatureBytes :: MonadThrow m => ByteString -> m Signature
- parseSigFast :: MonadThrow m => ByteString -> m Signature
- parseAtom :: Int -> (Type -> a) -> a -> a
- data SigParseError = SigParseError
- peekWord8AsInt :: ByteString -> Int -> Int
- parseSigFull :: MonadThrow m => ByteString -> m Signature
- extractFromVariant :: IsValue a => Variant -> Maybe a
- typeOf :: IsValue a => a -> Type
- class IsVariant a where
- toVariant :: a -> Variant
- fromVariant :: Variant -> Maybe a
- class IsVariant a => IsValue a where
- class IsValue a => IsAtom a where
- newtype Variant = Variant Value
- data Value
- = ValueAtom Atom
- | ValueVariant Variant
- | ValueBytes ByteString
- | ValueVector Type (Vector Value)
- | ValueMap Type Type (Map Atom Value)
- | ValueStructure [Value]
- data Atom
- showAtom :: Bool -> Atom -> String
- showValue :: Bool -> Value -> String
- showThings :: String -> (a -> String) -> String -> [a] -> String
- vectorToBytes :: Vector Value -> ByteString
- variantType :: Variant -> Type
- valueType :: Value -> Type
- atomType :: Atom -> Type
- bimap :: Ord k' => (k -> v -> (k', v')) -> Map k v -> Map k' v'
- bimapM :: (Monad m, Ord k') => (k -> v -> m (k', v')) -> Map k v -> m (Map k' v')
- varToVal :: IsVariant a => a -> Value
- newtype ObjectPath = ObjectPath String
- pathElements :: ObjectPath -> [String]
- fromElements :: [String] -> ObjectPath
- formatObjectPath :: ObjectPath -> String
- parseObjectPath :: MonadThrow m => String -> m ObjectPath
- objectPath_ :: String -> ObjectPath
- parserObjectPath :: Parser ()
- newtype InterfaceName = InterfaceName String
- formatInterfaceName :: InterfaceName -> String
- parseInterfaceName :: MonadThrow m => String -> m InterfaceName
- interfaceName_ :: String -> InterfaceName
- parserInterfaceName :: Parser ()
- newtype MemberName = MemberName String
- formatMemberName :: MemberName -> String
- parseMemberName :: MonadThrow m => String -> m MemberName
- memberName_ :: String -> MemberName
- parserMemberName :: Parser ()
- newtype ErrorName = ErrorName String
- formatErrorName :: ErrorName -> String
- parseErrorName :: MonadThrow m => String -> m ErrorName
- errorName_ :: String -> ErrorName
- newtype BusName = BusName String
- formatBusName :: BusName -> String
- parseBusName :: MonadThrow m => String -> m BusName
- busName_ :: String -> BusName
- parserBusName :: Parser ()
- newtype Structure = Structure [Value]
- structureItems :: Structure -> [Variant]
- data Array
- = Array Type (Vector Value)
- | ArrayBytes ByteString
- arrayItems :: Array -> [Variant]
- data Dictionary = Dictionary Type Type (Map Atom Value)
- dictionaryItems :: Dictionary -> [(Variant, Variant)]
- newtype Serial = Serial Word32
- serialValue :: Serial -> Word32
- firstSerial :: Serial
- nextSerial :: Serial -> Serial
- skipSepBy1 :: Parser a -> Parser b -> Parser ()
- forceParse :: String -> (String -> Maybe a) -> String -> a
- maybeParseString :: MonadThrow m => Parser a -> String -> m a
Documentation
Constructors
Instances
A signature is a list of D-Bus types, obeying some basic rules of validity.
The rules of signature validity are complex: see http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-signatures for details.
Instances
| IsString Signature Source # | |
Defined in DBus.Internal.Types Methods fromString :: String -> Signature # | |
| Show Signature Source # | |
| IsAtom Signature Source # | |
| IsValue Signature Source # | |
| IsVariant Signature Source # | |
| NFData Signature Source # | |
Defined in DBus.Internal.Types | |
| Eq Signature Source # | |
| Ord Signature Source # | |
signatureTypes :: Signature -> [Type] Source #
Get the list of types in a signature. The inverse of signature.
formatSignature :: Signature -> String Source #
Convert a signature into a signature string. The inverse of
parseSignature.
signature :: MonadThrow m => [Type] -> m Signature Source #
Convert a list of types into a valid signature.
Throws if the given types are not a valid signature.
signature_ :: [Type] -> Signature Source #
Convert a list of types into a valid signature.
Throws an exception if the given types are not a valid signature.
parseSignature :: MonadThrow m => String -> m Signature Source #
Parse a signature string into a valid signature.
Throws if the given string is not a valid signature.
parseSignatureBytes :: MonadThrow m => ByteString -> m Signature Source #
parseSigFast :: MonadThrow m => ByteString -> m Signature Source #
data SigParseError Source #
Constructors
| SigParseError |
Instances
| Exception SigParseError Source # | |
Defined in DBus.Internal.Types Methods toException :: SigParseError -> SomeException # fromException :: SomeException -> Maybe SigParseError # displayException :: SigParseError -> String # | |
| Show SigParseError Source # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> SigParseError -> ShowS # show :: SigParseError -> String # showList :: [SigParseError] -> ShowS # | |
peekWord8AsInt :: ByteString -> Int -> Int Source #
parseSigFull :: MonadThrow m => ByteString -> m Signature Source #
class IsVariant a where Source #
Instances
| IsVariant Int16 Source # | |
| IsVariant Int32 Source # | |
| IsVariant Int64 Source # | |
| IsVariant Word16 Source # | |
| IsVariant Word32 Source # | |
| IsVariant Word64 Source # | |
| IsVariant Word8 Source # | |
| IsVariant Fd Source # | |
| IsVariant ByteString Source # | |
Defined in DBus.Internal.Types Methods toVariant :: ByteString -> Variant Source # fromVariant :: Variant -> Maybe ByteString Source # | |
| IsVariant ByteString Source # | |
Defined in DBus.Internal.Types Methods toVariant :: ByteString -> Variant Source # fromVariant :: Variant -> Maybe ByteString Source # | |
| IsVariant Array Source # | |
| IsVariant BusName Source # | |
| IsVariant Dictionary Source # | |
Defined in DBus.Internal.Types Methods toVariant :: Dictionary -> Variant Source # fromVariant :: Variant -> Maybe Dictionary Source # | |
| IsVariant ErrorName Source # | |
| IsVariant InterfaceName Source # | |
Defined in DBus.Internal.Types Methods toVariant :: InterfaceName -> Variant Source # fromVariant :: Variant -> Maybe InterfaceName Source # | |
| IsVariant MemberName Source # | |
Defined in DBus.Internal.Types Methods toVariant :: MemberName -> Variant Source # fromVariant :: Variant -> Maybe MemberName Source # | |
| IsVariant ObjectPath Source # | |
Defined in DBus.Internal.Types Methods toVariant :: ObjectPath -> Variant Source # fromVariant :: Variant -> Maybe ObjectPath Source # | |
| IsVariant Serial Source # | |
| IsVariant Signature Source # | |
| IsVariant Structure Source # | |
| IsVariant Variant Source # | |
| IsVariant Text Source # | |
| IsVariant Text Source # | |
| IsVariant String Source # | |
| IsVariant () Source # | |
Defined in DBus.Internal.Types | |
| IsVariant Bool Source # | |
| IsVariant Double Source # | |
| IsValue a => IsVariant (Vector a) Source # | |
Defined in DBus.Internal.Types | |
| IsValue a => IsVariant [a] Source # | |
Defined in DBus.Internal.Types | |
| (Ord k, IsAtom k, IsValue v) => IsVariant (Map k v) Source # | |
| (IsVariant a1, IsVariant a2) => IsVariant (a1, a2) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3) => IsVariant (a1, a2, a3) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4) => IsVariant (a1, a2, a3, a4) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5) => IsVariant (a1, a2, a3, a4, a5) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6) => IsVariant (a1, a2, a3, a4, a5, a6) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7) => IsVariant (a1, a2, a3, a4, a5, a6, a7) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source # | |
Defined in DBus.Internal.Types | |
| (IsVariant a1, IsVariant a2, IsVariant a3, IsVariant a4, IsVariant a5, IsVariant a6, IsVariant a7, IsVariant a8, IsVariant a9, IsVariant a10, IsVariant a11, IsVariant a12, IsVariant a13, IsVariant a14, IsVariant a15) => IsVariant (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # | |
Defined in DBus.Internal.Types | |
class IsVariant a => IsValue a where Source #
Value types can be used as items in containers, such as lists or dictionaries.
Users may not provide new instances of IsValue because this could allow
containers to be created with items of heterogenous types.
Instances
| IsValue Int16 Source # | |
| IsValue Int32 Source # | |
| IsValue Int64 Source # | |
| IsValue Word16 Source # | |
| IsValue Word32 Source # | |
| IsValue Word64 Source # | |
| IsValue Word8 Source # | |
| IsValue Fd Source # | |
| IsValue ByteString Source # | |
Defined in DBus.Internal.Types | |
| IsValue ByteString Source # | |
Defined in DBus.Internal.Types | |
| IsValue ObjectPath Source # | |
Defined in DBus.Internal.Types | |
| IsValue Signature Source # | |
| IsValue Variant Source # | |
| IsValue Text Source # | |
| IsValue Text Source # | |
| IsValue String Source # | |
| IsValue () Source # | |
| IsValue Bool Source # | |
| IsValue Double Source # | |
| IsValue a => IsValue (Vector a) Source # | |
| IsValue a => IsValue [a] Source # | |
| (Ord k, IsAtom k, IsValue v) => IsValue (Map k v) Source # | |
| (IsValue a1, IsValue a2) => IsValue (a1, a2) Source # | |
| (IsValue a1, IsValue a2, IsValue a3) => IsValue (a1, a2, a3) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4) => IsValue (a1, a2, a3, a4) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5) => IsValue (a1, a2, a3, a4, a5) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6) => IsValue (a1, a2, a3, a4, a5, a6) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7) => IsValue (a1, a2, a3, a4, a5, a6, a7) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12) Source # | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13) Source # | |
Defined in DBus.Internal.Types | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14) Source # | |
Defined in DBus.Internal.Types | |
| (IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7, IsValue a8, IsValue a9, IsValue a10, IsValue a11, IsValue a12, IsValue a13, IsValue a14, IsValue a15) => IsValue (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # | |
Defined in DBus.Internal.Types Methods typeOf_ :: Proxy (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Type Source # toValue :: (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) -> Value Source # fromValue :: Value -> Maybe (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15) Source # | |
class IsValue a => IsAtom a where Source #
Atomic types can be used as keys to dictionaries.
Users may not provide new instances of IsAtom because this could allow
dictionaries to be created with invalid keys.
Instances
| IsAtom Int16 Source # | |
| IsAtom Int32 Source # | |
| IsAtom Int64 Source # | |
| IsAtom Word16 Source # | |
| IsAtom Word32 Source # | |
| IsAtom Word64 Source # | |
| IsAtom Word8 Source # | |
| IsAtom Fd Source # | |
| IsAtom ObjectPath Source # | |
Defined in DBus.Internal.Types | |
| IsAtom Signature Source # | |
| IsAtom Text Source # | |
| IsAtom Text Source # | |
| IsAtom String Source # | |
| IsAtom Bool Source # | |
| IsAtom Double Source # | |
Variants may contain any other built-in D-Bus value. Besides
representing native VARIANT values, they allow type-safe storage and
inspection of D-Bus collections.
Constructors
| ValueAtom Atom | |
| ValueVariant Variant | |
| ValueBytes ByteString | |
| ValueVector Type (Vector Value) | |
| ValueMap Type Type (Map Atom Value) | |
| ValueStructure [Value] |
Constructors
| AtomBool Bool | |
| AtomWord8 Word8 | |
| AtomWord16 Word16 | |
| AtomWord32 Word32 | |
| AtomWord64 Word64 | |
| AtomInt16 Int16 | |
| AtomInt32 Int32 | |
| AtomInt64 Int64 | |
| AtomDouble Double | |
| AtomUnixFd Fd | |
| AtomText Text | |
| AtomSignature Signature | |
| AtomObjectPath ObjectPath |
vectorToBytes :: Vector Value -> ByteString Source #
variantType :: Variant -> Type Source #
Every variant is strongly-typed; that is, the type of its contained value is known at all times. This function retrieves that type, so that the correct cast can be used to retrieve the value.
newtype ObjectPath Source #
Object paths are special strings, used to identify a particular object exported from a D-Bus application.
Object paths must begin with a slash, and consist of alphanumeric characters separated by slashes.
See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-marshaling-object-path for details.
Constructors
| ObjectPath String |
Instances
| IsString ObjectPath Source # | |
Defined in DBus.Internal.Types Methods fromString :: String -> ObjectPath # | |
| Show ObjectPath Source # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> ObjectPath -> ShowS # show :: ObjectPath -> String # showList :: [ObjectPath] -> ShowS # | |
| IsAtom ObjectPath Source # | |
Defined in DBus.Internal.Types | |
| IsValue ObjectPath Source # | |
Defined in DBus.Internal.Types | |
| IsVariant ObjectPath Source # | |
Defined in DBus.Internal.Types Methods toVariant :: ObjectPath -> Variant Source # fromVariant :: Variant -> Maybe ObjectPath Source # | |
| NFData ObjectPath Source # | |
Defined in DBus.Internal.Types Methods rnf :: ObjectPath -> () # | |
| Eq ObjectPath Source # | |
Defined in DBus.Internal.Types | |
| Ord ObjectPath Source # | |
Defined in DBus.Internal.Types Methods compare :: ObjectPath -> ObjectPath -> Ordering # (<) :: ObjectPath -> ObjectPath -> Bool # (<=) :: ObjectPath -> ObjectPath -> Bool # (>) :: ObjectPath -> ObjectPath -> Bool # (>=) :: ObjectPath -> ObjectPath -> Bool # max :: ObjectPath -> ObjectPath -> ObjectPath # min :: ObjectPath -> ObjectPath -> ObjectPath # | |
| Lift ObjectPath Source # | |
Defined in DBus.Internal.Types Methods lift :: Quote m => ObjectPath -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ObjectPath -> Code m ObjectPath # | |
pathElements :: ObjectPath -> [String] Source #
fromElements :: [String] -> ObjectPath Source #
formatObjectPath :: ObjectPath -> String Source #
parseObjectPath :: MonadThrow m => String -> m ObjectPath Source #
objectPath_ :: String -> ObjectPath Source #
parserObjectPath :: Parser () Source #
newtype InterfaceName Source #
Interfaces are used to group a set of methods and signals within an exported object. Interface names consist of alphanumeric characters separated by periods.
See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-names-interface for details.
Constructors
| InterfaceName String |
Instances
| IsString InterfaceName Source # | |
Defined in DBus.Internal.Types Methods fromString :: String -> InterfaceName # | |
| Show InterfaceName Source # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> InterfaceName -> ShowS # show :: InterfaceName -> String # showList :: [InterfaceName] -> ShowS # | |
| IsVariant InterfaceName Source # | |
Defined in DBus.Internal.Types Methods toVariant :: InterfaceName -> Variant Source # fromVariant :: Variant -> Maybe InterfaceName Source # | |
| NFData InterfaceName Source # | |
Defined in DBus.Internal.Types Methods rnf :: InterfaceName -> () # | |
| Eq InterfaceName Source # | |
Defined in DBus.Internal.Types Methods (==) :: InterfaceName -> InterfaceName -> Bool # (/=) :: InterfaceName -> InterfaceName -> Bool # | |
| Ord InterfaceName Source # | |
Defined in DBus.Internal.Types Methods compare :: InterfaceName -> InterfaceName -> Ordering # (<) :: InterfaceName -> InterfaceName -> Bool # (<=) :: InterfaceName -> InterfaceName -> Bool # (>) :: InterfaceName -> InterfaceName -> Bool # (>=) :: InterfaceName -> InterfaceName -> Bool # max :: InterfaceName -> InterfaceName -> InterfaceName # min :: InterfaceName -> InterfaceName -> InterfaceName # | |
| Lift InterfaceName Source # | |
Defined in DBus.Internal.Types Methods lift :: Quote m => InterfaceName -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => InterfaceName -> Code m InterfaceName # | |
parseInterfaceName :: MonadThrow m => String -> m InterfaceName Source #
interfaceName_ :: String -> InterfaceName Source #
parserInterfaceName :: Parser () Source #
newtype MemberName Source #
Member names are used to identify a single method or signal within an interface. Method names consist of alphanumeric characters.
See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-names-member for details.
Constructors
| MemberName String |
Instances
| IsString MemberName Source # | |
Defined in DBus.Internal.Types Methods fromString :: String -> MemberName # | |
| Show MemberName Source # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> MemberName -> ShowS # show :: MemberName -> String # showList :: [MemberName] -> ShowS # | |
| IsVariant MemberName Source # | |
Defined in DBus.Internal.Types Methods toVariant :: MemberName -> Variant Source # fromVariant :: Variant -> Maybe MemberName Source # | |
| NFData MemberName Source # | |
Defined in DBus.Internal.Types Methods rnf :: MemberName -> () # | |
| Eq MemberName Source # | |
Defined in DBus.Internal.Types | |
| Ord MemberName Source # | |
Defined in DBus.Internal.Types Methods compare :: MemberName -> MemberName -> Ordering # (<) :: MemberName -> MemberName -> Bool # (<=) :: MemberName -> MemberName -> Bool # (>) :: MemberName -> MemberName -> Bool # (>=) :: MemberName -> MemberName -> Bool # max :: MemberName -> MemberName -> MemberName # min :: MemberName -> MemberName -> MemberName # | |
| Lift MemberName Source # | |
Defined in DBus.Internal.Types Methods lift :: Quote m => MemberName -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => MemberName -> Code m MemberName # | |
formatMemberName :: MemberName -> String Source #
parseMemberName :: MonadThrow m => String -> m MemberName Source #
memberName_ :: String -> MemberName Source #
parserMemberName :: Parser () Source #
Error names are used to identify which type of error was returned from a method call. Error names consist of alphanumeric characters separated by periods.
See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-names-error for details.
Instances
| IsString ErrorName Source # | |
Defined in DBus.Internal.Types Methods fromString :: String -> ErrorName # | |
| Show ErrorName Source # | |
| IsVariant ErrorName Source # | |
| NFData ErrorName Source # | |
Defined in DBus.Internal.Types | |
| Eq ErrorName Source # | |
| Ord ErrorName Source # | |
formatErrorName :: ErrorName -> String Source #
parseErrorName :: MonadThrow m => String -> m ErrorName Source #
errorName_ :: String -> ErrorName Source #
Bus names are used to identify particular clients on the message bus. A bus name may be either unique or well-known, where unique names start with a colon. Bus names consist of alphanumeric characters separated by periods.
See http://dbus.freedesktop.org/doc/dbus-specification.html#message-protocol-names-bus for details.
formatBusName :: BusName -> String Source #
parseBusName :: MonadThrow m => String -> m BusName Source #
parserBusName :: Parser () Source #
A D-Bus Structure is a container type similar to Haskell tuples, storing
values of any type that is convertable to IsVariant. A Structure may
contain up to 255 values.
Most users can use the IsVariant instance for tuples to extract the
values of a structure. This type is for very large structures, which may
be awkward to work with as tuples.
structureItems :: Structure -> [Variant] Source #
A D-Bus Array is a container type similar to Haskell lists, storing zero or more values of a single D-Bus type.
Most users can use the IsVariant instance for lists or vectors to extract
the values of an array. This type is for advanced use cases, where the user
wants to convert array values to Haskell types that are not instances of
IsValue.
Constructors
| Array Type (Vector Value) | |
| ArrayBytes ByteString |
arrayItems :: Array -> [Variant] Source #
data Dictionary Source #
A D-Bus Dictionary is a container type similar to Haskell maps, storing zero or more associations between keys and values.
Most users can use the IsVariant instance for maps to extract the values
of a dictionary. This type is for advanced use cases, where the user
wants to convert dictionary items to Haskell types that are not instances
of IsValue.
Instances
| Show Dictionary Source # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> Dictionary -> ShowS # show :: Dictionary -> String # showList :: [Dictionary] -> ShowS # | |
| IsVariant Dictionary Source # | |
Defined in DBus.Internal.Types Methods toVariant :: Dictionary -> Variant Source # fromVariant :: Variant -> Maybe Dictionary Source # | |
| Eq Dictionary Source # | |
Defined in DBus.Internal.Types | |
dictionaryItems :: Dictionary -> [(Variant, Variant)] Source #
A value used to uniquely identify a particular message within a session. Serials are 32-bit unsigned integers, and eventually wrap.
serialValue :: Serial -> Word32 Source #
firstSerial :: Serial Source #
Get the first serial in the sequence.
nextSerial :: Serial -> Serial Source #
Get the next serial in the sequence. This may wrap around to
firstSerial.
maybeParseString :: MonadThrow m => Parser a -> String -> m a Source #