This file is indexed.

/usr/lib/ocaml/dtools/dtools.mli is in libdtools-ocaml-dev 0.3.1-1build2.

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
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
  (**************************************************************************)
  (*  ocaml-dtools                                                          *)
  (*  Copyright (C) 2003-2010  The Savonet Team                             *)
  (**************************************************************************)
  (*  This program is free software; you can redistribute it and/or modify  *)
  (*  it under the terms of the GNU General Public License as published by  *)
  (*  the Free Software Foundation; either version 2 of the License, or     *)
  (*  any later version.                                                    *)
  (**************************************************************************)
  (*  Contact: savonet-devl@lists.sourceforge.net                           *)
  (**************************************************************************)

(* $Id$ *)

(**
  ocaml-dtools.
  @author Stephane Gimenez
*)

(**
  Configuration management module.
*)
module Conf :
sig

  type link = string
      (** Type for links between keys *)

  type path = link list
      (** Type for paths between keys *)

  type ut =
      <
	kind: string option;
	descr: string;
	comments: string list;
	plug: link -> ut -> unit;
        subs: link list;
        path: path -> ut;
        routes: ut -> path list;
	ut: ut;
      >

  (** Type for untyped keys (or keys with unknown type)
      - [kind]: a string describing the type of this key
      - [descr]: a key description/title
      - [comments]: some comments on the key purposes
      - [plug]: a way to plug subkeys
      - [subs]: the list of link names to subkeys
      - [path]: a way to access subkeys
      - [routes]: a way to find paths to an other key
      *)

  type 'a t =
      <
	kind: string option;
  alias:
    ?comments:string list ->
    ?descr:string ->
    (ut -> unit) -> 'a t;
	descr: string;
	comments: string list;
	plug: link -> ut -> unit;
        subs: link list;
        path: path -> ut;
        routes: ut -> path list;
	ut: ut;
	set_d: 'a option -> unit;
	get_d: 'a option;
	set: 'a -> unit;
	get: 'a;
      >

  (** Type for 'a keys
      - [ut]: cast to un untyped key
      - [set_d]: set the default value associated to the key
      - [get_d]: get the default value associated to the key
      - [set]: set the key value according to a user demmand
      - [get]: retrieve the resulting key value
  *)

  type links = (link * ut) list
      (** A set of connections to others keys *)

  exception Undefined of ut
    (** Raised on access to an undefined key (without default value) *)
  exception Invalid of string
    (** Raised when an invalid link has been specified *)
  exception Unbound of ut * string
    (** Raised when a specified link does not exist *)
  exception Bound of ut * string
    (** Raised when a specified link already exist *)
  exception Mismatch of ut
    (** Raised on access to a key with a mismatching type *)
  exception Cyclic of ut * ut
    (** Raised on cyclic plug *)

  exception Wrong_Conf of string * string
    (** Raised when bad configuration assignations are encountered  *)
  exception File_Wrong_Conf of string * int * string
    (** Raised when bad configuration assignations are encountered
	inside configuration files  *)

  type 'a builder =
      ?d:'a ->
      ?p:(ut -> unit) ->
      ?l:links ->
      ?comments:string list ->
      string -> 'a t
    (** Receipt to build a 'a key *)

  val unit : unit builder
  val int : int builder
  val float : float builder
  val bool : bool builder
  val string : string builder
  val list : string list builder
    (** Some key builders *)

  val void :
    ?p:(ut -> unit) -> ?l:links -> ?comments:string list -> string -> ut
    (** A structural key builder *)

  val as_unit : ut -> unit t
  val as_int : ut -> int t
  val as_float : ut -> float t
  val as_bool : ut -> bool t
  val as_string : ut -> string t
  val as_list : ut -> string list t
    (**
      Casts to specificaly typed keys.
      Raises [Mismatch] on mismatching cast.
    *)

  val path_of_string : string -> path
    (** Convert a dot separated string to a path *)
  val string_of_path : path -> string
    (** Convert a path to a dot separated string *)

  val descr : ?prefix:path -> ut -> string
    (** Generate a description table of a (sub)key *)
  val dump :  ?prefix:path -> ut -> string
    (** Dump the configuration table for a (sub)key *)

  val conf_set : ut -> string -> unit
    (**
      Add a value to the configuration keys, according to the given
      correctly formated string: "type key :value"
      Raises [Wrong_Conf] in badly formated cases.
    *)
  val conf_file : ut -> string -> unit
    (**
      Read configuration values from the file associated with the given
      filename.
      Raises [File_Wrong_Conf] with filename line and and error message
      in case of a bad configuration file.
    *)

  val args : ut -> (string list * Arg.spec * string) list
    (**
      A set of command line options to be used with the Arg module.
    *)

end

(**
  Initialisation management module.
  Allow to define procedures that must be executed at start up, and
  procedures that are to be executed at exit to have a clean quit.
*)
module Init :
sig

  type t

  val start : t
    (** Root start atom *)
  val stop : t
    (** Root stop atom *)

  val make :
    ?name:string ->
    ?depends:(t list) -> ?triggers:(t list) ->
    ?after:(t list) -> ?before:(t list) ->
    (unit -> unit) -> t
    (**
      Define a init atom associated with the given [(unit -> unit)]
      procedure, which eventualy depends on others atoms (these atoms
      will be executed before the one currently defined) an triggers
      other atoms (these atoms will be executed after the one currently
      defined). [after] and [before] allow to register the currently
      defined atom in the depend and triggers lists of other atoms.
    *)

  val at_start :
    ?name:string ->
    ?depends:(t list) -> ?triggers:(t list) ->
    ?after:(t list) -> ?before:(t list) ->
    (unit -> unit) -> t
    (**
      Same as [make] plus a shortcut for "after Init.start".
    *)

  val at_stop :
    ?name:string ->
    ?depends:(t list) -> ?triggers:(t list) ->
    ?after:(t list) -> ?before:(t list) ->
    (unit -> unit) -> t
    (**
      Same as [make] plus a shortcut for "before Init.stop".
    *)

  val exec : t -> unit
    (**
      Launch the execution of a given init atom.
    *)

  val init : ?prohibit_root:bool -> (unit -> unit) -> unit
    (**
      This fuction must be used to launch the main procedure of the
      program. It first execute the registered start atoms, then call
      the main procedure, then execute the registered stop atoms.
      Exceptions raised by the main procedure are catched, in order to
      close properly even in such cases. Exceptions are raised again
      after cleaning.
      When invoqued with [~prohibit_root:true], it checks for root access
      rights (euid, egid) and exit in this case.
    *)

  exception StartError of exn
  exception StopError of exn

  val conf : Conf.ut
  val conf_daemon : bool Conf.t
  val conf_daemon_pidfile : bool Conf.t
  val conf_daemon_pidfile_path : string Conf.t
  val conf_concurrent : bool Conf.t
  val conf_trace : bool Conf.t
  val conf_catch_exn : bool Conf.t

  val args : (string list * Arg.spec * string) list
    (**
      A set of command line options to be used with the Arg module.
    *)

end


module Log :
sig

  type t =
      <
	active: int -> bool;
	f: 'a. int -> ('a, unit, string, unit) format4 -> 'a;
      >
    (**
       Type for loggers.
    *)

  type custom_log =
    {
      timestamp : bool ;
      exec      : string -> unit
    }

  val add_custom_log : string -> custom_log -> unit
    (**
      Add a custom logging functions. 
    *)

  val rm_custom_log : string -> unit
    (**
      Remove a custom logging functions.    
    *)

  val make : Conf.path -> t
    (**
      Make a logger labeled according to the given path.
    *)

  val start : Init.t
    (**
      An atom that starts the logging.
    *)

  val stop : Init.t
    (**
      An atom that stops the logging.
    *)

  val conf : Conf.ut
  val conf_level : int Conf.t
  val conf_unix_timestamps : bool Conf.t
  val conf_stdout : bool Conf.t
  val conf_file : bool Conf.t
  val conf_file_path : string Conf.t
  val conf_file_append : bool Conf.t
  val conf_file_perms : int Conf.t

  val args : (string list * Arg.spec * string) list
    (**
      A set of command line options to be used with the Arg module.
    *)

end