This file is indexed.

/usr/lib/ocaml/camlpdf/pdffun.mli is in libcamlpdf-ocaml-dev 2.2.1-1build1.

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
(** Parsing and Evaluating PDF Functions. *)

type calculator =
  | If of calculator list
  | IfElse of calculator list * calculator list
  | Bool of bool
  | Float of float
  | Int of int32
  | Abs
  | Add
  | Atan
  | Ceiling
  | Cos
  | Cvi
  | Cvr
  | Div
  | Exp
  | Floor
  | Idiv
  | Ln
  | Log
  | Mod
  | Mul
  | Neg
  | Round
  | Sin
  | Sqrt
  | Sub
  | Truncate
  | And
  | Bitshift
  | Eq
  | Ge
  | Gt
  | Le
  | Lt
  | Ne
  | Not
  | Or
  | Xor
  | Copy
  | Exch
  | Pop
  | Dup
  | Index
  | Roll

type sampled =
  {size : int list; 
   order : int;
   encode : float list;
   decode : float list;
   bps : int;
   samples : int32 array}

and interpolation =
  {c0 : float list;
   c1 : float list;
   n : float}

and stitching =
  {functions : t list;
   bounds : float list;
   stitch_encode : float list}

and pdf_fun_kind =
  | Interpolation of interpolation
  | Stitching of stitching
  | Sampled of sampled
  | Calculator of calculator list

and t =
  {func : pdf_fun_kind;
   domain : float list;
   range : float list option}
(** The type of functions. *)

(** Parse a function given a document and function object. *)
val parse_function : Pdf.t -> Pdf.pdfobject -> t

(** Raised from [eval_function] (see below) in the case of inputs which don't
match the evaluation *)
exception BadFunctionEvaluation of string

(** Evaluate a function given a list of inputs. *)
val eval_function : t -> float list -> float list

(** Flatten a function to its PDF representation *)
val pdfobject_of_function : Pdf.t -> t -> Pdf.pdfobject

(**/**)
val print_function : t -> unit