/usr/lib/ocaml/cairo/svg_cairo.mli is in libcairo-ocaml-dev 1:1.2.0-6build3.
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 | (**************************************************************************)
(* cairo-ocaml -- Objective Caml bindings for Cairo *)
(* Copyright © 2004-2005 Olivier Andrieu *)
(* *)
(* This code is free software and is licensed under the terms of the *)
(* GNU Lesser General Public License version 2.1 (the "LGPL"). *)
(**************************************************************************)
(** Rendering SVG documents with
cairo *)
type status =
SUCCESS
| NO_MEMORY
| IO_ERROR
| FILE_NOT_FOUND
| INVALID_VALUE
| INVALID_CALL
| PARSE_ERROR
exception Error of status
val init : unit
type t
external create : unit -> t = "ml_svg_cairo_create"
(** {3 Parsing} *)
external parse : t -> string -> unit = "ml_svg_cairo_parse"
external parse_string : t -> string -> unit = "ml_svg_cairo_parse_buffer"
external parse_chunk_begin : t -> unit = "ml_svg_cairo_parse_chunk_begin"
external parse_chunk : t -> string -> int -> int -> unit = "ml_svg_cairo_parse_chunk"
external parse_chunk_end : t -> unit = "ml_svg_cairo_parse_chunk_end"
(** {3 Rendering} *)
external render : t -> Cairo.t -> unit = "ml_svg_cairo_render"
external set_viewport_dimenstion : t -> int -> int -> unit = "ml_svg_cairo_set_viewport_dimension"
external get_size : t -> int * int = "ml_svg_cairo_get_size"
|