This file is indexed.

/usr/lib/ocaml/dose3/cudfAdd.mli is in libdose3-ocaml-dev 4.0.2-4.

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
(** Library of additional functions for the CUDF format. *)

(** {2 Basic comparison operations for packages} *)

(** Equality test: two CUDF packages are equal if their names and versions are equal. *)
val equal : Cudf.package -> Cudf.package -> bool

(** Compare function: compares two CUDF packages using standard CUDF comparison operator (i.e. comparing by their name and version). *)
val compare : Cudf.package -> Cudf.package -> int

(** {2 Specialized data structures for CUDF packages} *)

(** A hash function for CUDF packages, using only their name and version. *)
val hash : Cudf.package -> int

(** Sort function: sorts a CUDF packages list using the standard CUDF comparison operator in ascending order *)
val sort : Cudf.package list -> Cudf.package list

(** Data structures: *)

(** Specialized hashtable for CUDF packages. *)
module Cudf_hashtbl : (Hashtbl.S with type key = Cudf.package)

(** Specialized set data structure for CUDF packages. *)
module Cudf_set : (Set.S with type elt = Cudf.package)

(** Convert a list of CUDF packages to a set of CUDF packages. *)
val to_set : Cudf_set.elt list -> Cudf_set.t

(** {2 Extended function on Cudf data types } *)

(** Return the list of packages that that respect the given constraint *)
val who_provides : Cudf.universe -> Cudf_types.vpkg -> Cudf.package list

(** Return the list of packages satisfying the vpkg list *)
val resolve_deps : Cudf.universe -> Cudf_types.vpkglist -> Cudf.package list

(** Returns the list of packages that are dependencies of the given package *)
val who_depends : Cudf.universe -> Cudf.package -> Cudf.package list list

(** A table to associate to each id the list of packages id that are in
    conflict with it. Reflexive conflicts are made explicit.
*)
type ctable = (int, int list ref) ExtLib.Hashtbl.t

(** Create a ctable from a package universe *)
val init_conflicts : Cudf.universe -> ctable

(** Return the list of packages in conflict with the given package *)
val who_conflicts : ctable -> Cudf.universe -> Cudf.package -> Cudf.package list

(** Like who_provides but returns a list of cudf ids *)
val resolve_vpkg_int : Cudf.universe -> Cudf_types.vpkg -> int list

(** Like resolve_deps but returns a list of cudf ids *)
val resolve_vpkgs_int : Cudf.universe -> Cudf_types.vpkglist -> int list

(** {2 Functions to encode and decode strings. } *)
(* TODO: What are these functions doing in this module? *)

(** Encode a string.

    Replaces all the "not allowed" characters
    with their ASCII code (in hexadecimal format),
    prefixed with a '%' sign.
    
    Only "allowed" characters are letters, numbers and these: [@/+().-],
    all the others are replaced.
    
    Examples:
    {ul
    {li [encode "ab"  = "ab"]}
    {li [encode "|"   = "%7c"]}
    {li [encode "a|b" = "a%7cb"]}
    }
*)
val encode : string -> string

(** Decode a string. Opposite of the [encode] function.

    Replaces all the encoded "not allowed" characters
    in the string by their original (i.e. not encoded) versions.

    Examples:
    {ul
    {li [decode "ab" = "ab"]}
    {li [decode "%7c" = "|"]}
    {li [decode "a%7cb" = "a|b"]}
    }
*)
val decode : string -> string

(** {2 Additional functions on the CUDF data types. } *)

(** Returns a list of packages containing for each package only the
    latest version *)
val latest: Cudf.package list -> Cudf.package list

(** Set of strings *)
module StringSet : (Set.S with type elt = ExtLib.String.t)

(** Returns the set of all names in the given universe *)
val pkgnames : Cudf.universe -> StringSet.t

(** Add a new property to the given cudf preamble *)
val add_properties : Cudf.preamble -> Cudf_types.typedecl -> Cudf.preamble

(** return the value of the requested property. 
 * emit a warning and raise Not_found if the property does not exists *)
val get_property : string -> Cudf.package -> string

(** Returns true if the package is essential, that is the cudf package has
    a extra property named "essential" and its value is "yes" *)
val is_essential : Cudf.package -> bool

(** build a hash table that associates (package name, String version) to CUDF packages *)
val realversionmap : Cudf.package list ->
  (Cudf_types.pkgname * string, Cudf.package) ExtLib.Hashtbl.t

(** Return the unique cudf id of a package in a universe *)
val vartoint : Cudf.universe -> Cudf.package -> int

(** Given a universe and a cudf id returns the corresponding package.
    Raise Not_found if the id does not correspond to a package.
*)
val inttovar : Cudf.universe -> int -> Cudf.package

val cudfop :
  (string * string) option ->
  ([> `Eq | `Neq | `Geq | `Gt | `Leq | `Lt ] * string) option

val compute_pool : Cudf.universe -> int list list array * int list array

val add_to_package_list :
  ('a, 'b list ref) ExtLib.Hashtbl.t -> 'a -> 'b -> unit

val get_package_list : ('a, 'b list ref) ExtLib.Hashtbl.t -> 'a -> 'b list

(** normalize_set l returns the list l without any duplicate element. *)
val normalize_set : int list -> int list

(** {2 Formatting, printing, converting to string. } *)

val string_of : (Format.formatter -> 'a -> 'b) -> 'a -> string

val pp_version : Format.formatter -> Cudf.package -> unit
val pp_package : Format.formatter -> Cudf.package -> unit

(** return a string containg either the value of the optional field
    "number" or the cudf version *)
val string_of_version : Cudf.package -> string

(** return a string of the form "name ( = version)" *)
val string_of_package : Cudf.package -> string

(* Function signature for cudf package printer. The output represents
   a triple (name, version, (field name, value) list *)
type pp = Cudf.package -> string * string * (string * (string * bool)) list

(** [pp ?decode from_cudf pkg] package pretty printer.
    [from_cudf] a function that gets a (name,cudfversion) pair and returns a (name,realversion).
    [?fields] additional fields to print.
    [?decode] a function that decode the package name and version.
    
    returns : a pair (name,versiom,property list)

    note that if the package has version less then 0, then the version is printed
    as "nan"
*)
val pp :
  (Cudf_types.pkgname * Cudf_types.version -> 'a * Cudf_types.pkgname) ->
  ?fields: string list->
  ?decode: (Cudf_types.pkgname -> string) -> pp

(** [default_pp] default package printer. Extracts string values from a 
    cudf package : Name, Version, Fields. Where Fields is a list of 
    field name , value pairs . If the version of the package is
    a negative number, the version version if printed as "nan". *)
val default_pp : pp

(** cudf vpkglist printer. *)
val pp_vpkg : pp -> Format.formatter -> Cudf_types.vpkg -> unit

(** cudf vpkglist printer. *)
val pp_vpkglist : pp -> Format.formatter -> Cudf_types.vpkglist -> unit