This file is indexed.

/usr/lib/ocaml/gnuplot/gnuplot.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
(* 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.
*)

(**
  Library for scientific plotting using gnuplot.

  This library implements a simple interface to the gnuplot program.
  All functions talk to gnuplot through a pipe, so crude animations
  are possible.

  @author Christophe Troestler (chris_77\@sourceforge.net)
  @version 0.8.3
*)


(** {2 Common functions} *)

include Gnuplot_common.T

(** {2 Bigarray interface} *)

module Bigarray :
sig
  include Gnuplot_common.T
  type 'a vec = (float, Bigarray.float64_elt, 'a) Bigarray.Array1.t
  type 'a mat = (float, Bigarray.float64_elt, 'a) Bigarray.Array2.t

  (** {3 2D Plots } *)

(* FIXME: doc needs updating *)
  val x : handle -> ?tag:int -> ?style:style -> ?label:string -> ?n0:int ->
    ?ofsx:int -> ?incx:int -> 'a vec -> unit
    (** [x g ?style ?label ?n0 xvec] draws the points ([n0 + i],
      [xvec.{i}]) for [0 <= i < Array1.dim xvec] according to the style
      chosen.  Infinite and NaN values will be shown as discontinuities
      (i.e., no line will join the points before and after such values).

      @param style style of the graph (default = [Lines])
      @param label label for this graph (default: none)
      @param n0 x-coordinate of the first elements in [xvec]
      (default = index of the first element of [xvec]) *)

  val xy : handle -> ?tag:int -> ?style:style -> ?label:string ->
    ?ofsx:int -> ?incx:int -> 'a vec ->
    ?ofsy:int -> ?incy:int -> 'a vec -> unit
    (** [xy g ?style ?label xvec yvec] draws the points ([xvec.{i}],
      [yvec.{i}]) for [0 <= i < min(Array1.dim xvec)(Array1.dim yvec)]
      according to the style chosen.

      @param style style of the graph (default = [Lines])
      @param label label for this graph (default: none) *)

  val bin : handle -> ?tag:int -> ?label:string -> ?center:bool ->
    ?ofsx:int -> ?incx:int -> 'a vec ->
    ?ofsy:int -> ?incy:int -> 'a vec -> unit

  val vector : handle -> ?tag:int -> ?label:string ->
    ?ofsx:int -> ?incx:int -> 'a vec -> ?ofsy:int -> ?incy:int -> 'a vec ->
    ?ofsdx:int -> ?incdx:int -> 'a vec -> ?ofsdy:int -> ?incdy:int ->
    'a vec -> unit

  val err : handle -> ?tag:int ->
    ?xerr:'a vec -> 'a vec -> ?yerr:'a vec -> 'a vec -> unit


  (** {3 3D Plots} *)

  val xyz : handle -> ?tag:int -> ?style:style -> ?label:string ->
    'a vec -> 'a vec -> 'a mat -> unit
    (** [xyz g ?style ?label x y z] *)

  (* val contour : handle ->  *)
end


(** {2 Array interface} *)

module Array :
sig
  include Gnuplot_common.T
  type vec = float array
  type mat = float array array

  (** {3 2D Plots } *)

  val x : handle -> ?tag:int -> ?style:style -> ?label:string -> ?n0:int ->
    ?ofsx:int -> ?incx:int -> vec -> unit
    (** See {!Gnuplot.Bigarray.x} *)

  val xy : handle -> ?tag:int -> ?style:style -> ?label:string ->
    ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec
    -> unit
    (** See {!Gnuplot.Bigarray.xy} *)

  val bin : handle -> ?tag:int -> ?label:string -> ?center:bool ->
    ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec
    -> unit
    (** See {!Gnuplot.Bigarray.bin} *)

  val vector : handle -> ?tag:int -> ?label:string ->
    ?ofsx:int -> ?incx:int -> vec -> ?ofsy:int -> ?incy:int -> vec ->
    ?ofsdx:int -> ?incdx:int -> vec -> ?ofsdy:int -> ?incdy:int -> vec
    -> unit
    (** See {!Gnuplot.Bigarray.vector} *)

  val err : handle -> ?tag:int ->
    ?xerr:vec -> vec -> ?yerr:vec -> vec -> unit
    (** See {!Gnuplot.Bigarray.err} *)

  (** {3 3D Plots} *)

  val xyz : handle -> ?tag:int -> ?style:style -> ?label:string ->
    vec -> vec -> mat -> unit
    (** See {!Gnuplot.Bigarray.xyz} *)
end


(** {2 Functorial interface} *)
(** REMARK: This interface should not be used if performance is crucial. *)

module type DATA =
sig
  type vec (** 1D vectors, y coordinate only *)
  val iter : (float -> unit) -> vec -> unit

  type vec2 (** 2D vectors, x and y coordinates *)
  val iter2 : (float -> float -> unit) -> vec2 -> unit

  type vec4
    (** 2D vectors with additional info, x and y coordinates plus two
      more fields (for vector coordinates, errors,...). *)
  val iter4 : (float -> float -> float -> float -> unit) -> vec4 -> unit

  type mat (** Matrix type *)
  val iter_mat : (float -> float -> float -> unit) ->
    vec -> vec -> mat -> unit
end
  (** The vector and matrix types together with their iterators.  *)

module type PLOT_DATA =
sig
  include Gnuplot_common.T
  type vec
  type vec2
  type vec4
  type mat

  val x : handle -> ?tag:int -> ?style:style -> ?label:string -> ?n0:int ->
    vec -> unit
    (** See {!Gnuplot.Bigarray.x} *)
  val xy : handle -> ?tag:int -> ?style:style -> ?label:string ->
    vec2 -> unit
    (** See {!Gnuplot.Bigarray.xy} *)
  val bin : handle -> ?tag:int -> ?label:string -> vec2 -> unit
    (** See {!Gnuplot.Bigarray.bin} *)
  val vector : handle -> ?tag:int -> ?label:string -> vec4 -> unit
    (** See {!Gnuplot.Bigarray.vector} *)
  val err : handle -> ?tag:int -> vec4 -> unit
    (** See {!Gnuplot.Bigarray.err} *)
  val xyz : handle -> ?tag:int -> ?style:style -> ?label:string ->
    vec -> vec -> mat -> unit
    (** See {!Gnuplot.Bigarray.xyz} *)
end
  (** The module type returned by functorial interface. *)

module Make(D : DATA) :
  (PLOT_DATA with type vec = D.vec
             and type vec2 = D.vec2
             and type vec4 = D.vec4
             and type mat = D.mat)
  (** Functor building a module to plot the data types described in [D]. *)