This file is indexed.

/usr/lib/ocaml/equeue-ssl/uq_ssl.mli is in libocamlnet-ssl-ocaml-dev 3.4.1-2build2.

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
(* $Id: uq_ssl.mli 1607 2011-05-25 16:54:21Z gerd $ *)

(** Asynchronous SSL connections *)

exception Ssl_error of Ssl.ssl_error
  (** Used in [when_done] callbacks to indicate an SSL-specific error code *)


type ssl_socket_state =
    [ `Unset | `Client | `Server | `Unclean | `Clean ]

(** The [ssl_multiplex_controller] is an extended multiplex controller
  * which can also control SSL handshakes.
  *
  * Important note: SSL/TLS does not support half-open connections. When
  * one party closes the connection, the other party must immediately 
  * close the connection, too, throwing away any pending writes. See
  * RFC 2246.
 *)
class type ssl_multiplex_controller =
object
  inherit Uq_engines.multiplex_controller

  method ssl_socket : Ssl.socket

  method ssl_socket_state : ssl_socket_state
    (** Returns the socket state:
      * - [`Unset]: A fresh socket
      * - [`Client]: A socket playing the SSL client role
      * - [`Server]: A socket playing the SSL server role
      * - [`Unclean]: The socket state is unclean. The socket is no longer usable.
      * - [`Clean]: The SSL connection has been cleanly shut down.
      *)


  method ssl_connecting : bool
    (** Whether the initial SSL handshake is in progress that makes this
      * socket a client.
     *)

  method ssl_accepting : bool
    (** Whether the initial SSL handshake is in progress that makes this
      * socket a server.
     *)

  method start_ssl_connecting : 
    when_done:(exn option -> unit) -> unit -> unit
    (** Makes the socket an SSL client socket by initiating the handshake.
      * The [when_done] callback is invoked when the handshake is done.
      *
      * One can neither read nor write before that.
     *)

    (* CHECK: When SSL_connect returns 0, the connection is not established,
     * but the O'Caml function does not indicate this.
     *)

  method start_ssl_accepting :
    when_done:(exn option -> unit) -> unit -> unit
    (** Makes the socket an SSL server socket by initiating the handshake.
      * The [when_done] callback is invoked when the handshake is done.
      *
      * One can neither read nor write before that.
     *)

    (* CHECK: When SSL_accept returns 0, the connection is not established,
     * but the O'Caml function does not indicate this.
     *)

    (* Notes:
     * CHECK:
     * - It is not possible to shut down the SSL connection only for writing.
     * - 
     *)
end




val create_ssl_multiplex_controller : 
       ?close_inactive_descr:bool ->
       ?preclose:(unit -> unit) ->
       ?initial_state:ssl_socket_state ->
       ?timeout:(float * exn) ->
       Unix.file_descr -> Ssl.context -> Unixqueue.event_system ->
         ssl_multiplex_controller
  (** Creates a multiplex controller for an SSL socket. The descriptor must
    * be a connected socket descriptor.
    *
    * [close_inactive_descr]: Whether to close the file descriptor by
    * [inactivate].
    *
    * [preclose]: This function is called immediately before closing
    * the descriptor
    *
    * [initial_state]: can be set to [`Client] or [`Server] if the context
    * is already established. Defaults to [`Unset]
    *
    * [timeout]: if set to [(t, x)], started operations time out after [t]
    * seconds and pass the exception [x] back. A timeout is only indicated
    * when all started operations are inactive for [t] seconds.
   *)

val ssl_connect_engine : 
       ssl_multiplex_controller -> unit Uq_engines.engine
  (** This engine performs the client handshake. *)

val ssl_accept_engine : 
       ssl_multiplex_controller -> unit Uq_engines.engine
  (** This engine performs the server handshake. *)



(** {1 Debugging} *)

module Debug : sig
  val enable : bool ref
    (** Enables {!Netlog}-style debugging of this module *)
end