This file is indexed.

/usr/lib/ocaml/bz2/bz2.mli is in libbz2-ocaml-dev 0.6.0-6+b3.

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
(* CamlBZ2 - OCaml bindings for libbz2 (AKA, bzip2)
 *
 * Copyright © 2000-2005 Olivier Andrieu    <oandrieu@gmail.com>
 *           © 2008      Stefano Zacchiroli <zack@upsilon.cc>
 *
 * CamlBZ2 is free software; you can redistribute it and/or modify it
 * under the terms of the GNU Lesser General Public License (with the
 * special exception on linking described in file COPYING) as published
 * by the Free Software Foundation; either version 2.1 of the License,
 * or (at your option) any later version.
 *)

(** {1 Bzip2 interface} *)

(** The module [Bz] provides a basic interface to the [bzip2]
    compression library. *)

(** {2 Datatypes & exceptions} *)

type in_channel
type out_channel

exception IO_error of string
  (** Exception [IO_error] is raised when there is an error reading or
      writing on a compressed channel ; the string argument is the message
      reported by the OS. *)

exception Data_error
  (** Exception [Data_error] is raised when a data integrity error is
      detected during decompression. *)

exception Unexpected_EOF
  (** Exception [Unexpected_EOF] is raised when an [in_channel]
      finishes before the logical end of stream is detected. *)

(** When any of these exception is raised, the channel is
    automatically closed (but you still have to close the Pervasives
    channel). *)

val version : string
  (** Version of the underlying [bzip2] library. *)

(** {2 File I/O} *)

(** {3 File input} *)

(** [open_in ic] opens a compressed stream reading from the
    [Pervasives] input channel [ic].

    @param small when [true] requests usage of a different method for
    decompressing that is slower but uses less memory. Defaults:
    [false]
*)
external open_in : ?small:bool -> ?unused:string -> Pervasives.in_channel ->
  in_channel 
  = "mlbz_readopen"

(** [read buf pos len] reads up to [len] characters and store them in
    the string buffer [buf], starting at position [pos].

    @return number of bytes actually read, (a value strictly less than
    [len] means end of stream).

    @raise End_of_file if end of stream was already reached. *)
external read : in_channel -> string -> int -> int -> int
  = "mlbz_read"

(** If there's some data after the compressed stream that you want to
    read from the same [Pervasives] [in_channel], use
    [read_get_unused]. *)
external read_get_unused : in_channel -> string
  = "mlbz_readgetunused"

external close_in : in_channel -> unit
  = "mlbz_readclose"

(** {3 File output} *)

(** [open_out oc] creates an [out_channel] writing to the [Pervasives]
    output channel [oc]. Once the write operations are finished and
    the compressed channel is closed, it is possible to continue
    writing on the [Pervasives] channel. However, reading back
    requires special care (cf. above).

    @param block block size to use for compresion. It is a value
    between 1 and 9 inclusive. 9 is the default and provides best
    compression but takes most memory. *)
external open_out : ?block:int -> Pervasives.out_channel -> out_channel
  = "mlbz_writeopen"

(** [write oc buf pos len] writes [len] characters, coming from [buf]
    and starting at position [pos], to [oc] *)
external write : out_channel -> string -> int -> int -> unit
  = "mlbz_write"

external close_out : out_channel -> unit
  = "mlbz_writeclose"


(** {2 In-memory compression} *)

(** These functions compress to/decompress from string buffers. *)

(** [compress buf pos len] compress a data chunk coming from [buf],
    [len] character long, and starting at [pos].

    @return compressed data chunk as string *)
external compress : ?block:int -> string -> int -> int -> string
  = "mlbz_compress"

(** [uncompress buf pos len] uncompress a data chunk comfing from
    [buf], [len] character long, and starting at [pos].

    @param small see [Bz2.open_in] above
    @return uncompressed data chunk as string *)
external uncompress : ?small:bool -> string -> int -> int -> string
  = "mlbz_uncompress"