This file is indexed.

/usr/lib/ocaml/camlimages/oImages.mli is in libcamlimages-ocaml-dev 1:4.0.1-4build1.

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

(* $Id: oImages.mli,v 1.5 2009/03/01 11:24:10 furuse Exp $ *)

(** Class interface for Images *)

open Images;;
open Color;;

exception Non_supported_method;;
exception Wrong_image_class;;

type image_class = 
    ClassRgb24 
  | ClassIndex8 
  | ClassIndex16
  | ClassRgba32
  | ClassCmyk32;;

class type imgsize = object
  method width : int
  method height : int
end;;

class type ['a] map = object
  inherit imgsize

  method unsafe_get : int -> int -> 'a
  method unsafe_set : int -> int -> 'a -> unit
  method get : int -> int -> 'a
  method set : int -> int -> 'a -> unit
  method unsafe_access : int -> int -> string * int
end;;

class type oimage = object
  inherit imgsize

  method infos : info list
  method set_infos : info list -> unit

  method image_class : image_class
  method image : Images.t

  method destroy : unit
  method dump : string
      
  method save : string -> format option -> save_option list -> unit

  method coerce : oimage

  method blocks : int * int
  method dump_block : int -> int -> Bitmap.Block.t
end;;

class type rgba32_class = object
  inherit oimage
  inherit [Color.rgba] map

  method sub : int -> int -> int -> int -> rgba32_class
  method blit : int -> int -> rgba32_class -> int -> int -> int -> int -> unit
  method resize : (float -> unit) option -> int -> int -> rgba32_class
  method to_rgb24 : rgb24_class
end


and rgb24_class = object
  inherit oimage
  inherit [Color.rgb] map

  method sub : int -> int -> int -> int -> rgb24_class
  method blit : int -> int -> rgb24_class -> int -> int -> int -> int -> unit
  method resize : (float -> unit) option -> int -> int -> rgb24_class
  method to_rgba32 : rgba32_class
end;;

class rgba32_wrapper : Rgba32.t -> rgba32_class;;

class rgba32 : int -> int -> rgba32_class;;
class rgba32_filled : int -> int -> Color.rgba -> rgba32_class;;
class rgba32_with : int -> int -> Info.info list -> string -> rgba32_class;;

class rgb24_wrapper : Rgb24.t -> rgb24_class;;

class rgb24 : int -> int -> rgb24_class;;
class rgb24_filled : int -> int -> Color.rgb -> rgb24_class;;
class rgb24_with : int -> int -> Info.info list -> string -> rgb24_class;;

class type index8_class = object
  inherit oimage
  inherit [Index8.elt] map
  inherit OColor.rgbmap

  method sub : int -> int -> int -> int -> index8_class
  method blit : int -> int -> index8_class -> int -> int -> int -> int -> unit
  method get_color : int -> int -> Color.rgb
  method unsafe_get_color : int -> int -> Color.rgb
  method transparent : Index8.elt
  method set_transparent : Index8.elt -> unit
  method to_rgb24 : rgb24_class
  method to_rgba32 : rgba32_class
end;;

class index8_wrapper : Index8.t -> index8_class;;

class index8 : int -> int -> index8_class;;
class index8_filled : int -> int -> int -> index8_class;;
class index8_with : int -> int -> Info.info list -> 
  Color.rgb Color.map -> int -> string -> index8_class;;

class type index16_class = object
  inherit oimage
  inherit [Index16.elt] map
  inherit OColor.rgbmap

  method sub : int -> int -> int -> int -> index16_class
  method blit : int -> int -> index16_class -> int -> int -> int -> int -> unit
  method get_color : int -> int -> Color.rgb
  method unsafe_get_color : int -> int -> Color.rgb
  method transparent : Index16.elt
  method set_transparent : Index16.elt -> unit
  method to_rgb24 : rgb24_class
  method to_rgba32 : rgba32_class
end;;

class index16_wrapper : Index16.t -> index16_class;;

class index16 : int -> int -> index16_class;;
class index16_filled : int -> int -> int -> index16_class;;
class index16_with : int -> int -> Info.info list -> 
  Color.rgb Color.map -> int -> string -> index16_class;;

class type cmyk32_class = object
  inherit oimage
  inherit [Color.cmyk] map

  method sub : int -> int -> int -> int -> cmyk32_class
  method blit : int -> int -> cmyk32_class -> int -> int -> int -> int -> unit
  method resize : (float -> unit) option -> int -> int -> cmyk32_class
end;;

class cmyk32_wrapper : Cmyk32.t -> cmyk32_class;;

class cmyk32 : int -> int -> cmyk32_class;;
class cmyk32_filled : int -> int -> Color.cmyk -> cmyk32_class;;
class cmyk32_with : int -> int -> Info.info list -> string -> cmyk32_class;;

val rgb24 : oimage -> rgb24_class;;
val index8 : oimage -> index8_class;;
val index16 : oimage -> index16_class;;
val rgba32 : oimage -> rgba32_class;;
val cmyk32 : oimage -> cmyk32_class;;

type tagged = 
    Rgb24 of rgb24_class
  | Index8 of index8_class
  | Index16 of index16_class
  | Rgba32 of rgba32_class
  | Cmyk32 of cmyk32_class;;

val tag : oimage -> tagged;;
val make : Images.t -> oimage;;
val load : string -> Images.load_option list -> oimage;;
val sub : oimage -> int -> int -> int -> int -> oimage;;