This file is indexed.

/usr/lib/ocaml/dose2/napkin.mli is in libdose2-ocaml-dev 1.4.2-6build1.

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
(* Copyright 2005-2008 Berke DURAK, INRIA Rocquencourt, Jaap BOENDER.

This file is part of Dose2.

Dose2 is free software: you can redistribute it and/or modify
it under the terms of the GNU Lesser General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.

Dose2 is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public License
along with this program.  If not, see <http://www.gnu.org/licenses/>. *)

(** Normalized Abstract PacKage INformation.

    Provides a common datastructure for expressing package dependency information.
    Readers for Debian or RPM-style metadata output a stream of [package] structures. *)

(** The type [('a, 'b) selector] represents a range of versions where type ['a] represents versions and ['b] represents glob patterns. *)
type ('a) selector =
| Sel_LEQ of 'a
| Sel_GEQ of 'a
| Sel_LT of 'a
| Sel_GT of 'a
| Sel_EQ of 'a
| Sel_ANY;;

(** Maps over selectors. *)
val map_selector: ('a -> 'b) -> ('a) selector -> ('b) selector

(** A range of versions for a unit such as ocaml (>> 3.04) is represented by ["ocaml", Sel_GT "3.04"]. *)
type ('name, 'version, 'glob) versioned = 
| Unit_version of ('name * 'version selector)
| Glob_pattern of 'glob

(** The main datastructure used to represent packages. *)
type ('extra, 'unit, 'version, 'glob, 'architecture, 'source) package = {
  pk_unit            : 'unit;         (** The name of the unit, e.g., ["libc6"] *)
  pk_version         : 'version;      (** Its version ["2.3.6.ds1-8"] *)
  pk_architecture    : 'architecture; (** Its architecture ["i386"]; *)
  pk_extra           : 'extra;        (** Extra user-specific information *)
  pk_size            : int64;         (** Its packaged size, in bytes. *)
  pk_installed_size  : int64;         (** Its installed size, in bytes. *)
  pk_source          : 'source;       (** The source of this package. *)
  pk_provides        : ('unit, 'version, 'glob) versioned list;    (** A list of units provided by this package. *)
  pk_conflicts       : ('unit, 'version, 'glob) versioned list; (** A list of versions with which this package conflicts. *)
  pk_breaks          : ('unit, 'version, 'glob) versioned list; (** A list of versions with which this package breaks. *)
  pk_replaces        : ('unit, 'version, 'glob) versioned list; (** A list of versions which this package replaces. *)
  pk_depends         : ('unit, 'version, 'glob) versioned list list; (** A list of disjunctions which this package needs to run.  For instance,
                                             pk_if [depends] is [[[a;b];[c];[d;e;f]]] then this package requires (a or b) and c and (d or e or f). *)
  pk_pre_depends     : ('unit, 'version, 'glob) versioned list list; (** A list of disjunctions which this package needs to be configured. *)
  pk_suggests        : ('unit, 'version, 'glob) versioned list list; (** A list of disjunctions which this package suggests. *)
  pk_recommends      : ('unit, 'version, 'glob) versioned list list; (** A list of disjunctions which this package recommends. *)
  pk_enhances        : ('unit, 'version, 'glob) versioned list list; (** A list of disjunctions which this package enhances. *)
  pk_essential       : bool; (** If true, this is an essential package. *)
  pk_build_essential : bool  (** If true, this is a build-essential package. *)
};;

type default_package = (unit, string, string, string, string, string * string) package;;
type package_with_files = ((string * string) list, string, string, string, string, string * string) package;;

val map :
  extra:('extra1 -> 'extra2) ->
  unit:('unit1 -> 'unit2) ->
  version:('version1 -> 'version2) ->
	glob:('glob1 -> 'glob2) ->
  architecture:('architecture1 -> 'architecture2) ->
  source:('source1 -> 'source2) ->
  ('extra1, 'unit1, 'version1, 'glob1, 'architecture1, 'source1) package ->
  ('extra2, 'unit2, 'version2, 'glob2, 'architecture2, 'source2) package

(** Returns a textual representation of a versioned range in Debian style. *)
val string_of_versioned : (string, string, string) versioned -> string

(** Package names must be unique *)
val name : ('extra, 'unit, 'version, 'glob, 'architecture, 'source) package -> 'unit * 'version * 'architecture

(* A literate constructor for packages
val io_package :
  io_extra:'extra Io.literate ->
  io_unit:'unit Io.literate ->
  io_version:'version Io.literate ->
	io_glob:'glob Io.literate ->
  io_architecture:'architecture Io.literate ->
  io_source:'source Io.literate ->
  ('extra, 'unit, 'version, 'glob, 'architecture, 'source) package ->
  ('extra, 'unit, 'version, 'glob, 'architecture, 'source) package Io.literate *)

(** Channels are streams of packages *)
type channel = default_package Stream.t;;

(** Convert a package with extras to a default package *)
val to_default_package: ('a, string, string, string, string, string * string) package -> default_package;;