module Iconv:sig
..end
val iconv_get_version_opt : unit -> (int * int) option
Return Some (minor, major)
if GNU libiconv is used, otherswise None
.
val iconv_get_version_string_opt : unit -> string option
type
iconv_t
val iconv_open : tocode:string -> fromcode:string -> iconv_t
val substitute : iconv_t -> string
val set_substitute : iconv_t -> string -> unit
val unexist : iconv_t -> [> `auto | `illegal_sequence ]
val set_unexist : iconv_t -> [< `auto | `illegal_sequence ] -> unit
Correspond to ICONV_SET_ILSEQ_INVALID
of Citrus.
Citrus iconv internally substitutes valid characters does not exist in
tocode
if `auto
.
It is always `illegal_sequence
in GNU libiconv or glibc.
val min_sequence_in_fromcode : iconv_t -> int
type
iconv_fields = {
|
mutable inbuf : |
|
mutable inbuf_offset : |
|
mutable inbytesleft : |
|
mutable outbuf : |
|
mutable outbuf_offset : |
|
mutable outbytesleft : |
}
val iconv : iconv_t ->
iconv_fields -> bool -> [> `illegal_sequence | `ok | `overflow ]
val iconv_substitute : iconv_t -> iconv_fields -> bool -> [> `ok | `overflow ]
val iconv_end : iconv_t -> iconv_fields -> [> `ok | `overflow ]
val iconv_reset : iconv_t -> unit
val iconv_substring : iconv_t -> string -> int -> int -> string
val iconv_string : iconv_t -> string -> string
type
iconv_decode_state
typeiconv_decode = private
iconv_t * iconv_decode_state
val iconv_open_decode : fromcode:string -> iconv_decode
typeiconv_decode_error =
[ `illegal_sequence | `none | `truncated ]
val iconv_decode : iconv_decode ->
('a -> 'b -> char) ->
('a -> 'b -> 'b) ->
('a -> 'b -> bool) ->
('a -> 'b -> 'b -> Stdlib.Uchar.t -> 'c) ->
fail:('a -> 'b -> 'b -> [> iconv_decode_error ] -> 'c) ->
'a -> 'b -> 'c
module Out_iconv: Iconv__Out_iconv