This file is indexed.

/usr/lib/ocaml/camlimages/gif.mli is in libcamlimages-ocaml-dev 1:4.2.0-1.1build3.

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
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*            François Pessaux, projet Cristal, INRIA Rocquencourt     *)
(*            Pierre Weis, projet Cristal, INRIA Rocquencourt          *)
(*            Jun Furuse, projet Cristal, INRIA Rocquencourt           *)
(*                                                                     *)
(*  Copyright 1999-2004,                                               *)
(*  Institut National de Recherche en Informatique et en Automatique.  *)
(*  Distributed only by permission.                                    *)
(*                                                                     *)
(***********************************************************************)

(* $Id: gif.mli,v 1.1 2007/01/18 10:29:57 rousse Exp $ *)

(** High level interfaces *)
type gif_extension = 
   | GifComment of string list
   | GifGraphics of string list
   | GifPlaintext of string list
   | GifApplication of string list
   | GifOtherExt of int * string list;;

type gif_frame = {
  frame_left : int;
  frame_top : int;
  frame_bitmap : Index8.t;
  mutable frame_extensions : gif_extension list;
  frame_delay : int;
};;

type gif_sequence = {
  screen_width : int;
  screen_height : int;
  screen_colormap : Color.rgb Color.map;
  frames : gif_frame list;
  loops : int;
};;

val check_header : string -> Images.header;;
  (** Checks the file header *)

val load : string -> Images.load_option list -> gif_sequence
  (** Loads a gif image sequence *)
val load_sequence : string -> Images.load_option list -> Images.sequence
  (** Loads a gif image sequence, but to more general type *)
val load_first : string -> Images.load_option list -> Images.t
  (** Loads the first frame of a gif image sequence. *)
val save : string -> Images.save_option list -> gif_sequence -> unit
  (** Saves a gif image sequence *)
val save_image : string -> Images.save_option list -> Images.t -> unit
  (** Saves an image as a gif file with only one frame *)

(*** Below they are all low level interfaces *)

type in_channel;;
type out_channel;;

type screen_info = {
  s_width : int;
  s_height : int;
  s_color_resolution : int;
  s_back_ground_color : int;
  s_colormap : Color.rgb array;
};;

type record_type =
  | Undefined
  | Screen_desc
  | Image_desc
  | Extension
  | Terminate;;

type gif_desc = {
  desc_left : int;
  desc_top : int;
  desc_width : int;
  desc_height : int;
  desc_interlace : bool;
  desc_colormap : Color.rgb array;
};;

val dGifOpenFileName : string -> screen_info * in_channel;;
val dGifCloseFile : in_channel -> unit;;
val dGifGetRecordType : in_channel -> record_type;;
val dGifGetImageDesc : in_channel -> gif_desc;;
val dGifGetLine : in_channel -> string;;
val dGifGetExtension : in_channel -> int * string list;;

val eGifOpenFileName : string -> out_channel;;
val eGifCloseFile : out_channel -> unit;;
val eGifPutScreenDesc : out_channel ->screen_info -> unit;;
val eGifPutImageDesc : out_channel -> gif_desc -> unit;;
val eGifPutLine : out_channel -> string -> unit;;
val eGifPutExtension : out_channel -> int * string list -> unit;;