/usr/lib/ocaml/dose2/io.mli is in libdose2-ocaml-dev 1.4.2-6build1.
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 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 | (* Copyright 2005-2007 Berke DURAK.
This file is part of Dose2.
Dose2 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, either version 3 of the License, or
(at your option) any later version.
Dose2 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, see <http://www.gnu.org/licenses/>. *)
(** General structured I/O module.
This module defines the base types and combinators that you can use to build literates for your data type.
A literate for a type ['a] is someone who can both read and write values of type ['a] over arbitrary
fragment channels (which are defined in the module [Fragments].)
Once you have defined a literate, you can use it to do I/O over any kind of fragment channel. Basic fragment
channels (pretty-printed, human-readable ASCII ; binary and XML) are defined in the modules Human_io, Binary_io and
XML_io. You can also mix channel kinds and for instance read from binary fragment channels and write to ASCII
fragment channels.
To do IO with a type
[type foo = (int * (float list) * (string option list)) option array]
you must :
- Define a literate for your data type, usually using the combinators [io_pair], [io_list], etc.:
[
let io_foo =
io_array (io_option
io_int
(io_list io_float)
(io_list (io_option io_string)))
;;
]
- If you want to save your data, get a channel to save.
[ ]
*)
type io_in = Fragments.io_in
type io_out = Fragments.io_out
exception Unknown_constructor
(** When reading sum types, raise this exception if you are given an unknown constructor name. *)
type 'a r = io_in -> 'a
(** The type of readers. A reader takes an input channel and returns a value. *)
type 'a w = 'a -> io_out -> unit
(** Type type of writers. A writer takes a value, an output channel and returns nothing. *)
type 'a literate = 'a r * 'a w
(** A literate is something that can both read and write. *)
type 'a sum_io_spec = (string -> 'a r) * ('a -> string * (io_out -> unit))
(** The description of a sum type, to be passed to [io_sum] to build a literate for the given type.
It is a pair [(reader,writer)] where [reader] is first given the name of the constructor
and has to return a reader that will read the arguments of the constructor and apply
the constructor to return a value of type ['a]. [writer] pattern-matches the sum
type and returns a pair [(name, writer')] where [name] is a string encoding the name
of the constructor, and [writer'] is a writer for the arguments (which therefore have
to be curryfied.
For instance, the specifier for the ['a option] type is defined as:
[ (function
| "none" -> fun i -> None
| "some" -> fun i -> Some(read xio i)
| _ -> raise Unknown_tag),
(function
| None -> "none", write io_unit ()
| Some x -> "some", write xio x)
] *)
type 'a record_io_spec =
(string * ('a -> io_in -> 'a) * ('a -> io_out -> unit)) list
(** The description of a record type, to be passed to [io_record] to build a literate for
that record type. This is a list of triplets
[[(field1,reader1,writer1); (field2,reader2,writer2); ...]]
where [fieldi] is an identifiers for the field,
[readeri] takes the current value of the record,
and updates it by reading a value for the field [fieldi],
and [writeri] takes a record and an output channel and writes its
field [fieldi]. *)
type ('thing,'bag) iterator = 'bag -> ('thing -> unit) -> unit
(** An iterator takes a bag, a function, and runs the function over the elements of the bag. *)
type ('thing,'bag) builder = unit -> ('thing -> unit) * (unit -> 'bag)
(** A builder takes unit and returns a pair [(add,get)] where [add] is a function that adds
one element to the bag and [get] returns the contents of the bag. *)
type ('thing,'bag) collection_io_spec = 'thing literate * ('thing,'bag) iterator * ('thing,'bag) builder
(** The specification type for an abstract collection of things of type ['thing] is made of a literate for the
type ['thing], an iterator and a builder. *)
val assoc3 : 'a -> ('a * 'b * 'c) list -> 'b * 'c
val read : 'a literate -> io_in -> 'a
(** [read lit ch] reads a value from the channel [ch] using the literate [lit]. For instance,
[read io_int ch] returns an integer. *)
val write : 'a literate -> 'a -> io_out -> unit
(** [write lit v ch] writes the value [v] to the channel [ch] using the literate [lit]. For example,
[write io_int 33 ch] writes the integer [33] to the channel [ch]. *)
val write_and_flush : 'a literate -> 'a -> io_out -> unit
val finish : io_in -> unit
(** [finish ch] finishes reading the input channel. Actually, it reads the Stop_data tag. *)
val flush : io_out -> unit
(** [flush ch] flushed the output channel. Actually, it emits the Stop_data tag and flushes the I/O buffers. *)
val io_int : int literate
(** The literate for integers. *)
val io_int64 : int64 literate
(** The literate for 64-bit integers. *)
val io_string : string literate
(** The literate for strings. *)
val io_char : char literate
(** The literate for characters. *)
val io_bool : bool literate
(** The literate for booleans. *)
val io_float : float literate
(** The literate for floats. *)
val io_unit : unit literate
(** The literate for values of type unit. Actually, this one does nothing. *)
val io_convert : ('a -> 'b) -> ('b -> 'a) -> 'a literate -> 'b literate
(** Given a function [f : 'a -> 'b] its inverse [g : 'b -> 'a] and a literate [io] for ['a]
creates a literate for ['b]. *)
val io_pair : 'a literate -> 'b literate -> ('a * 'b) literate
(** The literate constructor for pairs. [io_pair lit1 lit2] takes literates [lit1] and [lit2] for types
['a] and ['b] and returns a literate for the type ['a * 'b]. *)
val io_triple : 'a literate -> 'b literate -> 'c literate -> ('a * 'b * 'c) literate
(** The literate constructor for triples. *)
val io_quadruple : 'a literate -> 'b literate -> 'c literate -> 'd literate -> ('a * 'b * 'c * 'd) literate
(** The literate constructor for quadruples. *)
val io_list : 'a literate -> 'a list literate
(** The literate constructor for lists. For example, [io_list io_int] is a literate able to read and write
lists of integers. *)
val io_array : 'a literate -> 'a array literate
(** The literate constructor for arrays. *)
val io_hashtbl : 'a literate -> 'b literate -> ('a, 'b) Hashtbl.t literate
(** The literate constructor for hash tables from the module Hashtbl.t. *)
val io_record : 'a record_io_spec -> 'a -> 'a literate
(** The literate constructor for records. Due to the nature of the Ocaml language, you have to provide a
[record_io_spec] describing your record. *)
val io_collection : ('thing,'bag) collection_io_spec -> 'bag literate
(** The literate constructor for abstract collections. *)
val io_sum : 'a sum_io_spec -> 'a literate
(** The literate constructor for sum types. Due to the nature of the Ocaml language, you have to provide a
[record_io_spec] describing your sum type. *)
val io_option : 'a literate -> 'a option literate
(** The literate constructor for the ['a option] sum type. *)
val io_not_implemented : 'a literate
(** Use this when you need to declare a literate but don't want to implement one. *)
val convert : reader:io_in -> writer:io_out -> unit -> unit
(** This function will copy data from [reader] to [writer]. This can be used to convert data between different
formats (e.g., pretty-printed to XML, or XML to binary, etc.) Note that it is not necessary to have a literate
for the data to be converted. *)
val dump : reader:io_in -> unit -> unit
(** This debugging function will dump the tokens to [stdout]. *)
|