Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Type
- showType :: Bool -> Type -> String
- newtype Signature = Signature [Type]
- signatureTypes :: Signature -> [Type]
- formatSignature :: Signature -> String
- typeCode :: Type -> String
- signature :: [Type] -> Maybe Signature
- signature_ :: [Type] -> Signature
- parseSignature :: String -> Maybe Signature
- parseSignatureBytes :: ByteString -> Maybe Signature
- parseSigFast :: ByteString -> Maybe Signature
- parseAtom :: Int -> (Type -> a) -> a -> a
- data SigParseError = SigParseError
- peekWord8AsInt :: Ptr Word8 -> Int -> IO Int
- parseSigFull :: ByteString -> Maybe Signature
- extractFromVariant :: IsValue a => Variant -> Maybe a
- class IsVariant a where
- class IsVariant a => IsValue a where
- class IsValue a => IsAtom a where
- newtype Variant = Variant Value
- data 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
- vectorItemType :: IsValue a => Vector a -> 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')
- mapItemType :: (IsValue k, IsValue v) => Map k v -> (Type, Type)
- varToVal :: IsVariant a => a -> Value
- newtype ObjectPath = ObjectPath String
- pathElements :: ObjectPath -> [String]
- fromElements :: [String] -> ObjectPath
- formatObjectPath :: ObjectPath -> String
- parseObjectPath :: String -> Maybe ObjectPath
- objectPath_ :: String -> ObjectPath
- parserObjectPath :: Parser ()
- newtype InterfaceName = InterfaceName String
- formatInterfaceName :: InterfaceName -> String
- parseInterfaceName :: String -> Maybe InterfaceName
- interfaceName_ :: String -> InterfaceName
- parserInterfaceName :: Parser ()
- newtype MemberName = MemberName String
- formatMemberName :: MemberName -> String
- parseMemberName :: String -> Maybe MemberName
- memberName_ :: String -> MemberName
- parserMemberName :: Parser ()
- newtype ErrorName = ErrorName String
- formatErrorName :: ErrorName -> String
- parseErrorName :: String -> Maybe ErrorName
- errorName_ :: String -> ErrorName
- newtype BusName = BusName String
- formatBusName :: BusName -> String
- parseBusName :: String -> Maybe 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 :: Parser a -> String -> Maybe a
Documentation
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.
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 :: [Type] -> Maybe Signature Source #
Convert a list of types into a valid signature.
Returns Nothing
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 :: String -> Maybe Signature Source #
Parse a signature string into a valid signature.
Returns Nothing
if the given string is not a valid signature.
parseSigFast :: ByteString -> Maybe Signature Source #
data SigParseError Source #
parseSigFull :: ByteString -> Maybe Signature Source #
class IsVariant a where Source #
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.
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.
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.
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.
pathElements :: ObjectPath -> [String] Source #
fromElements :: [String] -> ObjectPath Source #
formatObjectPath :: ObjectPath -> String Source #
parseObjectPath :: String -> Maybe 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.
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.
formatMemberName :: MemberName -> String Source #
parseMemberName :: String -> Maybe 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.
formatErrorName :: ErrorName -> String 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 #
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
.
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
.
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
.