/usr/lib/ocaml/ocsigenserver/ocsigen_senders.mli is in libocsigenserver-ocaml-dev 2.2.0-3.
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 | (* Ocsigen
* http://www.ocsigen.org
* sender_helpers.ml Copyright (C) 2005 Denis Berthod
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU Lesser General Public License as published by
* the Free Software Foundation, with linking exception;
* either version 2.1 of the License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
(** Functions to create results for various kinds of documents *)
module File_content : Ocsigen_http_frame.HTTP_CONTENT
with type t =
string * Ocsigen_charset_mime.charset_assoc * Ocsigen_charset_mime.mime_assoc
module Xhtml_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = Xhtml.M.doc
module Html5_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = Html5.M.doc
module Make_XML_Content(Xml : Xml_sigs.Iterable)
(Typed_xml : Xml_sigs.Typed_xml with module Xml := Xml) :
Ocsigen_http_frame.HTTP_CONTENT
with type t = Typed_xml.doc
and type options = Http_headers.accept Lazy.t
(** content * content-type *)
module Text_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = string * string
module Stream_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = string Ocsigen_stream.t
(** streams and content-type *)
module Streamlist_content :
Ocsigen_http_frame.HTTP_CONTENT
with type t = (unit -> string Ocsigen_stream.t Lwt.t) list
* string
module Empty_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = unit
(** directory name and corresponding URL path *)
module Directory_content :
Ocsigen_http_frame.HTTP_CONTENT with type t = string * string list
(** error code and/or exception *)
module Error_content :
Ocsigen_http_frame.HTTP_CONTENT
with type t = int option * exn option * Ocsigen_cookies.cookieset
(** Sending an error page *)
val send_error :
?code:int ->
?exn:exn ->
Ocsigen_http_com.slot ->
clientproto:Ocsigen_http_frame.Http_header.proto ->
?mode:Ocsigen_http_frame.Http_header.http_mode ->
?proto:Ocsigen_http_frame.Http_header.proto ->
?cookies:Ocsigen_cookies.cookieset ->
head:bool ->
sender:Ocsigen_http_com.sender_type ->
unit ->
unit Lwt.t
|