sig
  module Uint32 :
    sig
      type t [@@immediate64]
      val zero : Unicode.Uint32.t
      val compare : Unicode.Uint32.t -> Unicode.Uint32.t -> int
      val equal : Unicode.Uint32.t -> Unicode.Uint32.t -> bool
      val of_int : int -> Unicode.Uint32.t
      val of_int32 : int32 -> Unicode.Uint32.t
      val to_int : Unicode.Uint32.t -> int
      val to_int32 : Unicode.Uint32.t -> int32
    end
  type utf8_char = char
  type utf8_string = string
  type utf16_char = int
  type utf16_string =
      (int, Stdlib.Bigarray.int16_unsigned_elt, Stdlib.Bigarray.c_layout)
      Stdlib.Bigarray.Array1.t
  type utf32_char = Unicode.Uint32.t
  type utf32_string =
      (int32, Stdlib.Bigarray.int32_elt, Stdlib.Bigarray.c_layout)
      Stdlib.Bigarray.Array1.t
  type utf8_decode_error =
      [ `illegal_sequence
      | `over_17planes of int
      | `overly_long of
          [ `over_17planes of int
          | `some of Stdlib.Uchar.t
          | `surrogate_fragment of int ]
      | `surrogate_fragment of int
      | `truncated ]
  val utf8_sequence :
    fail:([> `illegal_sequence ] -> int) -> Unicode.utf8_char -> int
  val utf8_is_trailing : Unicode.utf8_char -> bool
  val utf8_decode3 :
    ('-> '-> Unicode.utf8_char) ->
    ('-> '-> 'e) ->
    ('-> '-> bool) ->
    ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
    fail:('->
          '-> '-> '-> '-> '-> [> Unicode.utf8_decode_error ] -> 'f) ->
    '-> '-> '-> '-> '-> 'f
  val utf8_decode :
    ('-> '-> Unicode.utf8_char) ->
    ('-> '-> 'b) ->
    ('-> '-> bool) ->
    ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
    fail:('-> '-> '-> [> Unicode.utf8_decode_error ] -> 'c) ->
    '-> '-> 'c
  val utf8_encode4 :
    ('-> '-> Unicode.utf8_char -> 'f) ->
    fail:('-> '-> '-> '-> '-> '-> [> `unexist ] -> 'f) ->
    '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
  val utf8_encode :
    ('-> '-> Unicode.utf8_char -> 'b) ->
    fail:('-> '-> [> `unexist ] -> 'b) ->
    '-> '-> Stdlib.Uchar.t -> 'b
  val utf8_lead : Unicode.utf8_string -> int -> int
  val utf8_rear : Unicode.utf8_string -> int -> int
  val utf8_get_code :
    fail:(Unicode.utf8_string ->
          int -> int -> [> Unicode.utf8_decode_error ] -> Stdlib.Uchar.t) ->
    Unicode.utf8_string -> int Stdlib.ref -> Stdlib.Uchar.t
  val utf8_set_code :
    fail:(bytes -> int -> [> `unexist ] -> Stdlib.Uchar.t) ->
    bytes -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
  type utf16_decode_error = [ `surrogate_fragment of int ]
  val utf16_sequence :
    fail:([> `surrogate_fragment of int ] -> int) ->
    Unicode.utf16_char -> int
  val utf16_is_trailing : Unicode.utf16_char -> bool
  val utf16_decode3 :
    ('-> '-> Unicode.utf16_char) ->
    ('-> '-> 'e) ->
    ('-> '-> bool) ->
    ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
    fail:('->
          '-> '-> '-> '-> '-> [> Unicode.utf16_decode_error ] -> 'f) ->
    '-> '-> '-> '-> '-> 'f
  val utf16_decode :
    ('-> '-> Unicode.utf16_char) ->
    ('-> '-> 'b) ->
    ('-> '-> bool) ->
    ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
    fail:('-> '-> '-> [> Unicode.utf16_decode_error ] -> 'c) ->
    '-> '-> 'c
  val utf16_encode4 :
    ('-> '-> Unicode.utf16_char -> 'f) ->
    fail:('-> '-> '-> '-> '-> '-> [> `unexist ] -> 'f) ->
    '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
  val utf16_encode :
    ('-> '-> Unicode.utf16_char -> 'b) ->
    fail:('-> '-> [> `unexist ] -> 'b) ->
    '-> '-> Stdlib.Uchar.t -> 'b
  val utf16_lead : Unicode.utf16_string -> int -> int
  val utf16_rear : Unicode.utf16_string -> int -> int
  val utf16_get_code :
    fail:(Unicode.utf16_string ->
          int -> int -> [> Unicode.utf16_decode_error ] -> Stdlib.Uchar.t) ->
    Unicode.utf16_string -> int Stdlib.ref -> Stdlib.Uchar.t
  val utf16_set_code :
    fail:(Unicode.utf16_string -> int -> [> `unexist ] -> Stdlib.Uchar.t) ->
    Unicode.utf16_string -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
  type utf32_decode_error =
      [ `illegal_sequence
      | `over_17planes of int
      | `surrogate_fragment of int ]
  val utf32_sequence :
    fail:([> `illegal_sequence | `surrogate_fragment of int ] -> int) ->
    Unicode.utf32_char -> int
  val utf32_is_trailing : Unicode.utf32_char -> bool
  val utf32_decode3 :
    ('-> '-> Unicode.utf32_char) ->
    ('-> '-> 'e) ->
    ('-> '-> bool) ->
    ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
    fail:('->
          '-> '-> '-> '-> '-> [> Unicode.utf32_decode_error ] -> 'f) ->
    '-> '-> '-> '-> '-> 'f
  val utf32_decode :
    ('-> '-> Unicode.utf32_char) ->
    ('-> '-> 'b) ->
    ('-> '-> bool) ->
    ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
    fail:('-> '-> '-> [> Unicode.utf32_decode_error ] -> 'c) ->
    '-> '-> 'c
  val utf32_encode4 :
    ('-> '-> Unicode.utf32_char -> 'f) ->
    fail:('-> '-> '-> '-> '-> '-> [>  ] -> 'f) ->
    '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
  val utf32_encode :
    ('-> '-> Unicode.utf32_char -> 'b) ->
    fail:('-> '-> [>  ] -> 'b) -> '-> '-> Stdlib.Uchar.t -> 'b
  val utf32_lead : Unicode.utf32_string -> int -> int
  val utf32_rear : Unicode.utf32_string -> int -> int
  val utf32_get_code :
    fail:(Unicode.utf32_string ->
          int -> int -> [> Unicode.utf32_decode_error ] -> Stdlib.Uchar.t) ->
    Unicode.utf32_string -> int Stdlib.ref -> Stdlib.Uchar.t
  val utf32_set_code :
    fail:(Unicode.utf32_string -> int -> [>  ] -> Stdlib.Uchar.t) ->
    Unicode.utf32_string -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
  val utf8_of_utf16 :
    fail:(Unicode.utf16_string ->
          int ->
          int -> [> `surrogate_fragment of int | `unexist ] -> Stdlib.Uchar.t) ->
    Unicode.utf16_string -> Unicode.utf8_string
  val utf8_of_utf32 :
    fail:(Unicode.utf32_string ->
          int ->
          int ->
          [> `illegal_sequence
           | `over_17planes of int
           | `surrogate_fragment of int
           | `unexist ] ->
          Stdlib.Uchar.t) ->
    Unicode.utf32_string -> Unicode.utf8_string
  val utf16_of_utf8 :
    fail:(Unicode.utf8_string ->
          int ->
          int ->
          [> `illegal_sequence
           | `over_17planes of int
           | `overly_long of
               [ `over_17planes of int
               | `some of Stdlib.Uchar.t
               | `surrogate_fragment of int ]
           | `surrogate_fragment of int
           | `truncated
           | `unexist ] ->
          Stdlib.Uchar.t) ->
    Unicode.utf8_string -> Unicode.utf16_string
  val utf16_of_utf32 :
    fail:(Unicode.utf32_string ->
          int ->
          int ->
          [> `illegal_sequence
           | `over_17planes of int
           | `surrogate_fragment of int
           | `unexist ] ->
          Stdlib.Uchar.t) ->
    Unicode.utf32_string -> Unicode.utf16_string
  val utf32_of_utf8 :
    fail:(Unicode.utf8_string ->
          int -> int -> [> Unicode.utf8_decode_error ] -> Stdlib.Uchar.t) ->
    Unicode.utf8_string -> Unicode.utf32_string
  val utf32_of_utf16 :
    fail:(Unicode.utf16_string ->
          int -> int -> [> Unicode.utf16_decode_error ] -> Stdlib.Uchar.t) ->
    Unicode.utf16_string -> Unicode.utf32_string
  module UTF8 :
    sig
      type elt = Unicode.utf8_char
      val sequence :
        fail:([> `illegal_sequence ] -> int) -> Unicode.UTF8.elt -> int
      val max_sequence : int
      val is_trailing : Unicode.UTF8.elt -> bool
      val decode3 :
        ('-> '-> Unicode.UTF8.elt) ->
        ('-> '-> 'e) ->
        ('-> '-> bool) ->
        ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
        fail:('->
              '->
              '-> '-> '-> '-> [> Unicode.utf8_decode_error ] -> 'f) ->
        '-> '-> '-> '-> '-> 'f
      val decode :
        ('-> '-> Unicode.UTF8.elt) ->
        ('-> '-> 'b) ->
        ('-> '-> bool) ->
        ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
        fail:('-> '-> '-> [> Unicode.utf8_decode_error ] -> 'c) ->
        '-> '-> 'c
      val encode4 :
        ('-> '-> Unicode.UTF8.elt -> 'f) ->
        fail:('-> '-> '-> '-> '-> '-> [> `unexist ] -> 'f) ->
        '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
      val encode :
        ('-> '-> Unicode.UTF8.elt -> 'b) ->
        fail:('-> '-> [> `unexist ] -> 'b) ->
        '-> '-> Stdlib.Uchar.t -> 'b
      type t = Unicode.utf8_string
      val compare : Unicode.UTF8.t -> Unicode.UTF8.t -> int
      val equal : Unicode.UTF8.t -> Unicode.UTF8.t -> bool
      external length : Unicode.UTF8.t -> int = "%string_length"
      external get : Unicode.UTF8.t -> int -> Unicode.UTF8.elt
        = "%string_safe_get"
      external unsafe_get : Unicode.UTF8.t -> int -> Unicode.UTF8.elt
        = "%string_unsafe_get"
      val empty : Unicode.UTF8.t
      val cat : Unicode.UTF8.t -> Unicode.UTF8.t -> Unicode.UTF8.t
      val sub : Unicode.UTF8.t -> int -> int -> Unicode.UTF8.t
      val blit : Unicode.UTF8.t -> int -> bytes -> int -> int -> unit
      external unsafe_blit :
        Unicode.UTF8.t -> int -> bytes -> int -> int -> unit
        = "caml_blit_string" [@@noalloc]
      val lead : Unicode.UTF8.t -> int -> int
      val rear : Unicode.UTF8.t -> int -> int
      val get_code :
        fail:(Unicode.UTF8.t ->
              int -> int -> [> Unicode.utf8_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.UTF8.t -> int Stdlib.ref -> Stdlib.Uchar.t
      val set_code :
        fail:(bytes -> int -> [> `unexist ] -> Stdlib.Uchar.t) ->
        bytes -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
      val of_utf16 :
        fail:(Unicode.utf16_string ->
              int ->
              int ->
              [> `surrogate_fragment of int | `unexist ] -> Stdlib.Uchar.t) ->
        Unicode.utf16_string -> Unicode.UTF8.t
      val of_utf32 :
        fail:(Unicode.utf32_string ->
              int ->
              int ->
              [> `illegal_sequence
               | `over_17planes of int
               | `surrogate_fragment of int
               | `unexist ] ->
              Stdlib.Uchar.t) ->
        Unicode.utf32_string -> Unicode.UTF8.t
      val of_array : Unicode.UTF8.elt array -> Unicode.UTF8.t
    end
  module UTF8_Bytes :
    sig
      type elt = Unicode.utf8_char
      type t = bytes
      val compare : Unicode.UTF8_Bytes.t -> Unicode.UTF8_Bytes.t -> int
      val equal : Unicode.UTF8_Bytes.t -> Unicode.UTF8_Bytes.t -> bool
      external length : Unicode.UTF8_Bytes.t -> int = "%bytes_length"
      external get : Unicode.UTF8_Bytes.t -> int -> Unicode.UTF8_Bytes.elt
        = "%bytes_safe_get"
      external unsafe_get :
        Unicode.UTF8_Bytes.t -> int -> Unicode.UTF8_Bytes.elt
        = "%bytes_unsafe_get"
      external set :
        Unicode.UTF8_Bytes.t -> int -> Unicode.UTF8_Bytes.elt -> unit
        = "%bytes_safe_set"
      external unsafe_set :
        Unicode.UTF8_Bytes.t -> int -> Unicode.UTF8_Bytes.elt -> unit
        = "%bytes_unsafe_set"
      val empty : Unicode.UTF8_Bytes.t
      external create : int -> Unicode.UTF8_Bytes.t = "caml_create_bytes"
      val copy : Unicode.UTF8_Bytes.t -> Unicode.UTF8_Bytes.t
      val cat :
        Unicode.UTF8_Bytes.t -> Unicode.UTF8_Bytes.t -> Unicode.UTF8_Bytes.t
      val sub : Unicode.UTF8_Bytes.t -> int -> int -> Unicode.UTF8_Bytes.t
      val fill :
        Unicode.UTF8_Bytes.t -> int -> int -> Unicode.UTF8_Bytes.elt -> unit
      external unsafe_fill :
        Unicode.UTF8_Bytes.t -> int -> int -> Unicode.UTF8_Bytes.elt -> unit
        = "caml_fill_bytes" [@@noalloc]
      val blit :
        Unicode.UTF8_Bytes.t ->
        int -> Unicode.UTF8_Bytes.t -> int -> int -> unit
      external unsafe_blit :
        Unicode.UTF8_Bytes.t ->
        int -> Unicode.UTF8_Bytes.t -> int -> int -> unit = "caml_blit_bytes"
        [@@noalloc]
      val lead : Unicode.UTF8_Bytes.t -> int -> int
      val rear : Unicode.UTF8_Bytes.t -> int -> int
      val get_code :
        fail:(Unicode.UTF8_Bytes.t ->
              int -> int -> [> Unicode.utf8_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.UTF8_Bytes.t -> int Stdlib.ref -> Stdlib.Uchar.t
      val set_code :
        fail:(Unicode.UTF8_Bytes.t -> int -> [> `unexist ] -> Stdlib.Uchar.t) ->
        Unicode.UTF8_Bytes.t -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
      val of_array : Unicode.UTF8_Bytes.elt array -> Unicode.UTF8_Bytes.t
    end
  module UTF16 :
    sig
      type elt = Unicode.utf16_char
      val sequence :
        fail:([> `surrogate_fragment of int ] -> int) ->
        Unicode.UTF16.elt -> int
      val max_sequence : int
      val is_trailing : Unicode.UTF16.elt -> bool
      val decode3 :
        ('-> '-> Unicode.UTF16.elt) ->
        ('-> '-> 'e) ->
        ('-> '-> bool) ->
        ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
        fail:('->
              '->
              '-> '-> '-> '-> [> Unicode.utf16_decode_error ] -> 'f) ->
        '-> '-> '-> '-> '-> 'f
      val decode :
        ('-> '-> Unicode.UTF16.elt) ->
        ('-> '-> 'b) ->
        ('-> '-> bool) ->
        ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
        fail:('-> '-> '-> [> Unicode.utf16_decode_error ] -> 'c) ->
        '-> '-> 'c
      val encode4 :
        ('-> '-> Unicode.UTF16.elt -> 'f) ->
        fail:('-> '-> '-> '-> '-> '-> [> `unexist ] -> 'f) ->
        '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
      val encode :
        ('-> '-> Unicode.UTF16.elt -> 'b) ->
        fail:('-> '-> [> `unexist ] -> 'b) ->
        '-> '-> Stdlib.Uchar.t -> 'b
      type t = Unicode.utf16_string
      external compare : Unicode.UTF16.t -> Unicode.UTF16.t -> int
        = "%compare"
      external equal : Unicode.UTF16.t -> Unicode.UTF16.t -> bool = "%equal"
      external length : Unicode.UTF16.t -> int = "%caml_ba_dim_1"
      external get : Unicode.UTF16.t -> int -> Unicode.UTF16.elt
        = "%caml_ba_ref_1"
      external unsafe_get : Unicode.UTF16.t -> int -> Unicode.UTF16.elt
        = "%caml_ba_unsafe_ref_1"
      external set : Unicode.UTF16.t -> int -> Unicode.UTF16.elt -> unit
        = "%caml_ba_set_1"
      external unsafe_set :
        Unicode.UTF16.t -> int -> Unicode.UTF16.elt -> unit
        = "%caml_ba_unsafe_set_1"
      val empty : Unicode.UTF16.t
      val create : int -> Unicode.UTF16.t
      val copy : Unicode.UTF16.t -> Unicode.UTF16.t
      val cat : Unicode.UTF16.t -> Unicode.UTF16.t -> Unicode.UTF16.t
      external sub : Unicode.UTF16.t -> int -> int -> Unicode.UTF16.t
        = "caml_ba_sub"
      val fill : Unicode.UTF16.t -> int -> int -> Unicode.UTF16.elt -> unit
      val blit :
        Unicode.UTF16.t -> int -> Unicode.UTF16.t -> int -> int -> unit
      val lead : Unicode.UTF16.t -> int -> int
      val rear : Unicode.UTF16.t -> int -> int
      val get_code :
        fail:(Unicode.UTF16.t ->
              int -> int -> [> Unicode.utf16_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.UTF16.t -> int Stdlib.ref -> Stdlib.Uchar.t
      val set_code :
        fail:(Unicode.UTF16.t -> int -> [> `unexist ] -> Stdlib.Uchar.t) ->
        Unicode.UTF16.t -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
      val of_utf8 :
        fail:(Unicode.utf8_string ->
              int ->
              int ->
              [> `illegal_sequence
               | `over_17planes of int
               | `overly_long of
                   [ `over_17planes of int
                   | `some of Stdlib.Uchar.t
                   | `surrogate_fragment of int ]
               | `surrogate_fragment of int
               | `truncated
               | `unexist ] ->
              Stdlib.Uchar.t) ->
        Unicode.utf8_string -> Unicode.UTF16.t
      val of_utf32 :
        fail:(Unicode.utf32_string ->
              int ->
              int ->
              [> `illegal_sequence
               | `over_17planes of int
               | `surrogate_fragment of int
               | `unexist ] ->
              Stdlib.Uchar.t) ->
        Unicode.utf32_string -> Unicode.UTF16.t
      val of_array : Unicode.UTF16.elt array -> Unicode.UTF16.t
    end
  module UTF32 :
    sig
      type elt = Unicode.utf32_char
      val sequence :
        fail:([> `illegal_sequence | `surrogate_fragment of int ] -> int) ->
        Unicode.UTF32.elt -> int
      val max_sequence : int
      val is_trailing : Unicode.UTF32.elt -> bool
      val decode3 :
        ('-> '-> Unicode.UTF32.elt) ->
        ('-> '-> 'e) ->
        ('-> '-> bool) ->
        ('-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f) ->
        fail:('->
              '->
              '-> '-> '-> '-> [> Unicode.utf32_decode_error ] -> 'f) ->
        '-> '-> '-> '-> '-> 'f
      val decode :
        ('-> '-> Unicode.UTF32.elt) ->
        ('-> '-> 'b) ->
        ('-> '-> bool) ->
        ('-> '-> '-> Stdlib.Uchar.t -> 'c) ->
        fail:('-> '-> '-> [> Unicode.utf32_decode_error ] -> 'c) ->
        '-> '-> 'c
      val encode4 :
        ('-> '-> Unicode.UTF32.elt -> 'f) ->
        fail:('-> '-> '-> '-> '-> '-> [>  ] -> 'f) ->
        '-> '-> '-> '-> '-> '-> Stdlib.Uchar.t -> 'f
      val encode :
        ('-> '-> Unicode.UTF32.elt -> 'b) ->
        fail:('-> '-> [>  ] -> 'b) -> '-> '-> Stdlib.Uchar.t -> 'b
      type t = Unicode.utf32_string
      val compare : Unicode.UTF32.t -> Unicode.UTF32.t -> int
      external equal : Unicode.UTF32.t -> Unicode.UTF32.t -> bool = "%equal"
      external length : Unicode.UTF32.t -> int = "%caml_ba_dim_1"
      val get : Unicode.UTF32.t -> int -> Unicode.UTF32.elt
      val unsafe_get : Unicode.UTF32.t -> int -> Unicode.UTF32.elt
      val set : Unicode.UTF32.t -> int -> Unicode.UTF32.elt -> unit
      val unsafe_set : Unicode.UTF32.t -> int -> Unicode.UTF32.elt -> unit
      val empty : Unicode.UTF32.t
      val create : int -> Unicode.UTF32.t
      val copy : Unicode.UTF32.t -> Unicode.UTF32.t
      val cat : Unicode.UTF32.t -> Unicode.UTF32.t -> Unicode.UTF32.t
      external sub : Unicode.UTF32.t -> int -> int -> Unicode.UTF32.t
        = "caml_ba_sub"
      val fill : Unicode.UTF32.t -> int -> int -> Unicode.UTF32.elt -> unit
      val blit :
        Unicode.UTF32.t -> int -> Unicode.UTF32.t -> int -> int -> unit
      val lead : Unicode.UTF32.t -> int -> int
      val rear : Unicode.UTF32.t -> int -> int
      val get_code :
        fail:(Unicode.UTF32.t ->
              int -> int -> [> Unicode.utf32_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.UTF32.t -> int Stdlib.ref -> Stdlib.Uchar.t
      val set_code :
        fail:(Unicode.UTF32.t -> int -> [>  ] -> Stdlib.Uchar.t) ->
        Unicode.UTF32.t -> int Stdlib.ref -> Stdlib.Uchar.t -> unit
      val of_utf8 :
        fail:(Unicode.utf8_string ->
              int -> int -> [> Unicode.utf8_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.utf8_string -> Unicode.UTF32.t
      val of_utf16 :
        fail:(Unicode.utf16_string ->
              int -> int -> [> Unicode.utf32_decode_error ] -> Stdlib.Uchar.t) ->
        Unicode.utf16_string -> Unicode.UTF32.t
      val of_array : Unicode.UTF32.elt array -> Unicode.UTF32.t
    end
end