Module Iconv

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 : string;
   mutable inbuf_offset : int;
   mutable inbytesleft : int;
   mutable outbuf : bytes;
   mutable outbuf_offset : int;
   mutable outbytesleft : int;
}
val iconv : iconv_t ->
iconv_fields -> [> `illegal_sequence | `ok | `overflow | `truncated ]
val iconv_end : iconv_t ->
iconv_fields -> [> `ended | `illegal_sequence | `overflow ]
val iconv_gen : bool ->
iconv_t ->
iconv_fields ->
[> `ended | `illegal_sequence | `ok | `overflow | `truncated ]
val iconv_substitute : iconv_t -> iconv_fields -> [> `ok | `overflow | `truncated ]
val iconv_substitute_end : iconv_t -> iconv_fields -> [> `ended | `overflow ]
val iconv_substitute_gen : bool ->
iconv_t ->
iconv_fields -> [> `ended | `ok | `overflow | `truncated ]
val iconv_unshift : iconv_t -> iconv_fields -> [> `ok | `overflow ]
val iconv_replace : iconv_t -> iconv_fields -> [> `ok | `overflow ]

Substitute an illegal sequence. iconv_replace cd fields does iconv_unshift cd first, then puts substitute cd to the output part of fields, and skips min_sequence_in_fromcode cd characters of the input part of fields.

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 
type iconv_decode = private iconv_t * iconv_decode_state 
val iconv_open_decode : fromcode:string -> iconv_decode
type iconv_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