This file is indexed.

/usr/lib/ocaml/camlimages/bitmap.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
 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
(***********************************************************************)
(*                                                                     *)
(*                           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: bitmap.mli,v 1.5 2009/07/04 03:39:28 furuse Exp $*)
 
(* Bitmaps used in images.
   Bitmaps are partitioned into blocks. Usually only one block is 
   allocated for one image, but for huge images, they needs more... *)

val debug : bool ref;;

(* see Swap to set swap file directory *)

val maximum_live : int ref;;
val maximum_block_size : int ref;;
  (* Configuration parameters for image swapping.

     You can specify the maximum size of live data by setting [maximum_live]
     in words. If the size of live data in heap exceeds [maximum_live], then
     Camlimages library tries to escape part of image buffer into "swap" 
     files. If swapped data are required, they are read back into memory.
     This swapping is automatically done by the camlimages library.
     If [maximum_live] is 0, image swapping is disabled.

     Swapped images are separated into block shaped "partitions". 
     [maximum_block_size] is a maximum size of each partition, also in 
     words. This parameter may affect the swapping performance. There is
     no theory (yet) how we should specify it. The author of the library
     propose to have (!maximum_live / 10). If it is larger, each swapping 
     becomes slower. If smaller, more swappings will occur. Too large and 
     too small maximum_block_size, both may make the program slower.

     If you use image swapping, you need to explicitly call [destroy]
     function of each image format (Rgb24.destroy, image#destroy, etc...)
     to free the memory and swap files of the needless images.

     The defaults are both 0. (i.e. swapping is disabled ) *)

module Block : sig
  type t = {
    width : int;
    height : int;
    x : int;
    y : int;
    dump : bytes;
  }
end

module type Bitdepth = sig
  val bytes_per_pixel : int
end;;

module Make(B:Bitdepth) : sig
  type t;;
  (* Bitmap type *)

  val create : int -> int -> bytes option -> t
    (* [create width height initopt] creates a bitmap of size
       [width] x [height]. You can set [initopt] the value to 
       fill the bitmap *)

  val create_with : int -> int -> bytes -> t
    (* [create_with width height initdata] creates a bitmap whose
        initial data is [initdata]. *)

  val create_with_scanlines : int -> int -> bytes array -> t

  val destroy : t -> unit
    (* Destroy bitmaps *)

  val access : t -> int -> int -> bytes * int

  val get_strip : t -> int -> int -> int -> bytes
  val set_strip : t -> int -> int -> int -> bytes -> unit
    (* Strip access
       Here, "strip" means a rectangle region with height 1.
  	 [get_strip t x y w] returns the bytes reprensentation of strip of [t]
       at (x, y) - (x + w - 1, y).
  	 [set_strip t x y w str] write [str] to the strip of [t]
       at (x, y) - (x + w - 1, y).
    *)
 
  val get_scanline : t -> int -> bytes
  val set_scanline : t -> int -> bytes -> unit
    (* Scanline access 
  	 [get_scanline t y] returns the bytes representation of the scanline
       of [t] at [y].
  	 [set_scanline t y str] writes [str] to the scanline of [t] at [y].
    *)

  (* only for one row *)      
  val get_scanline_ptr : t -> (int -> (bytes * int) * int) option

  val dump : t -> bytes
    (* Create a bytes representation of a bitmap. It may easily raise
       an exception Out_of_memory for large images. *)

  val copy : t -> t

  val sub : t -> int -> int -> int -> int -> t
    (* [sub src x y width height] returns sub-bitmap of [src],
       at (x, y) - (x + width - 1, y + height - 1). *)

  val blit : t -> int -> int -> t -> int -> int -> int -> int -> unit
    (* [blit src sx sy dst dx dy width height] copies the rectangle
       region of [src] at
       (sx, sy) - (sx + width - 1, sy + height - 1)
       to [dst], at
       (dx, dy) - (dx + width - 1, dy + height - 1) *)

  val blocks : t -> int * int
    (* returns number of blocks in row and column *)  

  val dump_block : t -> int -> int -> Block.t
end;;