This file is indexed.

/usr/lib/ocaml/gnuplot/gnuplot_common.mli is in libgnuplot-ocaml-dev 0.8.3-3build2.

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
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
(* Copyright (C) 2001-2004

     Christophe Troestler
     email: Christophe.Troestler@umh.ac.be
     WWW: http://math.umh.ac.be/an/software/

   This library is free software; you can redistribute it and/or
   modify it under the terms of the GNU Lesser General Public License
   version 2.1 as published by the Free Software Foundation, with the
   special exception on linking described in file LICENSE.

   This library 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 file
   LICENSE for more details.
*)
(* $Id: gnuplot_common.mli,v 1.3 2007-11-27 23:07:22 chris_77 Exp $ *)

(** Functions in the Gnuplot module that do not depend on a particular
  datatype.

  @author Christophe Troestler (Christophe.Troestler(at)umh.ac.be)
*)
module type T =
sig

(** The [string] in the constructors is the name of the filename.
  [EPSLaTeX] creates two filenames: the given [string] is the name of
  the TeX file (a ".tex" extension will be added if not present); the
  EPS file name is constructed from it by changing the extension
  ".tex" to ".eps".  *)
type device =
    Gnuplot_common_.device =
  | X              (** On screen (X11, AQUA or windows depending on
                       your platform) *)
  | Wxt            (** Interactive and cross-platform terminal for on-screen
                       rendering based on Cairo. *)
  | PS of string   (** Postscript *)
  | EPS of string  (** Encapsulated PostScript *)
  | EPSLaTeX of string (** Picture environment including an EPS file. *)
  | FIG of string  (** Xfig format *)
  | PNG of string  (** Portable Network Graphics *)
  | MP of string   (** Metapost *)
  | MF of string   (** Metafont *)
  | SVG of string  (** Scalable Vector Graphics *)


type color = int
    (** Color, compatible with the [Graphics] module. *)

(** Gnuplot handle *)
type handle = Gnuplot_common_.handle

(** Style of plotting lines *)
type style = Gnuplot_common_.style =
    Lines | Linespoints | Points | Dots | Impulses


(** {2 Initializing, closing and moving around (sub)pages} *)

val device_of_filename : string -> device
  (** [device_of_filename f] guesses the device corresponding to the
    extension of [f].

    @raise Failure if none is found. *)

val init :
  ?offline:string -> ?max_inline:int -> ?persist:bool -> ?color:bool ->
  ?nxsub:int -> ?nysub:int -> ?xsize:float -> ?ysize:float -> ?aspect:float ->
  device -> handle
  (** [init ?offline ?max_inline ?persist ?color ?nsubx ?nsuby ?sizex
    ?sizey ?aspect dev] returns a handle to a new gnuplot session
    with device [dev].

    @param offline name of the script file (typically with extension ".plt").
                 If this parameter is given, gnuplot will not be called
                 but instead all commands and data will be written to the
                 script file.

    @param max_inline the data can be communicated to gnuplot through a
                 pipe or a file.  The pipe will be used if the number of
                 data lines to send is less or equal to [max_inline].
                 For example, if [max_inline] is set to [max_int], all data
                 will be transmitted through the pipe.

    @param persist says whether the plot window should stay after
                 the handle has been closed (default: [true]).
    @param color if [true], a color output (as opposed to a
                 monochrome one) will be produced (default = [true])

    @param nxsub number of horizontal subpages (default = 1)
    @param nysub number of vertical subpages (default = 1)

    @param xsize the horizontal size of the output; must be > 0
                 (default = 100. mm or 550. pixels)
    @param ysize the vertical size of the output; must be > 0
                 (default = 100. mm or 550. pixels)
    @param aspect the aspect ratio of the output, i.e. the ratio of the
                  height on the width of the output; must be > 0 (default = 1.)

    For [Gnuplot.X], [Gnuplot.PNG] and [Gnuplot.SVG] devices, the size
    is expressed in pixels, for the other drivers, it is expressed in
    milimeters.  One has to specify both [sizex] and [sizey], in which
    case [aspect] is ignored, or one of them and [aspect].  On Win32,
    [Gnuplot.X] may ignore the sizes (depending on your privileges).

    @raise Invalid_argument if any of the parameters does not satisfy
    the above constraints. *)

val close : handle -> unit
  (** [close g] closes the gnuplot session [g].

    @raise Failure if the gnupot process does exit properly.  *)


val adv : ?sub:int -> handle -> unit
  (** [adv g] advances to the next subpage or, if necessary, opens a
    new page.  [adv ~sub:i g] goes to the subpage [i] or, if [i] is
    too big or [i <= 0], it starts a new page.  Subpages are counted
    row by row, the top left one being numbered 1.  Beware that some
    output devices (e.g., PNG) do not support multipage output.  *)

val clear : handle -> unit
  (** [clear g] clears the current subpage. *)



(** {2 Pens and colors} *)

val pen : handle -> int -> unit
  (** [pen g i] selects the [i]th pen type for the handle [g] -- [i]
    can at least take the values from 0 to 6 but some devices may
    allow a bigger range.
    @deprecated use [color] instead.*)
val color : handle -> color -> unit
  (** [color g c] use the RGB color [c] active for the subsequent drawings
      on the handle [g].  *)
val pen_width : handle -> float -> unit
  (** [pen_width g w] sets the pen thickness to [w] (in multiples of
    the default pen size) for the handle [g].  Note that some devices
    (e.g. PNG) do not obey such command -- this is a gnuplot
    limitation. *)
val point : handle -> int -> unit
  (** [point g i] selects the [i]th point type for the handle [g]. *)
val point_width : handle -> float -> unit
  (** [point_width g w] sets the point thickness to [w] (in multiples
    of the default point size) for the handle [g]. *)
val font : handle -> string -> unit
  (** [font g s] sets the current font for the handle [g] as [s] where
    [s] is device and system dependent. *)
val font_size : handle -> int -> unit
  (** [font_size g sz] sets the current font size for the handle [g]
    to [sz].  Negative or null values select the default size.  Note
    that the default font on some devices is not scalable -- thus the
    font size may seem to have no effect. *)


(** {2 Text} *)

val title : handle -> string -> unit
  (** [title g t] sets the title for the current subpage of the
    gnuplot session [g] to [t]. *)
val xlabel : handle -> string -> unit
  (** [xlabel g t] sets the label for x axis of the current subpage of
    the gnuplot session [g] to [t]. *)
val ylabel : handle -> string -> unit
  (** [ylabel g t] sets the label for y axis of the current subpage of
    the gnuplot session [g] to [t]. *)


type coord =
  | Graph    (** The coordinates of the last labelled axis *)
  | Viewport (** The area delimited by the borders, (0,0) being the
               bottom left corner and (1,1) the top right corner. *)
  | Subpage (** Subpage coordinates with (0,0) being the bottom left
              corner and (1,1) the top right corner. *)
  | World (** The entire graph with (0,0) being the bottom left corner
            and (1,1) the top right corner. *)

val text : handle -> ?tag:int -> ?frame:float -> ?rotate:float ->
  ?coord:coord -> float -> float -> string -> unit
  (** [text g x y text] write the string [text] at position ([x],[y])
    in grah coordinates on the gnuplot session [g].  Graph coordinates
    mean that ([x], [y]) are (0., 0.) at the bottom left of the
    surrounding box and (1., 1.) at the top right.

    @param rotate in degrees *)


(** {2 Tags} *)

val show : ?immediately:bool -> ?tag:int -> handle -> unit
  (** [tag_show ?immediately ?tag g] shows the plots handled by that
    tag.
    @param immediately (Default: true).
    @raise Invalid_argument if [t] is the system tag [0]. *)

val hide : ?immediately:bool -> ?tag:int -> handle -> unit

val auto : tag:int -> handle -> unit

val free : tag:int -> handle -> unit


(** {2 2D world coordinates, axes,...} *)

val win : handle -> float -> float -> float -> float -> unit
  (** [win g xmin xmax ymin ymax] sets the x and y ranges for the
    current subpage of the handle [g]. *)

type axis_opt
type border_loc = int list
    (** List of numbers among 1, 2, 3 and 4 corresponding to border
      locations.  In 2D, 1 denotes the left or bottom axis and 2 the
      right or top axis. *)

val axis : ?which:border_loc -> unit -> axis_opt
  (** [axis ?which ()] sets the zero axis.
    @param which is a list of the border numbers.  *)

val border : ?which:border_loc -> unit -> axis_opt
  (** [border ?which ()] set borders to the graph.
    @param which is a list of the border numbers. *)

val tics : ?which:border_loc -> ?outward:bool -> ?grid:bool ->
  ?minor:int -> ?minor_grid:bool -> ?log:bool -> ?step:float -> unit
  -> axis_opt
  (** [tics ?which ?outward ?minor ?grid ?log ?step ()]

    @param which a list of the border numbers.
    @param outward whether the tics point outside the border (default: false).
                 Beware this is a global setting for gnuplot, so all the tics
                 will be affected.
    @param grid  whether to draw a grid at each major tic (default: [false]).
    @param minor set the number of sub-intervals (not the number of
                 minor tics) between two major tics (default: 1 which
                 means no minor tics).
    @param minor_grid whether to draw a grid at each minor tic
                 (default: [false]).
    @param log   whether to enable log scaling.
    @param step  step between two consecutive tics. *)

val labels : ?which:border_loc -> ?prec:int -> ?rotate:bool -> unit
  -> axis_opt
  (** [labels ?which ?prec ?rotate ()] set the numeric labels
    accroding to the following parameters:

    @param which a list of the border numbers;
    @param prec  precision of the numeric labels;
    @param rotate rotate the labels of 90 degrees w.r.t. their usual position.
  *)

val box : ?x:axis_opt list -> ?y:axis_opt list -> handle -> unit

val env : handle ->
  ?xaxis:bool -> ?xgrid:bool -> ?xlog:bool -> float -> float ->
  ?yaxis:bool -> ?ygrid:bool -> ?ylog:bool -> float -> float -> unit
  (** [env g ?xaxis ?xgrid ?xlog xmin xmax ?yaxis ?ygrid ?ylog ymin
    ymax] is a convenience function to set the x and y ranges as well
    as some common parameters (using [win] and [box] separately is
    more powerful).

    @param xaxis displays the x axis (default: false)
    @param xgrid displays a grid at each x tic (default: false)
    @param xlog  select a logarithmic scaling for the x axis (default: false)
    @param yaxis displays the y axis (default: false)
    @param ygrid displays a grid at each y tic (default: false)
    @param ylog  select a logarithmic scaling for the y axis (default: false)
  *)



(** {2 2D Plots } *)

val fx : handle -> ?tag:int -> ?style:style -> ?label:string ->
  ?nsamples:int -> (float -> float) -> float -> float -> unit
  (** [fx g ?style ?label ?nsamples f a b] draws the graph of [f] over
    the interval going from [a] to [b] (inclusive).

    @param style style of the graph (default: [Lines])
    @param label label for this graph (default: none)
    @param nsamples number of points at which [f] is evaluated (default: 100)
  *)

val xy_param : handle -> ?tag:int -> ?style:style -> ?label:string ->
  ?nsamples:int -> (float -> float * float) -> float -> float -> unit
  (** [xy_param g ?tag ?style ?label ?nsamples f a b] draws the image
    of the function [f] (i.e., the cuve parametrized by [f]) over the
    interval going from [a] to [b] (inclusive).

    @param style style of the graph (default: [Lines])
    @param label label for this graph (default: none)
    @param nsamples number of points at which [f] is evaluated (default: 100)
  *)


val xy_file : handle -> ?tag:int -> ?style:style -> ?label:string ->
  string -> unit


(** {2 3D world coordinates, axes,...} *)

val box3 : ?x : axis_opt list -> ?y : axis_opt list -> ?z : axis_opt list ->
  handle -> unit

val env3 : handle ->
  ?xaxis:bool -> ?xgrid:bool -> ?xlog:bool -> float -> float ->
  ?yaxis:bool -> ?ygrid:bool -> ?ylog:bool -> float -> float ->
  ?zaxis:bool -> ?zgrid:bool -> ?zlog:bool -> float -> float -> unit
  (** [env g ?xgrid ?xlog xmin xmax ?ygrid ?ylog ymin ymax] sets x and
    y ranges. *)


(** {2 3D Plots} *)

val fxy : handle -> ?tag:int -> ?style:style -> ?label:string ->
  ?xnsamples:int -> ?ynsamples:int ->
  (float -> float -> float) -> float -> float -> float -> float
  -> unit
  (** [fxy g ?style ?label ?hidden ?xnsamples ?ynsamples f xmin xmax
    ymin ymax] *)

val fxy_param : handle -> ?tag:int -> ?style:style -> ?label:string ->
  ?xnsamples:int -> ?ynsamples:int ->
  (float -> float -> float * float * float) ->
  float -> float -> float -> float -> unit
  (** [fxy_param g ?style ?label ?hidden ?xnsamples ?ynsamples f xmin xmax
    ymin ymax] *)

val xyz_ft : handle -> ?tag:int -> ?style:style -> ?label:string ->
  ?tnsamples:int -> (float -> float * float * float) -> float -> float -> unit

end