Safe Haskell | Safe-Inferred |
---|---|
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 :: forall a. 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
- = 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
- 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
Generic Type # | |
Show Type # | |
NFData Type # | |
Defined in DBus.Internal.Types | |
Eq Type # | |
Ord Type # | |
type Rep Type # | |
Defined in DBus.Internal.Types type Rep Type = D1 ('MetaData "Type" "DBus.Internal.Types" "dbus-1.3.1-9AjZbN8siC74O1XFVBgFV" 'False) ((((C1 ('MetaCons "TypeBoolean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeWord8" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeWord16" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeWord32" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeWord64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInt16" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeInt32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInt64" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "TypeDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeUnixFd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeSignature" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeObjectPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeVariant" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: (C1 ('MetaCons "TypeDictionary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "TypeStructure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]))))))) |
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 # | |
Defined in DBus.Internal.Types Methods fromString :: String -> Signature | |
Show Signature # | |
IsAtom Signature # | |
IsValue Signature # | |
IsVariant Signature # | |
Defined in DBus.Internal.Types | |
NFData Signature # | |
Defined in DBus.Internal.Types | |
Eq Signature # | |
Ord Signature # | |
Defined in DBus.Internal.Types |
signatureTypes :: Signature -> [Type] #
Get the list of types in a signature. The inverse of signature
.
formatSignature :: Signature -> String #
Convert a signature into a signature string. The inverse of
parseSignature
.
signature :: MonadThrow m => [Type] -> m Signature #
Convert a list of types into a valid signature.
Throws if the given types are not a valid signature.
signature_ :: [Type] -> Signature #
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 #
Parse a signature string into a valid signature.
Throws if the given string is not a valid signature.
parseSignatureBytes :: MonadThrow m => ByteString -> m Signature #
parseSigFast :: MonadThrow m => ByteString -> m Signature #
data SigParseError #
Constructors
SigParseError |
Instances
Exception SigParseError # | |
Defined in DBus.Internal.Types Methods toException :: SigParseError -> SomeException fromException :: SomeException -> Maybe SigParseError displayException :: SigParseError -> String | |
Show SigParseError # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> SigParseError -> ShowS show :: SigParseError -> String showList :: [SigParseError] -> ShowS |
peekWord8AsInt :: ByteString -> Int -> Int #
parseSigFull :: MonadThrow m => ByteString -> m Signature #
extractFromVariant :: IsValue a => Variant -> Maybe a #
Instances
class IsVariant a => IsValue a where #
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 # | |
IsValue Int32 # | |
IsValue Int64 # | |
IsValue Word16 # | |
IsValue Word32 # | |
IsValue Word64 # | |
IsValue Word8 # | |
IsValue Fd # | |
IsValue ByteString # | |
IsValue ByteString # | |
IsValue ObjectPath # | |
Defined in DBus.Internal.Types Methods typeOf_ :: Proxy ObjectPath -> Type # toValue :: ObjectPath -> Value # fromValue :: Value -> Maybe ObjectPath # | |
IsValue Signature # | |
IsValue Variant # | |
IsValue Text # | |
IsValue Text # | |
IsValue String # | |
IsValue () # | |
IsValue Bool # | |
IsValue Double # | |
IsValue a => IsValue (Vector a) # | |
IsValue a => IsValue [a] # | |
(Ord k, IsAtom k, IsValue v) => IsValue (Map k v) # | |
(IsValue a1, IsValue a2) => IsValue (a1, a2) # | |
(IsValue a1, IsValue a2, IsValue a3) => IsValue (a1, a2, a3) # | |
(IsValue a1, IsValue a2, IsValue a3, IsValue a4) => IsValue (a1, a2, a3, a4) # | |
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5) => IsValue (a1, a2, a3, a4, a5) # | |
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6) => IsValue (a1, a2, a3, a4, a5, a6) # | |
(IsValue a1, IsValue a2, IsValue a3, IsValue a4, IsValue a5, IsValue a6, IsValue a7) => IsValue (a1, a2, a3, a4, a5, a6, a7) # | |
(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) # | |
(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) # | |
(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) # | |
(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) # | |
(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) # | |
(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) # | |
(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) # | |
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) # | |
Defined in DBus.Internal.Types |
class IsValue a => IsAtom a where #
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.
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 |
showThings :: String -> (a -> String) -> String -> [a] -> String #
vectorToBytes :: Vector Value -> ByteString #
variantType :: Variant -> Type #
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 #
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
pathElements :: ObjectPath -> [String] #
fromElements :: [String] -> ObjectPath #
formatObjectPath :: ObjectPath -> String #
parseObjectPath :: MonadThrow m => String -> m ObjectPath #
objectPath_ :: String -> ObjectPath #
parserObjectPath :: Parser () #
newtype InterfaceName #
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
formatInterfaceName :: InterfaceName -> String #
parseInterfaceName :: MonadThrow m => String -> m InterfaceName #
interfaceName_ :: String -> InterfaceName #
parserInterfaceName :: Parser () #
newtype MemberName #
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 # | |
Defined in DBus.Internal.Types Methods fromString :: String -> MemberName | |
Show MemberName # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> MemberName -> ShowS show :: MemberName -> String showList :: [MemberName] -> ShowS | |
IsVariant MemberName # | |
Defined in DBus.Internal.Types | |
NFData MemberName # | |
Defined in DBus.Internal.Types Methods rnf :: MemberName -> () | |
Eq MemberName # | |
Defined in DBus.Internal.Types | |
Ord MemberName # | |
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 # | |
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 #
parseMemberName :: MonadThrow m => String -> m MemberName #
memberName_ :: String -> MemberName #
parserMemberName :: Parser () #
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.
Constructors
ErrorName String |
Instances
IsString ErrorName # | |
Defined in DBus.Internal.Types Methods fromString :: String -> ErrorName | |
Show ErrorName # | |
IsVariant ErrorName # | |
Defined in DBus.Internal.Types | |
NFData ErrorName # | |
Defined in DBus.Internal.Types | |
Eq ErrorName # | |
Ord ErrorName # | |
Defined in DBus.Internal.Types |
formatErrorName :: ErrorName -> String #
parseErrorName :: MonadThrow m => String -> m ErrorName #
errorName_ :: String -> ErrorName #
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.
Constructors
BusName String |
formatBusName :: BusName -> String #
parseBusName :: MonadThrow m => String -> m BusName #
parserBusName :: Parser () #
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] #
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] #
data Dictionary #
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
.
Constructors
Dictionary Type Type (Map Atom Value) |
Instances
Show Dictionary # | |
Defined in DBus.Internal.Types Methods showsPrec :: Int -> Dictionary -> ShowS show :: Dictionary -> String showList :: [Dictionary] -> ShowS | |
IsVariant Dictionary # | |
Defined in DBus.Internal.Types | |
Eq Dictionary # | |
Defined in DBus.Internal.Types |
dictionaryItems :: Dictionary -> [(Variant, Variant)] #
A value used to uniquely identify a particular message within a session. Serials are 32-bit unsigned integers, and eventually wrap.
Constructors
Serial Word32 |
serialValue :: Serial -> Word32 #
firstSerial :: Serial #
Get the first serial in the sequence.
nextSerial :: Serial -> Serial #
Get the next serial in the sequence. This may wrap around to
firstSerial
.
skipSepBy1 :: Parser a -> Parser b -> Parser () #
forceParse :: String -> (String -> Maybe a) -> String -> a #
maybeParseString :: MonadThrow m => Parser a -> String -> m a #