This file is indexed.

/usr/lib/ocaml/obus/oBus_connection.mli is in libobus-ocaml-dev 1.1.5-5build1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  1
  2
  3
  4
  5
  6
  7
  8
  9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
(*
 * oBus_connection.mli
 * -------------------
 * Copyright : (c) 2008, Jeremie Dimino <jeremie@dimino.org>
 * Licence   : BSD3
 *
 * This file is a part of obus, an ocaml implementation of D-Bus.
 *)

(** D-Bus connections *)

(** This module implement manipulation of a D-Bus connection. A D-Bus
    connection is a channel opened with another application which also
    implement the D-Bus protocol. It is used to exchange D-Bus
    messages. *)

type t
    (** Type of D-Bus connections *)

val compare : t -> t -> int
  (** Same as [Pervasives.compare]. It allows this module to be used
      as argument to the functors [Set.Make] and [Map.Make]. *)

(** {6 Creation} *)

(** The following functions will return a connection which is ready to
    send and receive messages. You should use them only for direct
    connection to another application without passing through a
    message bus.

    Otherwise you should use [OBus_bus] or immediatly call
    [OBus_bus.register_connection] after the creation. *)

val of_addresses : ?switch : Lwt_switch.t -> ?shared : bool -> OBus_address.t list -> t Lwt.t
  (** [of_addresses ?switch ?shared addresses] try to get a working
      D-Bus connection from a list of addresses. The server must be
      accessible from at least one of these addresses.

      If [shared] is true and a connection to the same server is
      already open, then it is used instead of [transport]. This is
      the default behaviour. *)

val loopback : unit -> t
  (** Creates a connection with a loopback transport *)

val close : t -> unit Lwt.t
  (** Close a connection.

      All thread waiting for a reply will fail with the exception
      {!Connection_closed}.

      Notes:
      - when a connection is closed, the transport it use is
        closed too
      - if the connection is already closed, it does nothing
  *)

val active : t -> bool React.signal
  (** Returns whether a connection is active. *)

exception Connection_closed
  (** Raise when trying to use a closed connection *)

exception Connection_lost
  (** Raised when a connection has been lost *)

exception Transport_error of exn
  (** Raised when something wrong happen on the backend transport of
      the connection *)

(** {6 Informations} *)

val name : t -> OBus_name.bus
  (** Returns the unique name of the connection. This is only
      meaning-full is the other endpoint of the connection is a
      message bus. If it is not the case it returns [""]. *)

(**/**)
val set_name : t -> OBus_name.bus -> unit
(**/**)

val transport : t -> OBus_transport.t
  (** [transport connection] get the transport associated with a
      connection *)

val can_send_basic_type : t -> OBus_value.T.basic -> bool
val can_send_single_type : t -> OBus_value.T.single -> bool
val can_send_sequence_type : t -> OBus_value.T.sequence -> bool
  (** [can_send_*_type connection typ] returns whether values of the
      given type can be sent through the given connection. *)

(** {6 Sending messages} *)

(** These functions are the low-level functions for sending
    messages. They take and return a complete message description *)

val send_message : t -> OBus_message.t -> unit Lwt.t
  (** [send_message connection message] send a message without
      expecting a reply. *)

val send_message_with_reply : t -> OBus_message.t -> OBus_message.t Lwt.t
  (** [send_message_with_reply connection message] Send a message and
      return a thread which wait for the reply (which is a method
      return or an error) *)

val send_message_keep_serial : t -> OBus_message.t -> unit Lwt.t
  (** Same as {!send_message} but do not generate a serial for the
      message.

      Warning: this is for implementing a D-Bus daemon only, not for
      casual use. *)

val send_message_keep_serial_with_reply : t -> OBus_message.t -> OBus_message.t Lwt.t
  (** Same as {!send_message_with_reply} but do not generate a serial
      for the message.

      Warning: this is for implementing a D-Bus daemon only, not for
      casual use. *)

(** {6 Helpers for calling methods} *)

val method_call :
  connection : t ->
  ?destination : OBus_name.bus ->
  path : OBus_path.t ->
  ?interface : OBus_name.interface ->
  member : OBus_name.member ->
  i_args : 'a OBus_value.C.sequence ->
  o_args : 'b OBus_value.C.sequence ->
  'a -> 'b Lwt.t
  (** Calls a method using the given parameters, and waits for its
      reply. *)

val method_call_with_message :
  connection : t ->
  ?destination : OBus_name.bus ->
  path : OBus_path.t ->
  ?interface : OBus_name.interface ->
  member : OBus_name.member ->
  i_args : 'a OBus_value.C.sequence ->
  o_args : 'b OBus_value.C.sequence ->
  'a -> (OBus_message.t * 'b) Lwt.t
  (** Same as {!method_call}, but also returns the reply message so
      you can extract informations from it. *)

val method_call_no_reply :
  connection : t ->
  ?destination : OBus_name.bus ->
  path : OBus_path.t ->
  ?interface : OBus_name.interface ->
  member : OBus_name.member ->
  i_args : 'a OBus_value.C.sequence ->
  'a -> unit Lwt.t
  (** Same as {!method_call} but do not expect a reply *)

(** {6 General purpose filters} *)

(** Filters are functions whose are applied on all incoming and
    outgoing messages.

    For incoming messages they are called before dispatching, for
    outgoing ones, they are called just before being sent.
*)

type filter = OBus_message.t -> OBus_message.t option
  (** The result of a filter must be:

      - [Some msg] where [msg] is the message given to the filter
      modified or not, which means that the message is replaced by
      this one

      - [None] which means that the message will be dropped, i.e. not
      dispatched or not sent *)

val incoming_filters : t -> filter Lwt_sequence.t
  (** Filters applied on incomming messages *)

val outgoing_filters : t -> filter Lwt_sequence.t
  (** Filters appllied on outgoing messages *)

(** {6 Connection's local Storage} *)

(** Connection's local storage allow to attach values to a
    connection. It is internally used by modules of obus. *)

type 'a key
  (** Type of keys. Keys are used to identify a resource attached to a
      connection. *)

val new_key : unit -> 'a key
  (** [new_key ()] generates a new key. *)

val get : t -> 'a key -> 'a option
  (** [get connection key] returns the data associated to [key] in
      connection, if any. *)

val set : t -> 'a key -> 'a option -> unit
  (** [set connection key value] attach [value] to [connection] under
      the key [key]. [set connection key None] will remove any
      occurence of [key] from [connection]. *)

(** {6 Errors handling} *)

(** Note: when a filter/signal handler/method_call handler raise an
    exception, it is just dropped. If {!OBus_info.debug} is set then a
    message is printed on [stderr] *)

val set_on_disconnect : t -> (exn -> unit Lwt.t) -> unit
  (** Sets the function called when a fatal error happen or when the
      conection is lost.

      Notes:
      - the default function does nothing
      - it is not called when the connection is closed using {!close}
      - if the connection is closed, it does nothing
  *)

(** {6 Low-level} *)

val of_transport : ?switch : Lwt_switch.t -> ?guid : OBus_address.guid -> ?up : bool -> OBus_transport.t -> t
  (** Create a D-Bus connection on the given transport. If [guid] is
      provided the connection will be shared.

      [up] tell whether the connection is initially up or down,
      default is [true]. *)

(** A connection can be up or down, expect for connection created with
    [of_transport], newly created connection are always up.

    When a connection is down, messages will not be dispatched *)

val state : t -> [ `Up | `Down ] React.signal
  (** Signal holding the current state of the connection *)

val set_up : t -> unit
  (** Sets up the connection if it is not already up *)

val set_down : t -> unit
  (** Sets down the connection if it is not already down *)