This file is indexed.

/usr/lib/ocaml/obus/oBus_message.mli is in libobus-ocaml-dev 1.1.5-3build1.

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
(*
 * oBus_message.mli
 * ----------------
 * Copyright : (c) 2008, Jeremie Dimino <jeremie@dimino.org>
 * Licence   : BSD3
 *
 * This file is a part of obus, an ocaml implementation of D-Bus.
 *)

(** Message description *)

type serial = int32

(** {6 Message structure} *)

type body = OBus_value.V.sequence
    (** The body is a sequence of dynamically typed values *)

type typ =
  | Method_call of OBus_path.t * OBus_name.interface * OBus_name.member
  | Method_return of serial
  | Error of serial * OBus_name.error
  | Signal of OBus_path.t * OBus_name.interface * OBus_name.member

(** flags *)
type flags = {
  no_reply_expected : bool;
  no_auto_start : bool;
}

val no_reply_expected : flags -> bool
  (** [no_reply_expected] projection *)

val no_auto_start : flags -> bool
  (** [no_auto_start] projection *)

val make_flags : ?no_reply_expected:bool -> ?no_auto_start:bool -> unit -> flags
  (** Creates message flags. All optionnal arguments default to
      [false] *)

val default_flags : flags
  (** All false *)

type t = {
  flags : flags;
  serial : serial;
  typ : typ;
  destination : OBus_name.bus;
  sender : OBus_name.bus;
  body : body;
}

(** {8 Projections} *)

val flags : t -> flags
val serial : t -> serial
val typ : t -> typ
val destination : t -> OBus_name.bus
val sender : t -> OBus_name.bus
val body : t -> body

(** {6 Helpers for creating messages} *)

(** Note that when creating an message the serial field is not
    relevant, it is overridden by {!OBus_connection} at
    sending-time *)

val make :
  ?flags : flags ->
  ?serial : serial ->
  ?sender : OBus_name.bus ->
  ?destination : OBus_name.bus ->
  typ : typ ->
  body -> t

val method_call :
  ?flags : flags ->
  ?serial : serial ->
  ?sender : OBus_name.bus ->
  ?destination : OBus_name.bus ->
  path : OBus_path.t ->
  ?interface : OBus_name.interface ->
  member : OBus_name.member ->
  body -> t

val method_return :
  ?flags : flags ->
  ?serial : serial ->
  ?sender : OBus_name.bus ->
  ?destination : OBus_name.bus ->
  reply_serial : serial ->
  body -> t

val error :
  ?flags : flags ->
  ?serial : serial ->
  ?sender : OBus_name.bus ->
  ?destination : OBus_name.bus ->
  reply_serial : serial ->
  error_name : OBus_name.error ->
  body -> t

val signal :
  ?flags : flags ->
  ?serial : serial ->
  ?sender : OBus_name.bus ->
  ?destination : OBus_name.bus ->
  path : OBus_path.t ->
  interface : OBus_name.interface ->
  member : OBus_name.member ->
  body -> t

(** {6 Errors} *)

exception Invalid_reply of string
  (** Exception raised when the signature of the reply to a method
      call does not match the expected signature. The argument is an
      error message. *)

val invalid_reply : method_call : t -> expected_signature : OBus_value.signature -> method_return : t -> exn
  (** [invalid_reply ~method_call ~expected_signature ~method_return]
      returns an {!Invalid_reply} exception with a informative
      description of the error.

      It raises [Invalid_argument] if [method_call] is not a method
      call message or [method_return] is not a method return
      message *)

(** {6 Pretty-printing} *)

val print : Format.formatter -> t -> unit
  (** Print a message on a formatter *)