This file is indexed.

/usr/lib/ocaml/reins/dugADT.mli is in libreins-ocaml-dev 0.1a-5.

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
(**************************************************************************)
(*  The OCaml Reins Library                                               *)
(*                                                                        *)
(*  Copyright 2007 Mike Furr.                                             *)
(*  All rights reserved.  This file is distributed under the terms of the  *)
(*  GNU Lesser General Public License version 2.1 with the linking        *)
(*  exception given in the COPYING file.                                  *)
(**************************************************************************)

(** Abstract signature for ADTs => DUG extraction *)

module type S = sig

  type ('v,'t) generator
      (** functions that return a container and none of its arguments
	  are containers *)

  type ('v,'t) mutator
      (** functions that return a container and at least one arg is a
	  container *)

  type ('v,'t) observer
      (** functions that do not return a container, but takes one as
	  an argument *)

  type ('v,'t) op
      (** One of {generator,mutator,observer} *)

  val op_to_string : ('v,'t) op -> string

  val coerce_gen : ('v,'t) generator -> ('v,'t) op
  val coerce_mut : ('v,'t) mutator -> ('v,'t) op
  val coerce_obs : ('v,'t) observer -> ('v,'t) op

  val classify : ('v,'t) op -> 
    (('v,'t) generator,('v,'t) mutator,('v,'t) observer) Dug.kind
  val strip : ('v,'t) op -> (unit,unit) op

  val op_dependencies : ('a,Dug.Id.t) op -> Dug.Id.t list
  val create_op : 
    (unit,unit) op -> Dug.Id.t
    -> (unit -> 'a) -> (int -> Dug.Id.t) -> ('a,Dug.Id.t) op

end

(*
module type S =
  sig
    type 'a generator
    type 'a mutator
    type 'a observer
    type 'a op
    val op_to_string : 'a op -> string
    val coerce_gen : 'a generator -> 'a op
    val coerce_mut : 'a mutator -> 'a op
    val coerce_obs : 'a observer -> 'a op
    val classify : 'a op -> ('a generator, 'a mutator, 'a observer) Dug.kind
    val strip : 'a op -> unit op
    val op_dependencies : Dug.Id.t op -> Dug.Id.t list
    val create_op : unit op -> Dug.Id.t -> (int -> Dug.Id.t) -> Dug.Id.t op

  end
*)
(*
    module Impl : sig
      val benchmark : (Dug.Id.t generator, Dug.Id.t mutator, Dug.Id.t observer) Dug.t
	-> float
      val get_dug : unit -> (unit generator, unit mutator, unit observer) Dug.t
      val clear_profile : unit -> unit
    end
*)