From e4d3c6bc968ae7ebd632d41d1172af6c7b84f205 Mon Sep 17 00:00:00 2001 From: Anders Fugmann Date: Sun, 28 Jan 2024 00:04:32 +0100 Subject: [PATCH 1/2] Emit code for merging two messages and add tests to verify the implementation --- src/ocaml_protoc_plugin/deserialize.ml | 22 +- src/ocaml_protoc_plugin/merge.ml | 21 + .../ocaml_protoc_plugin.ml | 1 + src/ocaml_protoc_plugin/runtime.ml | 1 + src/ocaml_protoc_plugin/spec.ml | 6 +- src/plugin/code.ml | 9 +- src/plugin/emit.ml | 8 +- src/plugin/types.ml | 141 +++-- src/plugin/types.mli | 1 + src/spec/descriptor.ml | 526 +++++++++++++++--- src/spec/options.ml | 17 +- src/spec/plugin.ml | 67 ++- test/dune | 4 +- test/enum_test.ml | 9 +- test/merge.proto | 16 + test/merge_test.ml | 144 +++++ test/oneof.proto | 10 +- test/proto2.proto | 10 + test/proto2_test.ml | 12 +- test/test_lib.ml | 62 ++- 20 files changed, 940 insertions(+), 147 deletions(-) create mode 100644 src/ocaml_protoc_plugin/merge.ml create mode 100644 test/merge.proto create mode 100644 test/merge_test.ml diff --git a/src/ocaml_protoc_plugin/deserialize.ml b/src/ocaml_protoc_plugin/deserialize.ml index 9866a52..4836149 100644 --- a/src/ocaml_protoc_plugin/deserialize.ml +++ b/src/ocaml_protoc_plugin/deserialize.ml @@ -85,7 +85,7 @@ let read_of_spec: type a. a spec -> Field.field_type * (Reader.t -> a) = functio let v = Bytes.create length in Bytes.blit_string ~src:data ~src_pos:offset ~dst:v ~dst_pos:0 ~len:length; v - | Message from_proto -> Length_delimited, fun reader -> + | Message (from_proto, _merge) -> Length_delimited, fun reader -> let Field.{ offset; length; data } = Reader.read_length_delimited reader in from_proto (Reader.create ~offset ~length data) @@ -102,7 +102,7 @@ let default_value: type a. a spec -> a = function | Fixed64 -> Int64.zero | SFixed32 -> Int32.zero | SFixed64 -> Int64.zero - | Message of_proto -> of_proto (Reader.create "") + | Message (of_proto, _merge) -> of_proto (Reader.create "") | String -> "" | Bytes -> Bytes.empty | Int32_int -> 0 @@ -130,7 +130,11 @@ let read_field ~read:(expect, read_f) ~map v reader field_type = let value: type a. a compound -> a value = function | Basic (index, spec, default) -> - let read = read_field ~read:(read_of_spec spec) ~map:keep_last in + let map = match spec with + | Message (_, merge) -> merge + | _ -> keep_last + in + let read = read_field ~read:(read_of_spec spec) ~map in let required = match default with | Some _ -> Optional | None -> Required @@ -141,7 +145,17 @@ let value: type a. a compound -> a value = function in ([(index, read)], required, default, id) | Basic_opt (index, spec) -> - let read = read_field ~read:(read_of_spec spec) ~map:(fun _ v -> Some v) in + let map = match spec with + | Message (_, merge) -> + let map v1 v2 = + match v1 with + | None -> Some v2 + | Some prev -> Some (merge prev v2) + in + map + | _ -> fun _ v -> Some v (* Keep last for all other non-repeated types *) + in + let read = read_field ~read:(read_of_spec spec) ~map in ([(index, read)], Optional, None, id) | Repeated (index, spec, Packed) -> let field_type, read_f = read_of_spec spec in diff --git a/src/ocaml_protoc_plugin/merge.ml b/src/ocaml_protoc_plugin/merge.ml new file mode 100644 index 0000000..7f89f4e --- /dev/null +++ b/src/ocaml_protoc_plugin/merge.ml @@ -0,0 +1,21 @@ +(** Merge a two values. Need to match on the spec to merge messages recursivly *) +let merge: type t. t Spec.Deserialize.compound -> t -> t -> t = fun spec t t' -> match spec with + | Spec.Deserialize.Basic (_field, Message (_, merge), _) -> merge t t' + | Spec.Deserialize.Basic (_field, _spec, Some default) when t' = default -> t + | Spec.Deserialize.Basic (_field, _spec, _) -> t' + | Spec.Deserialize.Basic_opt (_field, Message (_, merge)) -> + begin + match t, t' with + | None, None -> None + | Some t, None -> Some t + | None, Some t -> Some t + | Some t, Some t' -> Some (merge t t') + end + | Spec.Deserialize.Basic_opt (_field, _spec) -> begin + match t' with + | Some _ -> t' + | None -> t + end + | Spec.Deserialize.Repeated (_field, _, _) -> t @ t' + (* | Spec.Deserialize.Oneof _ when t' = `not_set -> t *) + | Spec.Deserialize.Oneof _ -> failwith "Implementation is part of generated code" diff --git a/src/ocaml_protoc_plugin/ocaml_protoc_plugin.ml b/src/ocaml_protoc_plugin/ocaml_protoc_plugin.ml index 274c19d..6b911b4 100644 --- a/src/ocaml_protoc_plugin/ocaml_protoc_plugin.ml +++ b/src/ocaml_protoc_plugin/ocaml_protoc_plugin.ml @@ -3,6 +3,7 @@ module Serialize = Serialize module Deserialize = Deserialize module Spec = Spec module Runtime = Runtime +module Field = Field (**/**) module Reader = Reader diff --git a/src/ocaml_protoc_plugin/runtime.ml b/src/ocaml_protoc_plugin/runtime.ml index c8f5500..25afc05 100644 --- a/src/ocaml_protoc_plugin/runtime.ml +++ b/src/ocaml_protoc_plugin/runtime.ml @@ -7,4 +7,5 @@ module Runtime' = struct module Extensions = Extensions module Reader = Reader module Writer = Writer + module Merge = Merge end diff --git a/src/ocaml_protoc_plugin/spec.ml b/src/ocaml_protoc_plugin/spec.ml index a3cd53f..7a87805 100644 --- a/src/ocaml_protoc_plugin/spec.ml +++ b/src/ocaml_protoc_plugin/spec.ml @@ -7,6 +7,7 @@ module Make(T : T) = struct type packed = Packed | Not_packed type extension_ranges = (int * int) list type extensions = (int * Field.t) list + type 'a merge = 'a -> 'a -> 'a type _ spec = | Double : float spec @@ -40,7 +41,10 @@ module Make(T : T) = struct | String : string spec | Bytes : bytes spec | Enum : ('a, int -> 'a, 'a -> int) T.dir -> 'a spec - | Message : ('a, Reader.t -> 'a, Writer.t -> 'a -> Writer.t) T.dir -> 'a spec + | Message : ('a, ((Reader.t -> 'a) * 'a merge), Writer.t -> 'a -> Writer.t) T.dir -> 'a spec + + (* Existential types *) + type espec = Espec: _ spec -> espec type _ oneof = | Oneof_elem : int * 'b spec * ('a, ('b -> 'a), 'b) T.dir -> 'a oneof diff --git a/src/plugin/code.ml b/src/plugin/code.ml index a0b8f72..77e5138 100644 --- a/src/plugin/code.ml +++ b/src/plugin/code.ml @@ -29,8 +29,13 @@ let emit t indent fmt = | n -> String.sub ~pos:0 ~len:(String.length s - n) s in let prepend s = - String.split_on_char ~sep:'\n' s - |> List.iter ~f:(fun s -> t.code <- (trim_end ~char:' ' (t.indent ^ s)) :: t.code) + match String.split_on_char ~sep:'\n' s with + | line :: lines -> + t.code <- (trim_end ~char:' ' (t.indent ^ line)) :: t.code; + incr t; + List.iter lines ~f:(fun line -> t.code <- (trim_end ~char:' ' (t.indent ^ line)) :: t.code); + decr t; + | [] -> () in let emit s = match indent with diff --git a/src/plugin/emit.ml b/src/plugin/emit.ml index a887624..5bdcc33 100644 --- a/src/plugin/emit.ml +++ b/src/plugin/emit.ml @@ -211,14 +211,16 @@ let rec emit_message ~params ~syntax scope | Some _name -> let is_map_entry = is_map_entry options in let is_cyclic = Scope.is_cyclic scope in - let Types.{ type'; constructor; apply; deserialize_spec; serialize_spec; default_constructor_sig; default_constructor_impl } = + let Types.{ type'; constructor; apply; deserialize_spec; serialize_spec; + default_constructor_sig; default_constructor_impl; merge_impl } = Types.make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fields oneof_decls in - ignore (default_constructor_sig, default_constructor_impl); + ignore (merge_impl); Code.emit signature `None "val name': unit -> string"; Code.emit signature `None "type t = %s %s" type' params.annot; Code.emit signature `None "val make: %s" default_constructor_sig; + Code.emit signature `None "val merge: t -> t -> t"; Code.emit signature `None "val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t"; Code.emit signature `None "val to_proto: t -> Runtime'.Writer.t"; Code.emit signature `None "val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result"; @@ -227,6 +229,7 @@ let rec emit_message ~params ~syntax scope Code.emit implementation `None "let name' () = \"%s\"" (Scope.get_current_scope scope); Code.emit implementation `None "type t = %s%s" type' params.annot; Code.emit implementation `None "let make %s" default_constructor_impl; + Code.emit implementation `None "let merge = (%s)" merge_impl; Code.emit implementation `Begin "let to_proto' ="; Code.emit implementation `None "let spec = %s in" serialize_spec; @@ -240,7 +243,6 @@ let rec emit_message ~params ~syntax scope Code.emit implementation `None "let constructor = %s in" constructor; Code.emit implementation `None "let spec = %s in" deserialize_spec; Code.emit implementation `None "Runtime'.Deserialize.deserialize spec constructor"; - (* TODO: No need to have a function here. We could drop deserialize thing here *) Code.emit implementation `End "let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer)"; | None -> () in diff --git a/src/plugin/types.ml b/src/plugin/types.ml index baedeea..23b94bd 100644 --- a/src/plugin/types.ml +++ b/src/plugin/types.ml @@ -14,20 +14,19 @@ open StdLabels *) module T = Ocaml_protoc_plugin.Spec.Make(struct - type ('a, 'deser, 'ser) dir = (string * string * string * string option) + type ('a, 'deser, 'ser) dir = (string * string * string * string option * (string * string) list) end) open T open Spec.Descriptor.Google.Protobuf -(* Existential types *) -type espec = Espec: _ spec -> espec type type_modifier = | No_modifier of string (* The default value *) | Optional | List | Required + | Oneof_type of string * (string * string) list type type' = { name: string; modifier: type_modifier } @@ -53,6 +52,7 @@ type t = { serialize_spec: string; default_constructor_sig: string; default_constructor_impl: string; + merge_impl: string; } let sprintf = Printf.sprintf @@ -122,8 +122,8 @@ let string_of_default: type a. a spec -> a -> string = function | Bool -> string_of_bool | String -> sprintf "{|%s|}" | Bytes -> fun bytes -> sprintf "(Bytes.of_string {|%s|})" (Bytes.to_string bytes) - | Enum (_, _, _, Some s) -> fun _ -> s - | Enum (s', s, _, None) -> fun _ -> sprintf "(%s 0 (* And its an %s *))" s' s (* Is this the ocaml name???. Maybe we need the protoc name *) + | Enum (_, _, _, Some s, _) -> fun _ -> s + | Enum (s', s, _, None, _) -> fun _ -> sprintf "(%s 0 (* And its an %s *))" s' s (* Is this the ocaml name???. Maybe we need the protoc name *) | Message _ -> failwith "Messages defaults are not relevant" let default_of_spec: type a. a spec -> a = fun spec -> match spec with @@ -192,10 +192,10 @@ let string_of_spec: type a. [`Deserialize | `Serialize] -> a spec -> string = fu | _, Bool -> "bool" | _, String -> "string" | _, Bytes -> "bytes" - | `Deserialize, Enum (_, deser, _ , _) -> sprintf "(enum %s)" deser - | `Serialize, Enum (_, _, ser, _) -> sprintf "(enum %s)" ser - | `Deserialize, Message (_, deser, _ , _) -> sprintf "(message (fun t -> %s t))" deser - | `Serialize, Message (_, _, ser, _) -> sprintf "(message (fun t -> %s t))" ser + | `Deserialize, Enum (_, deser, _ , _, _) -> sprintf "(enum %s)" deser + | `Serialize, Enum (_, _, ser, _, _) -> sprintf "(enum %s)" ser + | `Deserialize, Message (_, deser, _ , _, _) -> sprintf "(message %s)" deser + | `Serialize, Message (_, _, ser, _, _) -> sprintf "(message %s)" ser let type_of_spec: type a. a spec -> string = function | Double -> "float" @@ -228,14 +228,18 @@ let type_of_spec: type a. a spec -> string = function | Bool -> "bool" | String -> "string" | Bytes -> "bytes" - | Enum (type', _, _, _) -> type' - | Message (type', _, _, _) -> type' + | Enum (type', _, _, _, _) -> type' + | Message (type', _, _, _, _) -> type' let spec_of_message ~scope type_name = let type' = Scope.get_scoped_name ~postfix:"t" scope type_name in - let deserialize_func = Scope.get_scoped_name ~postfix:"from_proto_exn" scope type_name in + let deserialize_func = + let from_proto = Scope.get_scoped_name ~postfix:"from_proto_exn" scope type_name in + let merge = Scope.get_scoped_name ~postfix:"merge" scope type_name in + sprintf "((fun writer -> %s writer), %s)" from_proto merge + in let serialize_func = Scope.get_scoped_name ~postfix:"to_proto'" scope type_name in - Message (type', deserialize_func, serialize_func, None) + Message (type', deserialize_func, serialize_func, None, []) let spec_of_enum ~scope type_name default = let type' = Scope.get_scoped_name ~postfix:"t" scope type_name in @@ -251,7 +255,7 @@ let spec_of_enum ~scope type_name default = | None -> Scope.get_scoped_enum_name scope type_name in - (type', deserialize_func, serialize_func, Some default) + (type', deserialize_func, serialize_func, Some default, []) open Parameters let spec_of_type ~params ~scope type_name default = @@ -294,7 +298,7 @@ let spec_of_type ~params ~scope type_name default = | TYPE_MESSAGE -> Espec (spec_of_message ~scope type_name) | TYPE_ENUM -> Espec (Enum (spec_of_enum ~scope type_name default)) -let string_of_oneof_elem dir (Oneof_elem (index, spec, (_, deser, ser, _))) = +let string_of_oneof_elem dir (Oneof_elem (index, spec, (_, deser, ser, _, _))) = let spec_string = string_of_spec dir spec in let s = match dir with `Deserialize -> deser | `Serialize -> ser in sprintf "oneof_elem (%d, %s, %s)" index spec_string s @@ -308,12 +312,11 @@ let string_of_packed = function | Not_packed -> "not_packed" let string_of_type = function - | { name; modifier = (No_modifier _ | Required); _ } -> name + | { name; modifier = (No_modifier _ | Required | Oneof_type _); _ } -> name | { name; modifier = List; _ } -> sprintf "%s list" name | { name; modifier = Optional; _ } -> sprintf "%s option" name -let c_of_compound: type a. string -> a compound -> c = fun name compound -> - match compound with +let c_of_compound: type a. string -> a compound -> c = fun name -> function | Basic (index, spec, default) -> let deserialize_spec = sprintf "basic (%d, %s, %s)" index (string_of_spec `Deserialize spec) (string_of_proto_type spec default) in let serialize_spec = sprintf "basic (%d, %s, %s)" index (string_of_spec `Serialize spec) (string_of_proto_type spec default) in @@ -335,10 +338,11 @@ let c_of_compound: type a. string -> a compound -> c = fun name compound -> let serialize_spec = sprintf "repeated (%d, %s, %s)" index (string_of_spec `Serialize spec) (string_of_packed packed) in let type' = { name = type_of_spec spec; modifier = List } in { name; type'; deserialize_spec; serialize_spec; } - | Oneof (type', deserialize_spec, serialize_spec, _) -> + | Oneof (type', deserialize_spec, serialize_spec, _, fields) -> let deserialize_spec = sprintf "oneof (%s)" deserialize_spec in let serialize_spec = sprintf "oneof (%s)" serialize_spec in - let type' = { name = type'; modifier = No_modifier {|`not_set|} } in + + let type' = { name = type'; modifier = Oneof_type ({|`not_set|}, fields) } in { name; type'; deserialize_spec; serialize_spec } let c_of_field ~params ~syntax ~scope field = @@ -417,7 +421,7 @@ let c_of_field ~params ~syntax ~scope field = (* Proto3 enum implicitly optional field *) | `Proto3, { label = Some Label.LABEL_OPTIONAL; type' = Some TYPE_ENUM; type_name; _} -> let spec = spec_of_enum ~scope type_name None in - let (_, _, _, default) = spec in + let (_, _, _, default, _) = spec in Basic (number, Enum spec, default) |> c_of_compound name @@ -485,16 +489,18 @@ let c_of_oneof ~params ~syntax:_ ~scope OneofDescriptorProto.{ name; _ } fields List.map ~f:(function | { number = Some number; name; type' = Some type'; type_name; _ } -> let Espec spec = spec_of_type ~params ~scope type_name None type' in - (number, name, type_of_spec spec, (Espec spec)) + (number, name, type_of_spec spec, Espec spec) | _ -> failwith "No index or type" ) fields in let oneof = let oneof_elems = + field_infos + |> List.map ~f:(fun (index, name, type', Espec spec) -> let adt_name = Scope.get_name_exn scope name in - adt_name, Oneof_elem (index, spec, (type', sprintf "fun v -> %s v" adt_name, "v", None)) - ) field_infos + adt_name, Oneof_elem (index, spec, (type', sprintf "fun v -> %s v" adt_name, "v", None, [])) + ) in let type' = field_infos @@ -510,16 +516,19 @@ let c_of_oneof ~params ~syntax:_ ~scope OneofDescriptorProto.{ name; _ } fields |> sprintf "[ %s ]" in let ser_oneof = - let default_elem = "`not_set -> failwith \"This case should never _ever_ happen\"" in - oneof_elems - |> List.map ~f:(fun (name, oneof_elem) -> + "| `not_set -> failwith \"This case should never _ever_ happen\"" :: + List.map oneof_elems ~f:(fun (name, oneof_elem) -> sprintf "%s v -> %s" name (string_of_oneof_elem `Serialize oneof_elem) ) - |> (fun l -> default_elem :: l) |> String.concat ~sep:" | " - |> sprintf "(function | %s)" + |> sprintf "(function %s)" in - Oneof (type', deser_oneofs, ser_oneof, None) + let constructors = + List.map oneof_elems ~f:(fun (name, Oneof_elem (_, spec, _)) -> + name, string_of_spec `Deserialize spec + ) + in + Oneof (type', deser_oneofs, ser_oneof, None, constructors) in c_of_compound (Option.value_exn name) oneof @@ -570,19 +579,17 @@ let make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fiel sprintf "%s:%s" (Scope.get_name scope name) type_name | { name; type' = { name = type_name; modifier = List }; _} -> sprintf "?%s:%s list" (Scope.get_name scope name) type_name - | { name; type' = { name = type_name; modifier = (Optional | No_modifier _) }; _} -> + | { name; type' = { name = type_name; modifier = (Optional | No_modifier _ | Oneof_type _) }; _} -> sprintf "?%s:%s" (Scope.get_name scope name) type_name in - let constructor_arg c = let name = Scope.get_name scope c.name in match c with | { type' = { modifier = Required; _}; _ } -> sprintf "~%s" name | { type' = { modifier = Optional; _ }; _} -> sprintf "?%s" name | { type' = { modifier = List; _ }; _} -> sprintf "?(%s = [])" name - | { type' = { modifier = No_modifier default; _}; _} -> sprintf "?(%s = %s)" name default + | { type' = { modifier = (No_modifier default | Oneof_type (default, _)); _}; _} -> sprintf "?(%s = %s)" name default in - let prepend ?(cond=true) elm l = match cond with | true -> elm :: l | false -> l @@ -598,10 +605,8 @@ let make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fiel not has_extensions && not is_cyclic) in - (* Or actually a single constr *) let type_constr fields = match fields, t_as_tuple with | [], _ -> "unit" - | [field], true -> field | fields, true -> String.concat ~sep:" * " fields |> sprintf "(%s)" @@ -611,7 +616,6 @@ let make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fiel in let type_destr fields = match fields, t_as_tuple with | [], _ -> "()" - | [field], true -> field | fields, true -> String.concat ~sep:", " fields |> sprintf "(%s)" @@ -696,5 +700,66 @@ let make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fiel |> sprintf "Runtime'.Serialize.C.( %s )" in + let merge_impl = + let as_tuple = t_as_tuple || List.length ts = 0 && not has_extensions in + let args = + List.map ["t1";"t2"] ~f:(fun s -> + match as_tuple with + | true -> + List.map ~f:(fun c -> sprintf "%s_%s" s (Scope.get_name scope c.name)) ts + |> String.concat ~sep:"," + |> sprintf "(%s)" + | false -> s + ) + |> String.concat ~sep:" " + in + let sep = match as_tuple with true -> "_" | false -> "." in + let merge_values = + List.map ts ~f:(function + | { name; deserialize_spec = _; type' = { modifier = Oneof_type (_, ctrs); _ }; _ } -> + (* Default values for oneof fields makes absolutely no sense!. + Consider a oneof type with two fields with a default value. + Its undecidable if any should be marked as set if none of the fields + are transmitted. The system should actually warn (or error) if + a syntax2 oneof field is marked with a default value + *) + + let name = Scope.get_name scope name in + sprintf "let %s = match ((t1%s%s), (t2%s%s)) with" name sep name sep name :: + List.map ~f:(fun (ctr, type') -> + let spec = sprintf "basic (0, %s, None)" type' in + sprintf " | (%s v1, %s v2) -> %s (Runtime'.Merge.merge Runtime'.Deserialize.C.( %s ) v1 v2)" ctr ctr ctr spec + ) ctrs + |> append " | (v1, `not_set) -> v1" + |> append " | (_, v2) -> v2" + |> append "in" + |> String.concat ~sep:"\n" + + | { name; deserialize_spec; _ } -> + let name = Scope.get_name scope name in + sprintf "let %s = Runtime'.Merge.merge Runtime'.Deserialize.C.( %s ) t1%s%s t2%s%s in\n" + name deserialize_spec sep name sep name + ) + |> append ~cond:has_extensions (sprintf "let extensions' = List.append t1%sextensions' t2%sextensions' in" sep sep) + |> String.concat ~sep:"\n" + in + let constr = + let names = + List.map ts ~f:(fun c -> Scope.get_name scope c.name) + |> append ~cond:has_extensions "extensions'" + in + match as_tuple with + | true -> + names + |> String.concat ~sep:"," + |> sprintf "(%s)" + | false -> + names + |> String.concat ~sep:"; " + |> sprintf "{ %s }" + in + sprintf "fun %s -> \n%s\n%s" args merge_values constr + in + (* The type contains optional elements. We should not have those *) - { type'; constructor; apply; deserialize_spec; serialize_spec; default_constructor_sig; default_constructor_impl } + { type'; constructor; apply; deserialize_spec; serialize_spec; default_constructor_sig; default_constructor_impl; merge_impl } diff --git a/src/plugin/types.mli b/src/plugin/types.mli index 7415a15..abf7dfb 100644 --- a/src/plugin/types.mli +++ b/src/plugin/types.mli @@ -8,6 +8,7 @@ type t = { serialize_spec: string; default_constructor_sig: string; default_constructor_impl: string; + merge_impl: string; } type field_spec = { diff --git a/src/spec/descriptor.ml b/src/spec/descriptor.ml index 2c92b99..33e703b 100644 --- a/src/spec/descriptor.ml +++ b/src/spec/descriptor.ml @@ -22,8 +22,9 @@ module rec Google : sig module rec Protobuf : sig module rec FileDescriptorSet : sig val name': unit -> string - type t = FileDescriptorProto.t list + type t = (FileDescriptorProto.t list) val make: ?file:FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -33,6 +34,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; package: string option; dependency: string list; message_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; service: ServiceDescriptorProto.t list; extension: FieldDescriptorProto.t list; options: FileOptions.t option; source_code_info: SourceCodeInfo.t option; public_dependency: int list; weak_dependency: int list; syntax: string option } val make: ?name:string -> ?package:string -> ?dependency:string list -> ?message_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?service:ServiceDescriptorProto.t list -> ?extension:FieldDescriptorProto.t list -> ?options:FileOptions.t -> ?source_code_info:SourceCodeInfo.t -> ?public_dependency:int list -> ?weak_dependency:int list -> ?syntax:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -43,6 +45,7 @@ module rec Google : sig val name': unit -> string type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } val make: ?start:int -> ?end':int -> ?options:ExtensionRangeOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -52,6 +55,7 @@ module rec Google : sig val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -60,6 +64,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; field: FieldDescriptorProto.t list; nested_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; extension_range: ExtensionRange.t list; extension: FieldDescriptorProto.t list; options: MessageOptions.t option; oneof_decl: OneofDescriptorProto.t list; reserved_range: ReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?field:FieldDescriptorProto.t list -> ?nested_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?extension_range:ExtensionRange.t list -> ?extension:FieldDescriptorProto.t list -> ?options:MessageOptions.t -> ?oneof_decl:OneofDescriptorProto.t list -> ?reserved_range:ReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -69,6 +74,7 @@ module rec Google : sig val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -90,6 +96,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; extendee: string option; number: int option; label: Label.t option; type': Type.t option; type_name: string option; default_value: string option; options: FieldOptions.t option; oneof_index: int option; json_name: string option; proto3_optional: bool option } val make: ?name:string -> ?extendee:string -> ?number:int -> ?label:Label.t -> ?type':Type.t -> ?type_name:string -> ?default_value:string -> ?options:FieldOptions.t -> ?oneof_index:int -> ?json_name:string -> ?proto3_optional:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -99,6 +106,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; options: OneofOptions.t option } val make: ?name:string -> ?options:OneofOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -109,6 +117,7 @@ module rec Google : sig val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -117,6 +126,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; value: EnumValueDescriptorProto.t list; options: EnumOptions.t option; reserved_range: EnumReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?value:EnumValueDescriptorProto.t list -> ?options:EnumOptions.t -> ?reserved_range:EnumReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -126,6 +136,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; number: int option; options: EnumValueOptions.t option } val make: ?name:string -> ?number:int -> ?options:EnumValueOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -135,6 +146,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; method': MethodDescriptorProto.t list; options: ServiceOptions.t option } val make: ?name:string -> ?method':MethodDescriptorProto.t list -> ?options:ServiceOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -144,6 +156,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; input_type: string option; output_type: string option; options: MethodOptions.t option; client_streaming: bool; server_streaming: bool } val make: ?name:string -> ?input_type:string -> ?output_type:string -> ?options:MethodOptions.t -> ?client_streaming:bool -> ?server_streaming:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -159,6 +172,7 @@ module rec Google : sig val name': unit -> string type t = { java_package: string option; java_outer_classname: string option; optimize_for: OptimizeMode.t; java_multiple_files: bool; go_package: string option; cc_generic_services: bool; java_generic_services: bool; py_generic_services: bool; java_generate_equals_and_hash: bool option; deprecated: bool; java_string_check_utf8: bool; cc_enable_arenas: bool; objc_class_prefix: string option; csharp_namespace: string option; swift_prefix: string option; php_class_prefix: string option; php_namespace: string option; php_generic_services: bool; php_metadata_namespace: string option; ruby_package: string option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?java_package:string -> ?java_outer_classname:string -> ?optimize_for:OptimizeMode.t -> ?java_multiple_files:bool -> ?go_package:string -> ?cc_generic_services:bool -> ?java_generic_services:bool -> ?py_generic_services:bool -> ?java_generate_equals_and_hash:bool -> ?deprecated:bool -> ?java_string_check_utf8:bool -> ?cc_enable_arenas:bool -> ?objc_class_prefix:string -> ?csharp_namespace:string -> ?swift_prefix:string -> ?php_class_prefix:string -> ?php_namespace:string -> ?php_generic_services:bool -> ?php_metadata_namespace:string -> ?ruby_package:string -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -168,6 +182,7 @@ module rec Google : sig val name': unit -> string type t = { message_set_wire_format: bool; no_standard_descriptor_accessor: bool; deprecated: bool; map_entry: bool option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?message_set_wire_format:bool -> ?no_standard_descriptor_accessor:bool -> ?deprecated:bool -> ?map_entry:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -189,6 +204,7 @@ module rec Google : sig val name': unit -> string type t = { ctype: CType.t; packed: bool option; deprecated: bool; lazy': bool; jstype: JSType.t; weak: bool; unverified_lazy: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?ctype:CType.t -> ?packed:bool -> ?deprecated:bool -> ?lazy':bool -> ?jstype:JSType.t -> ?weak:bool -> ?unverified_lazy:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -198,6 +214,7 @@ module rec Google : sig val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -207,6 +224,7 @@ module rec Google : sig val name': unit -> string type t = { allow_alias: bool option; deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?allow_alias:bool -> ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -216,6 +234,7 @@ module rec Google : sig val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -225,6 +244,7 @@ module rec Google : sig val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -240,6 +260,7 @@ module rec Google : sig val name': unit -> string type t = { deprecated: bool; idempotency_level: IdempotencyLevel.t; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?idempotency_level:IdempotencyLevel.t -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -250,6 +271,7 @@ module rec Google : sig val name': unit -> string type t = { name_part: string; is_extension: bool } val make: name_part:string -> is_extension:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -258,6 +280,7 @@ module rec Google : sig val name': unit -> string type t = { name: NamePart.t list; identifier_value: string option; positive_int_value: int option; negative_int_value: int option; double_value: float option; string_value: bytes option; aggregate_value: string option } val make: ?name:NamePart.t list -> ?identifier_value:string -> ?positive_int_value:int -> ?negative_int_value:int -> ?double_value:float -> ?string_value:bytes -> ?aggregate_value:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -268,14 +291,16 @@ module rec Google : sig val name': unit -> string type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } val make: ?path:int list -> ?span:int list -> ?leading_comments:string -> ?trailing_comments:string -> ?leading_detached_comments:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Location.t list + type t = (Location.t list) val make: ?location:Location.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -286,14 +311,16 @@ module rec Google : sig val name': unit -> string type t = { path: int list; source_file: string option; begin': int option; end': int option } val make: ?path:int list -> ?source_file:string -> ?begin':int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Annotation.t list + type t = (Annotation.t list) val make: ?annotation:Annotation.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -304,8 +331,9 @@ end = struct module rec Protobuf : sig module rec FileDescriptorSet : sig val name': unit -> string - type t = FileDescriptorProto.t list + type t = (FileDescriptorProto.t list) val make: ?file:FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -315,6 +343,7 @@ end = struct val name': unit -> string type t = { name: string option; package: string option; dependency: string list; message_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; service: ServiceDescriptorProto.t list; extension: FieldDescriptorProto.t list; options: FileOptions.t option; source_code_info: SourceCodeInfo.t option; public_dependency: int list; weak_dependency: int list; syntax: string option } val make: ?name:string -> ?package:string -> ?dependency:string list -> ?message_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?service:ServiceDescriptorProto.t list -> ?extension:FieldDescriptorProto.t list -> ?options:FileOptions.t -> ?source_code_info:SourceCodeInfo.t -> ?public_dependency:int list -> ?weak_dependency:int list -> ?syntax:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -325,6 +354,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } val make: ?start:int -> ?end':int -> ?options:ExtensionRangeOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -334,6 +364,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -342,6 +373,7 @@ end = struct val name': unit -> string type t = { name: string option; field: FieldDescriptorProto.t list; nested_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; extension_range: ExtensionRange.t list; extension: FieldDescriptorProto.t list; options: MessageOptions.t option; oneof_decl: OneofDescriptorProto.t list; reserved_range: ReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?field:FieldDescriptorProto.t list -> ?nested_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?extension_range:ExtensionRange.t list -> ?extension:FieldDescriptorProto.t list -> ?options:MessageOptions.t -> ?oneof_decl:OneofDescriptorProto.t list -> ?reserved_range:ReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -351,6 +383,7 @@ end = struct val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -372,6 +405,7 @@ end = struct val name': unit -> string type t = { name: string option; extendee: string option; number: int option; label: Label.t option; type': Type.t option; type_name: string option; default_value: string option; options: FieldOptions.t option; oneof_index: int option; json_name: string option; proto3_optional: bool option } val make: ?name:string -> ?extendee:string -> ?number:int -> ?label:Label.t -> ?type':Type.t -> ?type_name:string -> ?default_value:string -> ?options:FieldOptions.t -> ?oneof_index:int -> ?json_name:string -> ?proto3_optional:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -381,6 +415,7 @@ end = struct val name': unit -> string type t = { name: string option; options: OneofOptions.t option } val make: ?name:string -> ?options:OneofOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -391,6 +426,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -399,6 +435,7 @@ end = struct val name': unit -> string type t = { name: string option; value: EnumValueDescriptorProto.t list; options: EnumOptions.t option; reserved_range: EnumReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?value:EnumValueDescriptorProto.t list -> ?options:EnumOptions.t -> ?reserved_range:EnumReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -408,6 +445,7 @@ end = struct val name': unit -> string type t = { name: string option; number: int option; options: EnumValueOptions.t option } val make: ?name:string -> ?number:int -> ?options:EnumValueOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -417,6 +455,7 @@ end = struct val name': unit -> string type t = { name: string option; method': MethodDescriptorProto.t list; options: ServiceOptions.t option } val make: ?name:string -> ?method':MethodDescriptorProto.t list -> ?options:ServiceOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -426,6 +465,7 @@ end = struct val name': unit -> string type t = { name: string option; input_type: string option; output_type: string option; options: MethodOptions.t option; client_streaming: bool; server_streaming: bool } val make: ?name:string -> ?input_type:string -> ?output_type:string -> ?options:MethodOptions.t -> ?client_streaming:bool -> ?server_streaming:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -441,6 +481,7 @@ end = struct val name': unit -> string type t = { java_package: string option; java_outer_classname: string option; optimize_for: OptimizeMode.t; java_multiple_files: bool; go_package: string option; cc_generic_services: bool; java_generic_services: bool; py_generic_services: bool; java_generate_equals_and_hash: bool option; deprecated: bool; java_string_check_utf8: bool; cc_enable_arenas: bool; objc_class_prefix: string option; csharp_namespace: string option; swift_prefix: string option; php_class_prefix: string option; php_namespace: string option; php_generic_services: bool; php_metadata_namespace: string option; ruby_package: string option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?java_package:string -> ?java_outer_classname:string -> ?optimize_for:OptimizeMode.t -> ?java_multiple_files:bool -> ?go_package:string -> ?cc_generic_services:bool -> ?java_generic_services:bool -> ?py_generic_services:bool -> ?java_generate_equals_and_hash:bool -> ?deprecated:bool -> ?java_string_check_utf8:bool -> ?cc_enable_arenas:bool -> ?objc_class_prefix:string -> ?csharp_namespace:string -> ?swift_prefix:string -> ?php_class_prefix:string -> ?php_namespace:string -> ?php_generic_services:bool -> ?php_metadata_namespace:string -> ?ruby_package:string -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -450,6 +491,7 @@ end = struct val name': unit -> string type t = { message_set_wire_format: bool; no_standard_descriptor_accessor: bool; deprecated: bool; map_entry: bool option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?message_set_wire_format:bool -> ?no_standard_descriptor_accessor:bool -> ?deprecated:bool -> ?map_entry:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -471,6 +513,7 @@ end = struct val name': unit -> string type t = { ctype: CType.t; packed: bool option; deprecated: bool; lazy': bool; jstype: JSType.t; weak: bool; unverified_lazy: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?ctype:CType.t -> ?packed:bool -> ?deprecated:bool -> ?lazy':bool -> ?jstype:JSType.t -> ?weak:bool -> ?unverified_lazy:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -480,6 +523,7 @@ end = struct val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -489,6 +533,7 @@ end = struct val name': unit -> string type t = { allow_alias: bool option; deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?allow_alias:bool -> ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -498,6 +543,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -507,6 +553,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -522,6 +569,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; idempotency_level: IdempotencyLevel.t; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?idempotency_level:IdempotencyLevel.t -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -532,6 +580,7 @@ end = struct val name': unit -> string type t = { name_part: string; is_extension: bool } val make: name_part:string -> is_extension:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -540,6 +589,7 @@ end = struct val name': unit -> string type t = { name: NamePart.t list; identifier_value: string option; positive_int_value: int option; negative_int_value: int option; double_value: float option; string_value: bytes option; aggregate_value: string option } val make: ?name:NamePart.t list -> ?identifier_value:string -> ?positive_int_value:int -> ?negative_int_value:int -> ?double_value:float -> ?string_value:bytes -> ?aggregate_value:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -550,14 +600,16 @@ end = struct val name': unit -> string type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } val make: ?path:int list -> ?span:int list -> ?leading_comments:string -> ?trailing_comments:string -> ?leading_detached_comments:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Location.t list + type t = (Location.t list) val make: ?location:Location.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -568,14 +620,16 @@ end = struct val name': unit -> string type t = { path: int list; source_file: string option; begin': int option; end': int option } val make: ?path:int list -> ?source_file:string -> ?begin':int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Annotation.t list + type t = (Annotation.t list) val make: ?annotation:Annotation.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -584,25 +638,30 @@ end = struct end = struct module rec FileDescriptorSet : sig val name': unit -> string - type t = FileDescriptorProto.t list + type t = (FileDescriptorProto.t list) val make: ?file:FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end = struct let name' () = "descriptor.google.protobuf.FileDescriptorSet" - type t = FileDescriptorProto.t list - let make ?(file = []) () = file + type t = (FileDescriptorProto.t list) + let make ?(file = []) () = (file) + let merge = (fun (t1_file) (t2_file) -> + let file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> FileDescriptorProto.from_proto_exn writer), FileDescriptorProto.merge)), not_packed) ) t1_file t2_file in + + (file)) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (1, (message (fun t -> FileDescriptorProto.to_proto' t)), not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( repeated (1, (message FileDescriptorProto.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in serialize let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = - let constructor = fun file -> file in - let spec = Runtime'.Deserialize.C.( repeated (1, (message (fun t -> FileDescriptorProto.from_proto_exn t)), not_packed) ^:: nil ) in + let constructor = fun file -> (file) in + let spec = Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> FileDescriptorProto.from_proto_exn writer), FileDescriptorProto.merge)), not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -610,6 +669,7 @@ end = struct val name': unit -> string type t = { name: string option; package: string option; dependency: string list; message_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; service: ServiceDescriptorProto.t list; extension: FieldDescriptorProto.t list; options: FileOptions.t option; source_code_info: SourceCodeInfo.t option; public_dependency: int list; weak_dependency: int list; syntax: string option } val make: ?name:string -> ?package:string -> ?dependency:string list -> ?message_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?service:ServiceDescriptorProto.t list -> ?extension:FieldDescriptorProto.t list -> ?options:FileOptions.t -> ?source_code_info:SourceCodeInfo.t -> ?public_dependency:int list -> ?weak_dependency:int list -> ?syntax:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -618,15 +678,41 @@ end = struct let name' () = "descriptor.google.protobuf.FileDescriptorProto" type t = { name: string option; package: string option; dependency: string list; message_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; service: ServiceDescriptorProto.t list; extension: FieldDescriptorProto.t list; options: FileOptions.t option; source_code_info: SourceCodeInfo.t option; public_dependency: int list; weak_dependency: int list; syntax: string option } let make ?name ?package ?(dependency = []) ?(message_type = []) ?(enum_type = []) ?(service = []) ?(extension = []) ?options ?source_code_info ?(public_dependency = []) ?(weak_dependency = []) ?syntax () = { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.package t2.package in + + let dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, string, not_packed) ) t1.dependency t2.dependency in + + let message_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.message_type t2.message_type in + + let enum_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type in + + let service = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> ServiceDescriptorProto.from_proto_exn writer), ServiceDescriptorProto.merge)), not_packed) ) t1.service t2.service in + + let extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (7, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FileOptions.from_proto_exn writer), FileOptions.merge))) ) t1.options t2.options in + + let source_code_info = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, (message ((fun writer -> SourceCodeInfo.from_proto_exn writer), SourceCodeInfo.merge))) ) t1.source_code_info t2.source_code_info in + + let public_dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, int32_int, not_packed) ) t1.public_dependency t2.public_dependency in + + let weak_dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (11, int32_int, not_packed) ) t1.weak_dependency t2.weak_dependency in + + let syntax = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (12, string) ) t1.syntax t2.syntax in + + { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: repeated (3, string, not_packed) ^:: repeated (4, (message (fun t -> DescriptorProto.to_proto' t)), not_packed) ^:: repeated (5, (message (fun t -> EnumDescriptorProto.to_proto' t)), not_packed) ^:: repeated (6, (message (fun t -> ServiceDescriptorProto.to_proto' t)), not_packed) ^:: repeated (7, (message (fun t -> FieldDescriptorProto.to_proto' t)), not_packed) ^:: basic_opt (8, (message (fun t -> FileOptions.to_proto' t))) ^:: basic_opt (9, (message (fun t -> SourceCodeInfo.to_proto' t))) ^:: repeated (10, int32_int, not_packed) ^:: repeated (11, int32_int, not_packed) ^:: basic_opt (12, string) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: repeated (3, string, not_packed) ^:: repeated (4, (message DescriptorProto.to_proto'), not_packed) ^:: repeated (5, (message EnumDescriptorProto.to_proto'), not_packed) ^:: repeated (6, (message ServiceDescriptorProto.to_proto'), not_packed) ^:: repeated (7, (message FieldDescriptorProto.to_proto'), not_packed) ^:: basic_opt (8, (message FileOptions.to_proto')) ^:: basic_opt (9, (message SourceCodeInfo.to_proto')) ^:: repeated (10, int32_int, not_packed) ^:: repeated (11, int32_int, not_packed) ^:: basic_opt (12, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax } -> serialize writer name package dependency message_type enum_type service extension options source_code_info public_dependency weak_dependency syntax let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name package dependency message_type enum_type service extension options source_code_info public_dependency weak_dependency syntax -> { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: repeated (3, string, not_packed) ^:: repeated (4, (message (fun t -> DescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (5, (message (fun t -> EnumDescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (6, (message (fun t -> ServiceDescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (7, (message (fun t -> FieldDescriptorProto.from_proto_exn t)), not_packed) ^:: basic_opt (8, (message (fun t -> FileOptions.from_proto_exn t))) ^:: basic_opt (9, (message (fun t -> SourceCodeInfo.from_proto_exn t))) ^:: repeated (10, int32_int, not_packed) ^:: repeated (11, int32_int, not_packed) ^:: basic_opt (12, string) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: repeated (3, string, not_packed) ^:: repeated (4, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ^:: repeated (5, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ^:: repeated (6, (message ((fun writer -> ServiceDescriptorProto.from_proto_exn writer), ServiceDescriptorProto.merge)), not_packed) ^:: repeated (7, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ^:: basic_opt (8, (message ((fun writer -> FileOptions.from_proto_exn writer), FileOptions.merge))) ^:: basic_opt (9, (message ((fun writer -> SourceCodeInfo.from_proto_exn writer), SourceCodeInfo.merge))) ^:: repeated (10, int32_int, not_packed) ^:: repeated (11, int32_int, not_packed) ^:: basic_opt (12, string) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -635,6 +721,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } val make: ?start:int -> ?end':int -> ?options:ExtensionRangeOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -644,6 +731,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -652,6 +740,7 @@ end = struct val name': unit -> string type t = { name: string option; field: FieldDescriptorProto.t list; nested_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; extension_range: ExtensionRange.t list; extension: FieldDescriptorProto.t list; options: MessageOptions.t option; oneof_decl: OneofDescriptorProto.t list; reserved_range: ReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?field:FieldDescriptorProto.t list -> ?nested_type:DescriptorProto.t list -> ?enum_type:EnumDescriptorProto.t list -> ?extension_range:ExtensionRange.t list -> ?extension:FieldDescriptorProto.t list -> ?options:MessageOptions.t -> ?oneof_decl:OneofDescriptorProto.t list -> ?reserved_range:ReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -661,6 +750,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } val make: ?start:int -> ?end':int -> ?options:ExtensionRangeOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -669,15 +759,23 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto.ExtensionRange" type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } let make ?start ?end' ?options () = { start; end'; options } + let merge = (fun t1 t2 -> + let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in + + let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ExtensionRangeOptions.from_proto_exn writer), ExtensionRangeOptions.merge))) ) t1.options t2.options in + + { start; end'; options }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message (fun t -> ExtensionRangeOptions.to_proto' t))) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message ExtensionRangeOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { start; end'; options } -> serialize writer start end' options let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun start end' options -> { start; end'; options } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message (fun t -> ExtensionRangeOptions.from_proto_exn t))) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message ((fun writer -> ExtensionRangeOptions.from_proto_exn writer), ExtensionRangeOptions.merge))) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -685,6 +783,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -693,6 +792,12 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto.ReservedRange" type t = { start: int option; end': int option } let make ?start ?end' () = { start; end' } + let merge = (fun t1 t2 -> + let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in + + let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in + + { start; end' }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -708,15 +813,37 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto" type t = { name: string option; field: FieldDescriptorProto.t list; nested_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; extension_range: ExtensionRange.t list; extension: FieldDescriptorProto.t list; options: MessageOptions.t option; oneof_decl: OneofDescriptorProto.t list; reserved_range: ReservedRange.t list; reserved_name: string list } let make ?name ?(field = []) ?(nested_type = []) ?(enum_type = []) ?(extension_range = []) ?(extension = []) ?options ?(oneof_decl = []) ?(reserved_range = []) ?(reserved_name = []) () = { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let field = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.field t2.field in + + let nested_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.nested_type t2.nested_type in + + let enum_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type in + + let extension_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> ExtensionRange.from_proto_exn writer), ExtensionRange.merge)), not_packed) ) t1.extension_range t2.extension_range in + + let extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, (message ((fun writer -> MessageOptions.from_proto_exn writer), MessageOptions.merge))) ) t1.options t2.options in + + let oneof_decl = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (8, (message ((fun writer -> OneofDescriptorProto.from_proto_exn writer), OneofDescriptorProto.merge)), not_packed) ) t1.oneof_decl t2.oneof_decl in + + let reserved_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (9, (message ((fun writer -> ReservedRange.from_proto_exn writer), ReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range in + + let reserved_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, string, not_packed) ) t1.reserved_name t2.reserved_name in + + { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> FieldDescriptorProto.to_proto' t)), not_packed) ^:: repeated (3, (message (fun t -> DescriptorProto.to_proto' t)), not_packed) ^:: repeated (4, (message (fun t -> EnumDescriptorProto.to_proto' t)), not_packed) ^:: repeated (5, (message (fun t -> ExtensionRange.to_proto' t)), not_packed) ^:: repeated (6, (message (fun t -> FieldDescriptorProto.to_proto' t)), not_packed) ^:: basic_opt (7, (message (fun t -> MessageOptions.to_proto' t))) ^:: repeated (8, (message (fun t -> OneofDescriptorProto.to_proto' t)), not_packed) ^:: repeated (9, (message (fun t -> ReservedRange.to_proto' t)), not_packed) ^:: repeated (10, string, not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message FieldDescriptorProto.to_proto'), not_packed) ^:: repeated (3, (message DescriptorProto.to_proto'), not_packed) ^:: repeated (4, (message EnumDescriptorProto.to_proto'), not_packed) ^:: repeated (5, (message ExtensionRange.to_proto'), not_packed) ^:: repeated (6, (message FieldDescriptorProto.to_proto'), not_packed) ^:: basic_opt (7, (message MessageOptions.to_proto')) ^:: repeated (8, (message OneofDescriptorProto.to_proto'), not_packed) ^:: repeated (9, (message ReservedRange.to_proto'), not_packed) ^:: repeated (10, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name } -> serialize writer name field nested_type enum_type extension_range extension options oneof_decl reserved_range reserved_name let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name field nested_type enum_type extension_range extension options oneof_decl reserved_range reserved_name -> { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> FieldDescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (3, (message (fun t -> DescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (4, (message (fun t -> EnumDescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (5, (message (fun t -> ExtensionRange.from_proto_exn t)), not_packed) ^:: repeated (6, (message (fun t -> FieldDescriptorProto.from_proto_exn t)), not_packed) ^:: basic_opt (7, (message (fun t -> MessageOptions.from_proto_exn t))) ^:: repeated (8, (message (fun t -> OneofDescriptorProto.from_proto_exn t)), not_packed) ^:: repeated (9, (message (fun t -> ReservedRange.from_proto_exn t)), not_packed) ^:: repeated (10, string, not_packed) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ^:: repeated (3, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ^:: repeated (4, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ^:: repeated (5, (message ((fun writer -> ExtensionRange.from_proto_exn writer), ExtensionRange.merge)), not_packed) ^:: repeated (6, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ^:: basic_opt (7, (message ((fun writer -> MessageOptions.from_proto_exn writer), MessageOptions.merge))) ^:: repeated (8, (message ((fun writer -> OneofDescriptorProto.from_proto_exn writer), OneofDescriptorProto.merge)), not_packed) ^:: repeated (9, (message ((fun writer -> ReservedRange.from_proto_exn writer), ReservedRange.merge)), not_packed) ^:: repeated (10, string, not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -724,6 +851,7 @@ end = struct val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -732,15 +860,20 @@ end = struct let name' () = "descriptor.google.protobuf.ExtensionRangeOptions" type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { uninterpreted_option; extensions' } -> serialize writer uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun uninterpreted_option extensions' -> { uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -760,6 +893,7 @@ end = struct val name': unit -> string type t = { name: string option; extendee: string option; number: int option; label: Label.t option; type': Type.t option; type_name: string option; default_value: string option; options: FieldOptions.t option; oneof_index: int option; json_name: string option; proto3_optional: bool option } val make: ?name:string -> ?extendee:string -> ?number:int -> ?label:Label.t -> ?type':Type.t -> ?type_name:string -> ?default_value:string -> ?options:FieldOptions.t -> ?oneof_index:int -> ?json_name:string -> ?proto3_optional:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -838,15 +972,39 @@ end = struct let name' () = "descriptor.google.protobuf.FieldDescriptorProto" type t = { name: string option; extendee: string option; number: int option; label: Label.t option; type': Type.t option; type_name: string option; default_value: string option; options: FieldOptions.t option; oneof_index: int option; json_name: string option; proto3_optional: bool option } let make ?name ?extendee ?number ?label ?type' ?type_name ?default_value ?options ?oneof_index ?json_name ?proto3_optional () = { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let extendee = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.extendee t2.extendee in + + let number = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.number t2.number in + + let label = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (enum Label.from_int_exn)) ) t1.label t2.label in + + let type' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, (enum Type.from_int_exn)) ) t1.type' t2.type' in + + let type_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, string) ) t1.type_name t2.type_name in + + let default_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, string) ) t1.default_value t2.default_value in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FieldOptions.from_proto_exn writer), FieldOptions.merge))) ) t1.options t2.options in + + let oneof_index = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, int32_int) ) t1.oneof_index t2.oneof_index in + + let json_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (10, string) ) t1.json_name t2.json_name in + + let proto3_optional = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (17, bool) ) t1.proto3_optional t2.proto3_optional in + + { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, (enum Label.to_int)) ^:: basic_opt (5, (enum Type.to_int)) ^:: basic_opt (6, string) ^:: basic_opt (7, string) ^:: basic_opt (8, (message (fun t -> FieldOptions.to_proto' t))) ^:: basic_opt (9, int32_int) ^:: basic_opt (10, string) ^:: basic_opt (17, bool) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, (enum Label.to_int)) ^:: basic_opt (5, (enum Type.to_int)) ^:: basic_opt (6, string) ^:: basic_opt (7, string) ^:: basic_opt (8, (message FieldOptions.to_proto')) ^:: basic_opt (9, int32_int) ^:: basic_opt (10, string) ^:: basic_opt (17, bool) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional } -> serialize writer name extendee number label type' type_name default_value options oneof_index json_name proto3_optional let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name extendee number label type' type_name default_value options oneof_index json_name proto3_optional -> { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, (enum Label.from_int_exn)) ^:: basic_opt (5, (enum Type.from_int_exn)) ^:: basic_opt (6, string) ^:: basic_opt (7, string) ^:: basic_opt (8, (message (fun t -> FieldOptions.from_proto_exn t))) ^:: basic_opt (9, int32_int) ^:: basic_opt (10, string) ^:: basic_opt (17, bool) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, (enum Label.from_int_exn)) ^:: basic_opt (5, (enum Type.from_int_exn)) ^:: basic_opt (6, string) ^:: basic_opt (7, string) ^:: basic_opt (8, (message ((fun writer -> FieldOptions.from_proto_exn writer), FieldOptions.merge))) ^:: basic_opt (9, int32_int) ^:: basic_opt (10, string) ^:: basic_opt (17, bool) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -854,6 +1012,7 @@ end = struct val name': unit -> string type t = { name: string option; options: OneofOptions.t option } val make: ?name:string -> ?options:OneofOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -862,15 +1021,21 @@ end = struct let name' () = "descriptor.google.protobuf.OneofDescriptorProto" type t = { name: string option; options: OneofOptions.t option } let make ?name ?options () = { name; options } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, (message ((fun writer -> OneofOptions.from_proto_exn writer), OneofOptions.merge))) ) t1.options t2.options in + + { name; options }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, (message (fun t -> OneofOptions.to_proto' t))) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, (message OneofOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; options } -> serialize writer name options let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name options -> { name; options } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, (message (fun t -> OneofOptions.from_proto_exn t))) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, (message ((fun writer -> OneofOptions.from_proto_exn writer), OneofOptions.merge))) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -879,6 +1044,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -887,6 +1053,7 @@ end = struct val name': unit -> string type t = { name: string option; value: EnumValueDescriptorProto.t list; options: EnumOptions.t option; reserved_range: EnumReservedRange.t list; reserved_name: string list } val make: ?name:string -> ?value:EnumValueDescriptorProto.t list -> ?options:EnumOptions.t -> ?reserved_range:EnumReservedRange.t list -> ?reserved_name:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -896,6 +1063,7 @@ end = struct val name': unit -> string type t = { start: int option; end': int option } val make: ?start:int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -904,6 +1072,12 @@ end = struct let name' () = "descriptor.google.protobuf.EnumDescriptorProto.EnumReservedRange" type t = { start: int option; end': int option } let make ?start ?end' () = { start; end' } + let merge = (fun t1 t2 -> + let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in + + let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in + + { start; end' }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -919,15 +1093,27 @@ end = struct let name' () = "descriptor.google.protobuf.EnumDescriptorProto" type t = { name: string option; value: EnumValueDescriptorProto.t list; options: EnumOptions.t option; reserved_range: EnumReservedRange.t list; reserved_name: string list } let make ?name ?(value = []) ?options ?(reserved_range = []) ?(reserved_name = []) () = { name; value; options; reserved_range; reserved_name } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let value = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> EnumValueDescriptorProto.from_proto_exn writer), EnumValueDescriptorProto.merge)), not_packed) ) t1.value t2.value in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumOptions.from_proto_exn writer), EnumOptions.merge))) ) t1.options t2.options in + + let reserved_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumReservedRange.from_proto_exn writer), EnumReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range in + + let reserved_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, string, not_packed) ) t1.reserved_name t2.reserved_name in + + { name; value; options; reserved_range; reserved_name }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> EnumValueDescriptorProto.to_proto' t)), not_packed) ^:: basic_opt (3, (message (fun t -> EnumOptions.to_proto' t))) ^:: repeated (4, (message (fun t -> EnumReservedRange.to_proto' t)), not_packed) ^:: repeated (5, string, not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message EnumValueDescriptorProto.to_proto'), not_packed) ^:: basic_opt (3, (message EnumOptions.to_proto')) ^:: repeated (4, (message EnumReservedRange.to_proto'), not_packed) ^:: repeated (5, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; value; options; reserved_range; reserved_name } -> serialize writer name value options reserved_range reserved_name let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name value options reserved_range reserved_name -> { name; value; options; reserved_range; reserved_name } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> EnumValueDescriptorProto.from_proto_exn t)), not_packed) ^:: basic_opt (3, (message (fun t -> EnumOptions.from_proto_exn t))) ^:: repeated (4, (message (fun t -> EnumReservedRange.from_proto_exn t)), not_packed) ^:: repeated (5, string, not_packed) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message ((fun writer -> EnumValueDescriptorProto.from_proto_exn writer), EnumValueDescriptorProto.merge)), not_packed) ^:: basic_opt (3, (message ((fun writer -> EnumOptions.from_proto_exn writer), EnumOptions.merge))) ^:: repeated (4, (message ((fun writer -> EnumReservedRange.from_proto_exn writer), EnumReservedRange.merge)), not_packed) ^:: repeated (5, string, not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -935,6 +1121,7 @@ end = struct val name': unit -> string type t = { name: string option; number: int option; options: EnumValueOptions.t option } val make: ?name:string -> ?number:int -> ?options:EnumValueOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -943,15 +1130,23 @@ end = struct let name' () = "descriptor.google.protobuf.EnumValueDescriptorProto" type t = { name: string option; number: int option; options: EnumValueOptions.t option } let make ?name ?number ?options () = { name; number; options } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let number = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.number t2.number in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumValueOptions.from_proto_exn writer), EnumValueOptions.merge))) ) t1.options t2.options in + + { name; number; options }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message (fun t -> EnumValueOptions.to_proto' t))) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message EnumValueOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; number; options } -> serialize writer name number options let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name number options -> { name; number; options } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message (fun t -> EnumValueOptions.from_proto_exn t))) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message ((fun writer -> EnumValueOptions.from_proto_exn writer), EnumValueOptions.merge))) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -959,6 +1154,7 @@ end = struct val name': unit -> string type t = { name: string option; method': MethodDescriptorProto.t list; options: ServiceOptions.t option } val make: ?name:string -> ?method':MethodDescriptorProto.t list -> ?options:ServiceOptions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -967,15 +1163,23 @@ end = struct let name' () = "descriptor.google.protobuf.ServiceDescriptorProto" type t = { name: string option; method': MethodDescriptorProto.t list; options: ServiceOptions.t option } let make ?name ?(method' = []) ?options () = { name; method'; options } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let method' = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> MethodDescriptorProto.from_proto_exn writer), MethodDescriptorProto.merge)), not_packed) ) t1.method' t2.method' in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ServiceOptions.from_proto_exn writer), ServiceOptions.merge))) ) t1.options t2.options in + + { name; method'; options }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> MethodDescriptorProto.to_proto' t)), not_packed) ^:: basic_opt (3, (message (fun t -> ServiceOptions.to_proto' t))) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message MethodDescriptorProto.to_proto'), not_packed) ^:: basic_opt (3, (message ServiceOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; method'; options } -> serialize writer name method' options let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name method' options -> { name; method'; options } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message (fun t -> MethodDescriptorProto.from_proto_exn t)), not_packed) ^:: basic_opt (3, (message (fun t -> ServiceOptions.from_proto_exn t))) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: repeated (2, (message ((fun writer -> MethodDescriptorProto.from_proto_exn writer), MethodDescriptorProto.merge)), not_packed) ^:: basic_opt (3, (message ((fun writer -> ServiceOptions.from_proto_exn writer), ServiceOptions.merge))) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -983,6 +1187,7 @@ end = struct val name': unit -> string type t = { name: string option; input_type: string option; output_type: string option; options: MethodOptions.t option; client_streaming: bool; server_streaming: bool } val make: ?name:string -> ?input_type:string -> ?output_type:string -> ?options:MethodOptions.t -> ?client_streaming:bool -> ?server_streaming:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -991,15 +1196,29 @@ end = struct let name' () = "descriptor.google.protobuf.MethodDescriptorProto" type t = { name: string option; input_type: string option; output_type: string option; options: MethodOptions.t option; client_streaming: bool; server_streaming: bool } let make ?name ?input_type ?output_type ?options ?(client_streaming = false) ?(server_streaming = false) () = { name; input_type; output_type; options; client_streaming; server_streaming } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let input_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.input_type t2.input_type in + + let output_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.output_type t2.output_type in + + let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ) t1.options t2.options in + + let client_streaming = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, Some (false)) ) t1.client_streaming t2.client_streaming in + + let server_streaming = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, bool, Some (false)) ) t1.server_streaming t2.server_streaming in + + { name; input_type; output_type; options; client_streaming; server_streaming }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message (fun t -> MethodOptions.to_proto' t))) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message MethodOptions.to_proto')) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; input_type; output_type; options; client_streaming; server_streaming } -> serialize writer name input_type output_type options client_streaming server_streaming let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name input_type output_type options client_streaming server_streaming -> { name; input_type; output_type; options; client_streaming; server_streaming } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message (fun t -> MethodOptions.from_proto_exn t))) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1013,6 +1232,7 @@ end = struct val name': unit -> string type t = { java_package: string option; java_outer_classname: string option; optimize_for: OptimizeMode.t; java_multiple_files: bool; go_package: string option; cc_generic_services: bool; java_generic_services: bool; py_generic_services: bool; java_generate_equals_and_hash: bool option; deprecated: bool; java_string_check_utf8: bool; cc_enable_arenas: bool; objc_class_prefix: string option; csharp_namespace: string option; swift_prefix: string option; php_class_prefix: string option; php_namespace: string option; php_generic_services: bool; php_metadata_namespace: string option; ruby_package: string option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?java_package:string -> ?java_outer_classname:string -> ?optimize_for:OptimizeMode.t -> ?java_multiple_files:bool -> ?go_package:string -> ?cc_generic_services:bool -> ?java_generic_services:bool -> ?py_generic_services:bool -> ?java_generate_equals_and_hash:bool -> ?deprecated:bool -> ?java_string_check_utf8:bool -> ?cc_enable_arenas:bool -> ?objc_class_prefix:string -> ?csharp_namespace:string -> ?swift_prefix:string -> ?php_class_prefix:string -> ?php_namespace:string -> ?php_generic_services:bool -> ?php_metadata_namespace:string -> ?ruby_package:string -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1041,15 +1261,60 @@ end = struct let name' () = "descriptor.google.protobuf.FileOptions" type t = { java_package: string option; java_outer_classname: string option; optimize_for: OptimizeMode.t; java_multiple_files: bool; go_package: string option; cc_generic_services: bool; java_generic_services: bool; py_generic_services: bool; java_generate_equals_and_hash: bool option; deprecated: bool; java_string_check_utf8: bool; cc_enable_arenas: bool; objc_class_prefix: string option; csharp_namespace: string option; swift_prefix: string option; php_class_prefix: string option; php_namespace: string option; php_generic_services: bool; php_metadata_namespace: string option; ruby_package: string option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?java_package ?java_outer_classname ?(optimize_for = OptimizeMode.SPEED) ?(java_multiple_files = false) ?go_package ?(cc_generic_services = false) ?(java_generic_services = false) ?(py_generic_services = false) ?java_generate_equals_and_hash ?(deprecated = false) ?(java_string_check_utf8 = false) ?(cc_enable_arenas = true) ?objc_class_prefix ?csharp_namespace ?swift_prefix ?php_class_prefix ?php_namespace ?(php_generic_services = false) ?php_metadata_namespace ?ruby_package ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let java_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.java_package t2.java_package in + + let java_outer_classname = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.java_outer_classname t2.java_outer_classname in + + let optimize_for = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (9, (enum OptimizeMode.from_int_exn), Some (OptimizeMode.SPEED)) ) t1.optimize_for t2.optimize_for in + + let java_multiple_files = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, Some (false)) ) t1.java_multiple_files t2.java_multiple_files in + + let go_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (11, string) ) t1.go_package t2.go_package in + + let cc_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (16, bool, Some (false)) ) t1.cc_generic_services t2.cc_generic_services in + + let java_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (17, bool, Some (false)) ) t1.java_generic_services t2.java_generic_services in + + let py_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (18, bool, Some (false)) ) t1.py_generic_services t2.py_generic_services in + + let java_generate_equals_and_hash = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (20, bool) ) t1.java_generate_equals_and_hash t2.java_generate_equals_and_hash in + + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (23, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let java_string_check_utf8 = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (27, bool, Some (false)) ) t1.java_string_check_utf8 t2.java_string_check_utf8 in + + let cc_enable_arenas = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (31, bool, Some (true)) ) t1.cc_enable_arenas t2.cc_enable_arenas in + + let objc_class_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (36, string) ) t1.objc_class_prefix t2.objc_class_prefix in + + let csharp_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (37, string) ) t1.csharp_namespace t2.csharp_namespace in + + let swift_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (39, string) ) t1.swift_prefix t2.swift_prefix in + + let php_class_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (40, string) ) t1.php_class_prefix t2.php_class_prefix in + + let php_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (41, string) ) t1.php_namespace t2.php_namespace in + + let php_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (42, bool, Some (false)) ) t1.php_generic_services t2.php_generic_services in + + let php_metadata_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (44, string) ) t1.php_metadata_namespace t2.php_metadata_namespace in + + let ruby_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (45, string) ) t1.ruby_package t2.ruby_package in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.to_int), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.to_int), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } -> serialize writer java_package java_outer_classname optimize_for java_multiple_files go_package cc_generic_services java_generic_services py_generic_services java_generate_equals_and_hash deprecated java_string_check_utf8 cc_enable_arenas objc_class_prefix csharp_namespace swift_prefix php_class_prefix php_namespace php_generic_services php_metadata_namespace ruby_package uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun java_package java_outer_classname optimize_for java_multiple_files go_package cc_generic_services java_generic_services py_generic_services java_generate_equals_and_hash deprecated java_string_check_utf8 cc_enable_arenas objc_class_prefix csharp_namespace swift_prefix php_class_prefix php_namespace php_generic_services php_metadata_namespace ruby_package uninterpreted_option extensions' -> { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.from_int_exn), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.from_int_exn), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1057,6 +1322,7 @@ end = struct val name': unit -> string type t = { message_set_wire_format: bool; no_standard_descriptor_accessor: bool; deprecated: bool; map_entry: bool option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?message_set_wire_format:bool -> ?no_standard_descriptor_accessor:bool -> ?deprecated:bool -> ?map_entry:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1065,15 +1331,28 @@ end = struct let name' () = "descriptor.google.protobuf.MessageOptions" type t = { message_set_wire_format: bool; no_standard_descriptor_accessor: bool; deprecated: bool; map_entry: bool option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(message_set_wire_format = false) ?(no_standard_descriptor_accessor = false) ?(deprecated = false) ?map_entry ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let message_set_wire_format = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1.message_set_wire_format t2.message_set_wire_format in + + let no_standard_descriptor_accessor = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (2, bool, Some (false)) ) t1.no_standard_descriptor_accessor t2.no_standard_descriptor_accessor in + + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let map_entry = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bool) ) t1.map_entry t2.map_entry in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } -> serialize writer message_set_wire_format no_standard_descriptor_accessor deprecated map_entry uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun message_set_wire_format no_standard_descriptor_accessor deprecated map_entry uninterpreted_option extensions' -> { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1093,6 +1372,7 @@ end = struct val name': unit -> string type t = { ctype: CType.t; packed: bool option; deprecated: bool; lazy': bool; jstype: JSType.t; weak: bool; unverified_lazy: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?ctype:CType.t -> ?packed:bool -> ?deprecated:bool -> ?lazy':bool -> ?jstype:JSType.t -> ?weak:bool -> ?unverified_lazy:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1141,15 +1421,34 @@ end = struct let name' () = "descriptor.google.protobuf.FieldOptions" type t = { ctype: CType.t; packed: bool option; deprecated: bool; lazy': bool; jstype: JSType.t; weak: bool; unverified_lazy: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(ctype = CType.STRING) ?packed ?(deprecated = false) ?(lazy' = false) ?(jstype = JSType.JS_NORMAL) ?(weak = false) ?(unverified_lazy = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let ctype = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), Some (CType.STRING)) ) t1.ctype t2.ctype in + + let packed = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.packed t2.packed in + + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let lazy' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, Some (false)) ) t1.lazy' t2.lazy' in + + let jstype = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, (enum JSType.from_int_exn), Some (JSType.JS_NORMAL)) ) t1.jstype t2.jstype in + + let weak = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, Some (false)) ) t1.weak t2.weak in + + let unverified_lazy = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (15, bool, Some (false)) ) t1.unverified_lazy t2.unverified_lazy in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, (enum CType.to_int), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.to_int), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, (enum CType.to_int), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.to_int), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } -> serialize writer ctype packed deprecated lazy' jstype weak unverified_lazy uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun ctype packed deprecated lazy' jstype weak unverified_lazy uninterpreted_option extensions' -> { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.from_int_exn), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.from_int_exn), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1157,6 +1456,7 @@ end = struct val name': unit -> string type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1165,15 +1465,20 @@ end = struct let name' () = "descriptor.google.protobuf.OneofOptions" type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { uninterpreted_option; extensions' } -> serialize writer uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun uninterpreted_option extensions' -> { uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1181,6 +1486,7 @@ end = struct val name': unit -> string type t = { allow_alias: bool option; deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?allow_alias:bool -> ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1189,15 +1495,24 @@ end = struct let name' () = "descriptor.google.protobuf.EnumOptions" type t = { allow_alias: bool option; deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?allow_alias ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { allow_alias; deprecated; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let allow_alias = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.allow_alias t2.allow_alias in + + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { allow_alias; deprecated; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { allow_alias; deprecated; uninterpreted_option; extensions' } -> serialize writer allow_alias deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun allow_alias deprecated uninterpreted_option extensions' -> { allow_alias; deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1205,6 +1520,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1213,15 +1529,22 @@ end = struct let name' () = "descriptor.google.protobuf.EnumValueOptions" type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { deprecated; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; uninterpreted_option; extensions' } -> serialize writer deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated uninterpreted_option extensions' -> { deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1229,6 +1552,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1237,15 +1561,22 @@ end = struct let name' () = "descriptor.google.protobuf.ServiceOptions" type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { deprecated; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; uninterpreted_option; extensions' } -> serialize writer deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated uninterpreted_option extensions' -> { deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1259,6 +1590,7 @@ end = struct val name': unit -> string type t = { deprecated: bool; idempotency_level: IdempotencyLevel.t; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } val make: ?deprecated:bool -> ?idempotency_level:IdempotencyLevel.t -> ?uninterpreted_option:UninterpretedOption.t list -> ?extensions':Runtime'.Extensions.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1287,15 +1619,24 @@ end = struct let name' () = "descriptor.google.protobuf.MethodOptions" type t = { deprecated: bool; idempotency_level: IdempotencyLevel.t; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(idempotency_level = IdempotencyLevel.IDEMPOTENCY_UNKNOWN) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; idempotency_level; uninterpreted_option; extensions' } + let merge = (fun t1 t2 -> + let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ) t1.deprecated t2.deprecated in + + let idempotency_level = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (34, (enum IdempotencyLevel.from_int_exn), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ) t1.idempotency_level t2.idempotency_level in + + let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in + + let extensions' = List.append t1.extensions' t2.extensions' in + { deprecated; idempotency_level; uninterpreted_option; extensions' }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.to_int), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message (fun t -> UninterpretedOption.to_proto' t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.to_int), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; idempotency_level; uninterpreted_option; extensions' } -> serialize writer deprecated idempotency_level uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated idempotency_level uninterpreted_option extensions' -> { deprecated; idempotency_level; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.from_int_exn), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message (fun t -> UninterpretedOption.from_proto_exn t)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.from_int_exn), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1304,6 +1645,7 @@ end = struct val name': unit -> string type t = { name_part: string; is_extension: bool } val make: name_part:string -> is_extension:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1312,6 +1654,7 @@ end = struct val name': unit -> string type t = { name: NamePart.t list; identifier_value: string option; positive_int_value: int option; negative_int_value: int option; double_value: float option; string_value: bytes option; aggregate_value: string option } val make: ?name:NamePart.t list -> ?identifier_value:string -> ?positive_int_value:int -> ?negative_int_value:int -> ?double_value:float -> ?string_value:bytes -> ?aggregate_value:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1321,6 +1664,7 @@ end = struct val name': unit -> string type t = { name_part: string; is_extension: bool } val make: name_part:string -> is_extension:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1329,6 +1673,12 @@ end = struct let name' () = "descriptor.google.protobuf.UninterpretedOption.NamePart" type t = { name_part: string; is_extension: bool } let make ~name_part ~is_extension () = { name_part; is_extension } + let merge = (fun t1 t2 -> + let name_part = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, string, None) ) t1.name_part t2.name_part in + + let is_extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (2, bool, None) ) t1.is_extension t2.is_extension in + + { name_part; is_extension }) let to_proto' = let spec = Runtime'.Serialize.C.( basic (1, string, None) ^:: basic (2, bool, None) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1344,15 +1694,31 @@ end = struct let name' () = "descriptor.google.protobuf.UninterpretedOption" type t = { name: NamePart.t list; identifier_value: string option; positive_int_value: int option; negative_int_value: int option; double_value: float option; string_value: bytes option; aggregate_value: string option } let make ?(name = []) ?identifier_value ?positive_int_value ?negative_int_value ?double_value ?string_value ?aggregate_value () = { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> NamePart.from_proto_exn writer), NamePart.merge)), not_packed) ) t1.name t2.name in + + let identifier_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.identifier_value t2.identifier_value in + + let positive_int_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, uint64_int) ) t1.positive_int_value t2.positive_int_value in + + let negative_int_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, int64_int) ) t1.negative_int_value t2.negative_int_value in + + let double_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, double) ) t1.double_value t2.double_value in + + let string_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bytes) ) t1.string_value t2.string_value in + + let aggregate_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.aggregate_value t2.aggregate_value in + + { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value }) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (2, (message (fun t -> NamePart.to_proto' t)), not_packed) ^:: basic_opt (3, string) ^:: basic_opt (4, uint64_int) ^:: basic_opt (5, int64_int) ^:: basic_opt (6, double) ^:: basic_opt (7, bytes) ^:: basic_opt (8, string) ^:: nil ) in + let spec = Runtime'.Serialize.C.( repeated (2, (message NamePart.to_proto'), not_packed) ^:: basic_opt (3, string) ^:: basic_opt (4, uint64_int) ^:: basic_opt (5, int64_int) ^:: basic_opt (6, double) ^:: basic_opt (7, bytes) ^:: basic_opt (8, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value } -> serialize writer name identifier_value positive_int_value negative_int_value double_value string_value aggregate_value let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name identifier_value positive_int_value negative_int_value double_value string_value aggregate_value -> { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value } in - let spec = Runtime'.Deserialize.C.( repeated (2, (message (fun t -> NamePart.from_proto_exn t)), not_packed) ^:: basic_opt (3, string) ^:: basic_opt (4, uint64_int) ^:: basic_opt (5, int64_int) ^:: basic_opt (6, double) ^:: basic_opt (7, bytes) ^:: basic_opt (8, string) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> NamePart.from_proto_exn writer), NamePart.merge)), not_packed) ^:: basic_opt (3, string) ^:: basic_opt (4, uint64_int) ^:: basic_opt (5, int64_int) ^:: basic_opt (6, double) ^:: basic_opt (7, bytes) ^:: basic_opt (8, string) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1361,14 +1727,16 @@ end = struct val name': unit -> string type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } val make: ?path:int list -> ?span:int list -> ?leading_comments:string -> ?trailing_comments:string -> ?leading_detached_comments:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Location.t list + type t = (Location.t list) val make: ?location:Location.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1378,6 +1746,7 @@ end = struct val name': unit -> string type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } val make: ?path:int list -> ?span:int list -> ?leading_comments:string -> ?trailing_comments:string -> ?leading_detached_comments:string list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1386,6 +1755,18 @@ end = struct let name' () = "descriptor.google.protobuf.SourceCodeInfo.Location" type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } let make ?(path = []) ?(span = []) ?leading_comments ?trailing_comments ?(leading_detached_comments = []) () = { path; span; leading_comments; trailing_comments; leading_detached_comments } + let merge = (fun t1 t2 -> + let path = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path in + + let span = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, int32_int, packed) ) t1.span t2.span in + + let leading_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.leading_comments t2.leading_comments in + + let trailing_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.trailing_comments t2.trailing_comments in + + let leading_detached_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, string, not_packed) ) t1.leading_detached_comments t2.leading_detached_comments in + + { path; span; leading_comments; trailing_comments; leading_detached_comments }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, int32_int, packed) ^:: repeated (2, int32_int, packed) ^:: basic_opt (3, string) ^:: basic_opt (4, string) ^:: repeated (6, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1399,17 +1780,21 @@ end = struct let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end let name' () = "descriptor.google.protobuf.SourceCodeInfo" - type t = Location.t list - let make ?(location = []) () = location + type t = (Location.t list) + let make ?(location = []) () = (location) + let merge = (fun (t1_location) (t2_location) -> + let location = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Location.from_proto_exn writer), Location.merge)), not_packed) ) t1_location t2_location in + + (location)) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (1, (message (fun t -> Location.to_proto' t)), not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( repeated (1, (message Location.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in serialize let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = - let constructor = fun location -> location in - let spec = Runtime'.Deserialize.C.( repeated (1, (message (fun t -> Location.from_proto_exn t)), not_packed) ^:: nil ) in + let constructor = fun location -> (location) in + let spec = Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Location.from_proto_exn writer), Location.merge)), not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1418,14 +1803,16 @@ end = struct val name': unit -> string type t = { path: int list; source_file: string option; begin': int option; end': int option } val make: ?path:int list -> ?source_file:string -> ?begin':int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end val name': unit -> string - type t = Annotation.t list + type t = (Annotation.t list) val make: ?annotation:Annotation.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1435,6 +1822,7 @@ end = struct val name': unit -> string type t = { path: int list; source_file: string option; begin': int option; end': int option } val make: ?path:int list -> ?source_file:string -> ?begin':int -> ?end':int -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -1443,6 +1831,16 @@ end = struct let name' () = "descriptor.google.protobuf.GeneratedCodeInfo.Annotation" type t = { path: int list; source_file: string option; begin': int option; end': int option } let make ?(path = []) ?source_file ?begin' ?end' () = { path; source_file; begin'; end' } + let merge = (fun t1 t2 -> + let path = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path in + + let source_file = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.source_file t2.source_file in + + let begin' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.begin' t2.begin' in + + let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, int32_int) ) t1.end' t2.end' in + + { path; source_file; begin'; end' }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, int32_int, packed) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1456,17 +1854,21 @@ end = struct let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end let name' () = "descriptor.google.protobuf.GeneratedCodeInfo" - type t = Annotation.t list - let make ?(annotation = []) () = annotation + type t = (Annotation.t list) + let make ?(annotation = []) () = (annotation) + let merge = (fun (t1_annotation) (t2_annotation) -> + let annotation = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Annotation.from_proto_exn writer), Annotation.merge)), not_packed) ) t1_annotation t2_annotation in + + (annotation)) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (1, (message (fun t -> Annotation.to_proto' t)), not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( repeated (1, (message Annotation.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in serialize let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = - let constructor = fun annotation -> annotation in - let spec = Runtime'.Deserialize.C.( repeated (1, (message (fun t -> Annotation.from_proto_exn t)), not_packed) ^:: nil ) in + let constructor = fun annotation -> (annotation) in + let spec = Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Annotation.from_proto_exn writer), Annotation.merge)), not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end diff --git a/src/spec/options.ml b/src/spec/options.ml index 7a1bac3..7900363 100644 --- a/src/spec/options.ml +++ b/src/spec/options.ml @@ -25,16 +25,21 @@ end (**/**) module rec Options : sig val name': unit -> string - type t = bool + type t = (bool) val make: ?mangle_names:bool -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result val from_proto_exn: Runtime'.Reader.t -> t end = struct let name' () = "options.Options" - type t = bool - let make ?(mangle_names = false) () = mangle_names + type t = (bool) + let make ?(mangle_names = false) () = (mangle_names) + let merge = (fun (t1_mangle_names) (t2_mangle_names) -> + let mangle_names = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1_mangle_names t2_mangle_names in + + (mangle_names)) let to_proto' = let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -42,7 +47,7 @@ end = struct let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = - let constructor = fun mangle_names -> mangle_names in + let constructor = fun mangle_names -> (mangle_names) in let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) @@ -54,10 +59,10 @@ and Ocaml_options : sig val set: Imported'modules.Descriptor.Google.Protobuf.FileOptions.t -> Options.t option -> Imported'modules.Descriptor.Google.Protobuf.FileOptions.t end = struct type t = Options.t option - let get_exn extendee = Runtime'.Extensions.get Runtime'.Deserialize.C.(basic_opt (1074, (message (fun t -> Options.from_proto_exn t)))) (extendee.Imported'modules.Descriptor.Google.Protobuf.FileOptions.extensions') + let get_exn extendee = Runtime'.Extensions.get Runtime'.Deserialize.C.(basic_opt (1074, (message ((fun writer -> Options.from_proto_exn writer), Options.merge)))) (extendee.Imported'modules.Descriptor.Google.Protobuf.FileOptions.extensions') let get extendee = Runtime'.Result.catch (fun () -> get_exn extendee) let set extendee t = - let extensions' = Runtime'.Extensions.set Runtime'.Serialize.C.(basic_opt (1074, (message (fun t -> Options.to_proto' t)))) (extendee.Imported'modules.Descriptor.Google.Protobuf.FileOptions.extensions') t in + let extensions' = Runtime'.Extensions.set Runtime'.Serialize.C.(basic_opt (1074, (message Options.to_proto'))) (extendee.Imported'modules.Descriptor.Google.Protobuf.FileOptions.extensions') t in { extendee with Imported'modules.Descriptor.Google.Protobuf.FileOptions.extensions' = extensions' } [@@warning "-23"] end diff --git a/src/spec/plugin.ml b/src/spec/plugin.ml index eeb454e..954c730 100644 --- a/src/spec/plugin.ml +++ b/src/spec/plugin.ml @@ -30,6 +30,7 @@ module rec Google : sig val name': unit -> string type t = { major: int option; minor: int option; patch: int option; suffix: string option } val make: ?major:int -> ?minor:int -> ?patch:int -> ?suffix:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -39,6 +40,7 @@ module rec Google : sig val name': unit -> string type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } val make: ?file_to_generate:string list -> ?parameter:string -> ?compiler_version:Version.t -> ?proto_file:Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -55,6 +57,7 @@ module rec Google : sig val name': unit -> string type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } val make: ?name:string -> ?insertion_point:string -> ?content:string -> ?generated_code_info:Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -63,6 +66,7 @@ module rec Google : sig val name': unit -> string type t = { error: string option; supported_features: int option; file: File.t list } val make: ?error:string -> ?supported_features:int -> ?file:File.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -77,6 +81,7 @@ end = struct val name': unit -> string type t = { major: int option; minor: int option; patch: int option; suffix: string option } val make: ?major:int -> ?minor:int -> ?patch:int -> ?suffix:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -86,6 +91,7 @@ end = struct val name': unit -> string type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } val make: ?file_to_generate:string list -> ?parameter:string -> ?compiler_version:Version.t -> ?proto_file:Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -102,6 +108,7 @@ end = struct val name': unit -> string type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } val make: ?name:string -> ?insertion_point:string -> ?content:string -> ?generated_code_info:Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -110,6 +117,7 @@ end = struct val name': unit -> string type t = { error: string option; supported_features: int option; file: File.t list } val make: ?error:string -> ?supported_features:int -> ?file:File.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -122,6 +130,7 @@ end = struct val name': unit -> string type t = { major: int option; minor: int option; patch: int option; suffix: string option } val make: ?major:int -> ?minor:int -> ?patch:int -> ?suffix:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -131,6 +140,7 @@ end = struct val name': unit -> string type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } val make: ?file_to_generate:string list -> ?parameter:string -> ?compiler_version:Version.t -> ?proto_file:Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -147,6 +157,7 @@ end = struct val name': unit -> string type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } val make: ?name:string -> ?insertion_point:string -> ?content:string -> ?generated_code_info:Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -155,6 +166,7 @@ end = struct val name': unit -> string type t = { error: string option; supported_features: int option; file: File.t list } val make: ?error:string -> ?supported_features:int -> ?file:File.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -165,6 +177,7 @@ end = struct val name': unit -> string type t = { major: int option; minor: int option; patch: int option; suffix: string option } val make: ?major:int -> ?minor:int -> ?patch:int -> ?suffix:string -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -173,6 +186,16 @@ end = struct let name' () = "plugin.google.protobuf.compiler.Version" type t = { major: int option; minor: int option; patch: int option; suffix: string option } let make ?major ?minor ?patch ?suffix () = { major; minor; patch; suffix } + let merge = (fun t1 t2 -> + let major = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.major t2.major in + + let minor = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.minor t2.minor in + + let patch = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.patch t2.patch in + + let suffix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.suffix t2.suffix in + + { major; minor; patch; suffix }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -189,6 +212,7 @@ end = struct val name': unit -> string type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } val make: ?file_to_generate:string list -> ?parameter:string -> ?compiler_version:Version.t -> ?proto_file:Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -197,15 +221,25 @@ end = struct let name' () = "plugin.google.protobuf.compiler.CodeGeneratorRequest" type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } let make ?(file_to_generate = []) ?parameter ?compiler_version ?(proto_file = []) () = { file_to_generate; parameter; compiler_version; proto_file } + let merge = (fun t1 t2 -> + let file_to_generate = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, string, not_packed) ) t1.file_to_generate t2.file_to_generate in + + let parameter = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.parameter t2.parameter in + + let compiler_version = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> Version.from_proto_exn writer), Version.merge))) ) t1.compiler_version t2.compiler_version in + + let proto_file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.merge)), not_packed) ) t1.proto_file t2.proto_file in + + { file_to_generate; parameter; compiler_version; proto_file }) let to_proto' = - let spec = Runtime'.Serialize.C.( repeated (1, string, not_packed) ^:: basic_opt (2, string) ^:: basic_opt (3, (message (fun t -> Version.to_proto' t))) ^:: repeated (15, (message (fun t -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.to_proto' t)), not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( repeated (1, string, not_packed) ^:: basic_opt (2, string) ^:: basic_opt (3, (message Version.to_proto')) ^:: repeated (15, (message Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { file_to_generate; parameter; compiler_version; proto_file } -> serialize writer file_to_generate parameter compiler_version proto_file let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun file_to_generate parameter compiler_version proto_file -> { file_to_generate; parameter; compiler_version; proto_file } in - let spec = Runtime'.Deserialize.C.( repeated (1, string, not_packed) ^:: basic_opt (2, string) ^:: basic_opt (3, (message (fun t -> Version.from_proto_exn t))) ^:: repeated (15, (message (fun t -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.from_proto_exn t)), not_packed) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( repeated (1, string, not_packed) ^:: basic_opt (2, string) ^:: basic_opt (3, (message ((fun writer -> Version.from_proto_exn writer), Version.merge))) ^:: repeated (15, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.merge)), not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -220,6 +254,7 @@ end = struct val name': unit -> string type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } val make: ?name:string -> ?insertion_point:string -> ?content:string -> ?generated_code_info:Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -228,6 +263,7 @@ end = struct val name': unit -> string type t = { error: string option; supported_features: int option; file: File.t list } val make: ?error:string -> ?supported_features:int -> ?file:File.t list -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -255,6 +291,7 @@ end = struct val name': unit -> string type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } val make: ?name:string -> ?insertion_point:string -> ?content:string -> ?generated_code_info:Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t -> unit -> t + val merge: t -> t -> t val to_proto': Runtime'.Writer.t -> t -> Runtime'.Writer.t val to_proto: t -> Runtime'.Writer.t val from_proto: Runtime'.Reader.t -> (t, [> Runtime'.Result.error]) result @@ -263,30 +300,48 @@ end = struct let name' () = "plugin.google.protobuf.compiler.CodeGeneratorResponse.File" type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } let make ?name ?insertion_point ?content ?generated_code_info () = { name; insertion_point; content; generated_code_info } + let merge = (fun t1 t2 -> + let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in + + let insertion_point = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.insertion_point t2.insertion_point in + + let content = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (15, string) ) t1.content t2.content in + + let generated_code_info = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (16, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.merge))) ) t1.generated_code_info t2.generated_code_info in + + { name; insertion_point; content; generated_code_info }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (15, string) ^:: basic_opt (16, (message (fun t -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.to_proto' t))) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (15, string) ^:: basic_opt (16, (message Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; insertion_point; content; generated_code_info } -> serialize writer name insertion_point content generated_code_info let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name insertion_point content generated_code_info -> { name; insertion_point; content; generated_code_info } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (15, string) ^:: basic_opt (16, (message (fun t -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.from_proto_exn t))) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (15, string) ^:: basic_opt (16, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.merge))) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end let name' () = "plugin.google.protobuf.compiler.CodeGeneratorResponse" type t = { error: string option; supported_features: int option; file: File.t list } let make ?error ?supported_features ?(file = []) () = { error; supported_features; file } + let merge = (fun t1 t2 -> + let error = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.error t2.error in + + let supported_features = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, uint64_int) ) t1.supported_features t2.supported_features in + + let file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> File.from_proto_exn writer), File.merge)), not_packed) ) t1.file t2.file in + + { error; supported_features; file }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, uint64_int) ^:: repeated (15, (message (fun t -> File.to_proto' t)), not_packed) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, uint64_int) ^:: repeated (15, (message File.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { error; supported_features; file } -> serialize writer error supported_features file let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun error supported_features file -> { error; supported_features; file } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, uint64_int) ^:: repeated (15, (message (fun t -> File.from_proto_exn t)), not_packed) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, uint64_int) ^:: repeated (15, (message ((fun writer -> File.from_proto_exn writer), File.merge)), not_packed) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end diff --git a/test/dune b/test/dune index 94800bf..0b9d9c9 100644 --- a/test/dune +++ b/test/dune @@ -36,7 +36,7 @@ (rule (targets basic.ml primitive_types.ml int_types.ml repeated.ml enum.ml empty_message.ml - message.ml oneof.ml map.ml package.ml include.ml included.ml large.ml + message.ml oneof.ml merge.ml map.ml package.ml include.ml included.ml large.ml included2.ml included3_dash.ml service.ml recursive.ml protocol.ml name_clash.ml name_clash_mangle.ml proto2.ml packed.ml mangle_names.ml extensions.ml options.ml name_clash2.ml empty.ml service_rpc_clash.ml service_empty_package.ml) @@ -44,7 +44,7 @@ (:plugin ../src/plugin/protoc_gen_ocaml.exe) (:proto basic.proto primitive_types.proto int_types.proto repeated.proto enum.proto empty_message.proto - message.proto oneof.proto map.proto package.proto large.proto + message.proto oneof.proto merge.proto map.proto package.proto large.proto include.proto included.proto included2.proto included3-dash.proto service.proto recursive.proto protocol.proto name_clash.proto name_clash_mangle.proto proto2.proto packed.proto mangle_names.proto extensions.proto options.proto diff --git a/test/enum_test.ml b/test/enum_test.ml index 9a8ffa7..8d3be19 100644 --- a/test/enum_test.ml +++ b/test/enum_test.ml @@ -14,13 +14,10 @@ let%expect_test _ = let%expect_test _ = let module T = Enum.Aliasing in let t = T.Enum.Z in - Test_lib.test_encode (module T) t; - (* We do expect the enum to be deserialized as Y. *) + (* Due to aliasing, we expect this to be deserialized as 'Y'. *) + Test_lib.test_encode (module T) ~expect:T.Enum.Y t; [%expect {| - e: Y - - Expect :Z - Observed:Y |}] + e: Y |}] let%expect_test _ = let module T = Enum.Negative in diff --git a/test/merge.proto b/test/merge.proto new file mode 100644 index 0000000..ab9116d --- /dev/null +++ b/test/merge.proto @@ -0,0 +1,16 @@ +syntax = "proto3"; + +package merge; + +message T { + int64 a = 1; + repeated int64 b = 2; + repeated string c = 3; + T d = 4; + + oneof o { + int64 i = 12; + T k = 11; + string j = 10; + }; +} diff --git a/test/merge_test.ml b/test/merge_test.ml new file mode 100644 index 0000000..8f28e3b --- /dev/null +++ b/test/merge_test.ml @@ -0,0 +1,144 @@ +open !StdLabels +open Merge.Merge + +let test_merge (type t) (module T: Test_lib.T with type t = t) (init : t) (ts: t list) = + let open Ocaml_protoc_plugin in + + let writer = Writer.init () in + let expect = + List.fold_left ~init ~f:(fun acc t -> + Printf.printf "%s\n" (T.show t); + let _ = T.to_proto' writer t in + T.merge acc t + ) ts + in + let merged = T.from_proto (Reader.create (Writer.contents writer)) |> Result.get ~msg:"Unable to decode merged messages" in + Printf.printf "Merged: %s\n" (T.show merged); + let () = match merged = expect with + | false -> + Printf.printf "Merge results not equal\n"; + Printf.printf "Expected: %s\n" (T.show expect); + | true -> () + in + () + +let%expect_test "merge int" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t1 = T.make ~a:5 () in + let t2 = T.make ~a:7 () in + test_merge (module T) (T.make ()) [t1; t2]; + [%expect {| + { a = 5; b = []; c = []; d = None; o = `not_set } + { a = 7; b = []; c = []; d = None; o = `not_set } + Merged: { a = 7; b = []; c = []; d = None; o = `not_set } |}] + +let%expect_test "merge int" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t1 = T.make ~b:[1;2;3] () in + let t2 = T.make ~b:[4;5;6] () in + let t3 = T.make ~b:[7;8;9] () in + test_merge (module T) (T.make ()) [t1; t2; t3]; + [%expect {| + { a = 0; b = [1; 2; 3]; c = []; d = None; o = `not_set } + { a = 0; b = [4; 5; 6]; c = []; d = None; o = `not_set } + { a = 0; b = [7; 8; 9]; c = []; d = None; o = `not_set } + Merged: { a = 0; b = [1; 2; 3; 4; 5; 6; 7; 8; 9]; c = []; d = None; o = `not_set } |}] + +let%expect_test "merge string" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t1 = T.make ~c:["1";"2";"3"] () in + let t2 = T.make ~c:["4";"5";"6"] () in + let t3 = T.make ~c:["7";"8";"9"] () in + test_merge (module T) (T.make ()) [t1; t2; t3]; + [%expect {| + { a = 0; b = []; c = ["1"; "2"; "3"]; d = None; o = `not_set } + { a = 0; b = []; c = ["4"; "5"; "6"]; d = None; o = `not_set } + { a = 0; b = []; c = ["7"; "8"; "9"]; d = None; o = `not_set } + Merged: { a = 0; b = []; c = ["1"; "2"; "3"; "4"; "5"; "6"; "7"; "8"; "9"]; d = None; + o = `not_set } |}] + +let%expect_test "merge message" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t11 = T.make ~a:1 ~b:[1;2;3] () in + let t12 = T.make ~a:2 ~b:[4;5;6] () in + let t13 = T.make ~a:3 ~b:[7;8;9] () in + let t1 = T.make ~a:6 ~d:t11 () in + let t2 = T.make ~a:7 ~d:t12 () in + let t3 = T.make ~a:8 ~d:t13 () in + + test_merge (module T) (T.make ()) [t1; t2; t3]; + [%expect {| + { a = 6; b = []; c = []; + d = (Some { a = 1; b = [1; 2; 3]; c = []; d = None; o = `not_set }); + o = `not_set } + { a = 7; b = []; c = []; + d = (Some { a = 2; b = [4; 5; 6]; c = []; d = None; o = `not_set }); + o = `not_set } + { a = 8; b = []; c = []; + d = (Some { a = 3; b = [7; 8; 9]; c = []; d = None; o = `not_set }); + o = `not_set } + Merged: { a = 8; b = []; c = []; + d = + (Some { a = 3; b = [1; 2; 3; 4; 5; 6; 7; 8; 9]; c = []; d = None; + o = `not_set }); + o = `not_set } |}] + +let%expect_test "merge last oneof" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t1 = T.make ~o:(`I 5) () in + let t2 = T.make ~o:(`J "7") () in + test_merge (module T) (T.make ()) [t1; t2]; + [%expect {| + { a = 0; b = []; c = []; d = None; o = `I (5) } + { a = 0; b = []; c = []; d = None; o = `J ("7") } + Merged: { a = 0; b = []; c = []; d = None; o = `J ("7") } |}] + +let%expect_test "merge message oneof" = + (* Create a set of tests, each expanding on the previous *) + (* And we should extend test_encode to verify merge for all message types *) + (* But in this test we want to explicitly test it *) + (* Also for merging multiple messages *) + + let t11 = T.make ~a:1 ~b:[1;2;3] () in + let t12 = T.make ~a:2 ~b:[4;5;6] () in + let t13 = T.make ~a:3 ~b:[7;8;9] () in + + let t1 = T.make ~o:(`K t11) () in + let t2 = T.make ~o:(`K t12) () in + let t3 = T.make ~o:(`K t13) () in + test_merge (module T) (T.make ()) [t1; t2; t3]; + [%expect {| + { a = 0; b = []; c = []; d = None; + o = `K ({ a = 1; b = [1; 2; 3]; c = []; d = None; o = `not_set }) } + { a = 0; b = []; c = []; d = None; + o = `K ({ a = 2; b = [4; 5; 6]; c = []; d = None; o = `not_set }) } + { a = 0; b = []; c = []; d = None; + o = `K ({ a = 3; b = [7; 8; 9]; c = []; d = None; o = `not_set }) } + Merged: { a = 0; b = []; c = []; d = None; + o = `K ({ a = 3; b = [7; 8; 9]; c = []; d = None; o = `not_set }) } + Merge results not equal + Expected: { a = 0; b = []; c = []; d = None; + o = + `K ({ a = 3; b = [1; 2; 3; 4; 5; 6; 7; 8; 9]; c = []; d = None; + o = `not_set }) + } |}] diff --git a/test/oneof.proto b/test/oneof.proto index 022fe58..a365527 100644 --- a/test/oneof.proto +++ b/test/oneof.proto @@ -52,11 +52,17 @@ message Test5 { } message Test6 { - int64 i = 1; + optional int64 i = 1; oneof a { int64 a1 = 10; int64 a2 = 21; }; int64 j = 20; - oneof b { int64 f = 30; }; + oneof b { + int64 f = 30; + int64 ff = 31; + }; + oneof c { + Test6 g = 40; + }; } diff --git a/test/proto2.proto b/test/proto2.proto index 1423ed6..aad73be 100644 --- a/test/proto2.proto +++ b/test/proto2.proto @@ -70,4 +70,14 @@ message MessageDefaults { optional float oc = 22 [default = -27]; optional double od = 23 [default = -27]; optional bool oe = 24 [default = true]; + oneof of { + int64 og = 1 [default = 5]; + }; +} + +message Oneof_default { + oneof a { + int64 i = 1 [default = 5]; + int64 j = 2 [default = 7]; + }; } diff --git a/test/proto2_test.ml b/test/proto2_test.ml index 9bd6d2a..3c69756 100644 --- a/test/proto2_test.ml +++ b/test/proto2_test.ml @@ -51,6 +51,12 @@ let%expect_test "Default created messages should not set any fields" = in (); [%expect {| Size of message: 0 - { o0 = "default string"; o1 = "default bytes"; o2 = 27; o3 = 27; o4 = -27; - o5 = -27; o6 = -27; o7 = -27; o8 = 27l; o9 = 27L; oa = -27l; ob = -27L; - oc = -27.; od = -27.; oe = true } |}] + { of' = `not_set; o0 = "default string"; o1 = "default bytes"; o2 = 27; + o3 = 27; o4 = -27; o5 = -27; o6 = -27; o7 = -27; o8 = 27l; o9 = 27L; + oa = -27l; ob = -27L; oc = -27.; od = -27.; oe = true } |}] + +let%expect_test "Default values in oneofs are ignored" = + let module T = Proto2.Oneof_default in + let t = T.make ~a:(`I 5) () in + Test_lib.test_encode (module T) t; + [%expect {| i: 5 |}] diff --git a/test/test_lib.ml b/test/test_lib.ml index 93ce8ed..5f41af6 100644 --- a/test/test_lib.ml +++ b/test/test_lib.ml @@ -1,10 +1,13 @@ open StdLabels +open Ocaml_protoc_plugin module type T = sig type t [@@deriving show, eq] - val to_proto : t -> Ocaml_protoc_plugin.Writer.t - val from_proto : Ocaml_protoc_plugin.Reader.t -> t Ocaml_protoc_plugin.Result.t + val to_proto' : Writer.t -> t -> Writer.t + val to_proto : t -> Writer.t + val from_proto : Reader.t -> t Result.t val name' : unit -> string + val merge: t -> t -> t end let hexlify data = @@ -41,14 +44,36 @@ let dump_protoc ?(protoc_args=[]) name data = | 0 -> () | n -> Printf.printf "'protoc' exited with status code: %d\n" n +let test_merge (type t) (module M : T with type t = t) (t: t) = + let iterations = [1;2;3;4] in + let writer = Writer.init () in + let _ = + List.fold_left ~init:(writer, t) ~f:(fun (writer, expect) i -> + let writer = M.to_proto' writer t in + let contents = Writer.contents writer |> Reader.create in + let () = + match M.from_proto contents with + | Error err -> Printf.printf "Error decoding after %d iterations: %s\n" i (Result.show_error err) + | Ok observed when M.equal expect observed -> () + | Ok observed -> + Printf.printf "Wrong value after %d iterations\nExpect: %s\nObserved:%s\n" i ([%show: M.t] expect) ([%show: M.t] observed) + in + (writer, M.merge expect t) + ) iterations + in + () + + (** Create a common function for testing. *) -let test_encode (type t) ?dump ?(protoc=true) ?protoc_args (module M : T with type t = t) ?(validate : t option) (expect : t) = +let test_encode (type t) ?dump ?(protoc=true) ?protoc_args (module M : T with type t = t) ?(validate : t option) ?(expect : t option) (t : t) = + let expect = Option.value ~default:t expect in let () = match validate with | Some v when v <> expect -> Printf.printf "Validate match failed\n" | _ -> () in - let data = M.to_proto expect |> Ocaml_protoc_plugin.Writer.contents in + let data = M.to_proto expect |> Writer.contents in + let () = match dump with | Some _ -> hexlify data @@ -58,11 +83,24 @@ let test_encode (type t) ?dump ?(protoc=true) ?protoc_args (module M : T with ty | true -> dump_protoc ?protoc_args (M.name' ()) data | false -> () in - (* Decode the message *) - let in_data = Ocaml_protoc_plugin.Reader.create data in - match M.from_proto in_data with - | Ok observed when M.equal expect observed -> () - | Ok observed -> - Printf.printf "\nExpect :%s\nObserved:%s\n" ([%show: M.t] expect) ([%show: M.t] observed) - | Error err -> - Printf.printf "\nDecode failed: %s \n" (Ocaml_protoc_plugin.Result.show_error err) + let in_data_unordered = + let writer = Writer.init () in + Writer.write_field writer (1 lsl 29 - 1) (Field.varint_unboxed 5); + let _ = M.to_proto' writer expect in + Reader.create (Writer.contents writer) + in + let in_data = Reader.create data in + match (M.from_proto in_data, M.from_proto in_data_unordered) with + | Ok observed, Ok observed_unordered -> begin + match M.equal expect observed, M.equal expect observed_unordered with + | true, true -> + test_merge (module M) expect + | false, _ -> + Printf.printf "\nExpect: %s\nObserved:%s\n" ([%show: M.t] expect) ([%show: M.t] observed) + | _, false -> + Printf.printf "\nExpect(unordered):%s\nObserved:%s\n" ([%show: M.t] expect) ([%show: M.t] observed_unordered) + end + | Error err, _ -> + Printf.printf "\nDecode failed: %s \n" (Result.show_error err) + | _, Error err -> + Printf.printf "\nDecode unordered failed: %s \n" (Result.show_error err) From 9140a26f95de0acbc68b848fc69c43316953f5c9 Mon Sep 17 00:00:00 2001 From: Anders Fugmann Date: Mon, 29 Jan 2024 00:38:58 +0100 Subject: [PATCH 2/2] Fix problem with required proto2 messages. - Remove Required/Optional in deserialization - re-introduce a basic_opt type to be more explicit about presense of default values --- src/ocaml_protoc_plugin/deserialize.ml | 82 ++-- src/ocaml_protoc_plugin/extensions.ml | 1 + src/ocaml_protoc_plugin/merge.ml | 12 +- src/ocaml_protoc_plugin/serialize.ml | 19 +- src/ocaml_protoc_plugin/spec.ml | 14 +- src/plugin/types.ml | 58 +-- src/spec/descriptor.ml | 534 ++++++++++--------------- src/spec/options.ml | 9 +- src/spec/plugin.ml | 61 ++- test/oneof.proto | 2 +- test/proto2.proto | 20 + 11 files changed, 343 insertions(+), 469 deletions(-) diff --git a/src/ocaml_protoc_plugin/deserialize.ml b/src/ocaml_protoc_plugin/deserialize.ml index 4836149..6b94490 100644 --- a/src/ocaml_protoc_plugin/deserialize.ml +++ b/src/ocaml_protoc_plugin/deserialize.ml @@ -5,18 +5,16 @@ module S = Spec.Deserialize module C = S.C open S -type required = Required | Optional - type 'a reader = 'a -> Reader.t -> Field.field_type -> 'a -type 'a getter = 'a -> 'a +type ('a, 'b) getter = 'a -> 'b type 'a field_spec = (int * 'a reader) -type 'a value = ('a field_spec list * required * 'a * 'a getter) +type _ value = Value: ('b field_spec list * 'b * ('b, 'a) getter) -> 'a value type extensions = (int * Field.t) list type (_, _) value_list = | VNil : ('a, 'a) value_list | VNil_ext : (extensions -> 'a, 'a) value_list - | VCons : ('a value) * ('b, 'c) value_list -> ('a -> 'b, 'c) value_list + | VCons : 'a value * ('b, 'c) value_list -> ('a -> 'b, 'c) value_list type sentinel_field_spec = int * (Reader.t -> Field.field_type -> unit) type 'a sentinel_getter = unit -> 'a @@ -88,7 +86,7 @@ let read_of_spec: type a. a spec -> Field.field_type * (Reader.t -> a) = functio | Message (from_proto, _merge) -> Length_delimited, fun reader -> let Field.{ offset; length; data } = Reader.read_length_delimited reader in from_proto (Reader.create ~offset ~length data) - +(* let default_value: type a. a spec -> a = function | Double -> 0.0 | Float -> 0.0 @@ -117,7 +115,7 @@ let default_value: type a. a spec -> a = function | SFixed64_int -> 0 | Enum of_int -> of_int 0 | Bool -> false - +*) let id x = x let keep_last _ v = v @@ -129,34 +127,29 @@ let read_field ~read:(expect, read_f) ~map v reader field_type = error_wrong_field "Deserialize" field let value: type a. a compound -> a value = function + | Basic_req (index, spec) -> + let map _ v2 = Some v2 in + let read = read_field ~read:(read_of_spec spec) ~map in + let getter = function Some v -> v | None -> error_required_field_missing () in + Value ([(index, read)], None, getter) | Basic (index, spec, default) -> - let map = match spec with - | Message (_, merge) -> merge - | _ -> keep_last + let map = keep_last in let read = read_field ~read:(read_of_spec spec) ~map in - let required = match default with - | Some _ -> Optional - | None -> Required - in - let default = match default with - | None -> default_value spec - | Some default -> default - in - ([(index, read)], required, default, id) + Value ([(index, read)], default, id) | Basic_opt (index, spec) -> let map = match spec with | Message (_, merge) -> let map v1 v2 = match v1 with | None -> Some v2 - | Some prev -> Some (merge prev v2) + | Some v1 -> Some (merge v1 v2) in map | _ -> fun _ v -> Some v (* Keep last for all other non-repeated types *) in let read = read_field ~read:(read_of_spec spec) ~map in - ([(index, read)], Optional, None, id) + Value ([(index, read)], None, id) | Repeated (index, spec, Packed) -> let field_type, read_f = read_of_spec spec in let rec read_packed_values read_f acc reader = @@ -175,16 +168,16 @@ let value: type a. a compound -> a value = function let field = Reader.read_field_content ft reader in error_wrong_field "Deserialize" field in - ([(index, read)], Optional, [], List.rev) + Value ([(index, read)], [], List.rev) | Repeated (index, spec, Not_packed) -> let read = read_field ~read:(read_of_spec spec) ~map:(fun vs v -> v :: vs) in - ([(index, read)], Optional, [], List.rev) + Value ([(index, read)], [], List.rev) | Oneof oneofs -> let make_reader: a oneof -> a field_spec = fun (Oneof_elem (index, spec, constr)) -> let read = read_field ~read:(read_of_spec spec) ~map:(fun _ -> constr) in (index, read) in - (List.map ~f:make_reader oneofs, Optional, `not_set, id) + Value (List.map ~f:make_reader oneofs, `not_set, id) module IntMap = Map.Make(struct type t = int let compare = Int.compare end) @@ -197,15 +190,12 @@ let deserialize_full: type constr a. extension_ranges -> (constr, a) value_list | VNil -> NNil | VNil_ext -> NNil_ext (* Consider optimizing when optional is true *) - | VCons ((fields, required, default, getter), rest) -> - let v = ref (default, required) in - let get () = match !v with - | _, Required -> error_required_field_missing (); - | v, Optional-> getter v - in + | VCons (Value (fields, default, getter), rest) -> + let v = ref default in + let get () = getter !v in let fields = List.map ~f:(fun (index, read) -> - let read reader field_type = let v' = fst !v in v := (read v' reader field_type, Optional) in + let read reader field_type = (v := read !v reader field_type) in (index, read) ) fields in @@ -277,11 +267,11 @@ let deserialize: type constr a. (constr, a) compound_list -> constr -> Reader.t in let rec read_values: type constr a. extension_ranges -> Field.field_type -> int -> Reader.t -> constr -> extensions -> (constr, a) value_list -> a = fun extension_ranges tpe idx reader constr extensions -> - let rec read_repeated tpe index read_f default get reader = + let rec read_repeated tpe index read_f default reader = let default = read_f default reader tpe in let (tpe, idx) = next_field reader in match idx = index with - | true -> read_repeated tpe index read_f default get reader + | true -> read_repeated tpe index read_f default reader | false -> default, tpe, idx in function @@ -290,34 +280,27 @@ let deserialize: type constr a. (constr, a) compound_list -> constr -> Reader.t | VNil_ext when idx = Int.max_int -> constr (List.rev extensions) (* All fields read successfully. Apply extensions and return result. *) - | VCons (([index, read_f], _required, default, get), vs) when index = idx -> + | VCons (Value ([index, read_f], default, get), vs) when index = idx -> (* Read all values, and apply constructor once all fields have been read. This pattern is the most likely to be matched for all values, and is added as an optimization to avoid reconstructing the value list for each recursion. *) - let default, tpe, idx = read_repeated tpe index read_f default get reader in + let default, tpe, idx = read_repeated tpe index read_f default reader in let constr = (constr (get default)) in read_values extension_ranges tpe idx reader constr extensions vs - | VCons (((index, read_f) :: fields, _required, default, get), vs) when index = idx -> + | VCons (Value ((index, read_f) :: fields, default, get), vs) when index = idx -> (* Read all values for the given field *) - let default, tpe, idx = read_repeated tpe index read_f default get reader in - read_values extension_ranges tpe idx reader constr extensions (VCons ((fields, Optional, default, get), vs)) + let default, tpe, idx = read_repeated tpe index read_f default reader in + read_values extension_ranges tpe idx reader constr extensions (VCons (Value (fields, default, get), vs)) | vs when in_extension_ranges extension_ranges idx -> (* Extensions may be sent inline. Store all valid extensions, before starting to apply constructors *) let extensions = (idx, Reader.read_field_content tpe reader) :: extensions in let (tpe, idx) = next_field reader in read_values extension_ranges tpe idx reader constr extensions vs - | VCons (([], Required, _default, _get), _vs) -> - (* If there are no more fields to be read we will never find the value. - If all values are read, then raise, else revert to full deserialization *) - begin match (idx = Int.max_int) with - | true -> error_required_field_missing () - | false -> raise Restart_full - end - | VCons ((_ :: fields, optional, default, get), vs) -> + | VCons (Value (_ :: fields, default, get), vs) -> (* Drop the field, as we dont expect to find it. *) - read_values extension_ranges tpe idx reader constr extensions (VCons ((fields, optional, default, get), vs)) - | VCons (([], Optional, default, get), vs) -> + read_values extension_ranges tpe idx reader constr extensions (VCons (Value (fields, default, get), vs)) + | VCons (Value ([], default, get), vs) -> (* Apply destructor. This case is only relevant for oneof fields *) read_values extension_ranges tpe idx reader (constr (get default)) extensions vs | VNil | VNil_ext -> @@ -335,6 +318,7 @@ let deserialize: type constr a. (constr, a) compound_list -> constr -> Reader.t let (tpe, idx) = next_field reader in try read_values extension_ranges tpe idx reader constr [] values - with Restart_full -> + with (Restart_full | Result.Error `Required_field_missing) -> + (* Revert to full deserialization *) Reader.reset reader offset; deserialize_full extension_ranges values constr reader diff --git a/src/ocaml_protoc_plugin/extensions.ml b/src/ocaml_protoc_plugin/extensions.ml index 07add8f..5dbe688 100644 --- a/src/ocaml_protoc_plugin/extensions.ml +++ b/src/ocaml_protoc_plugin/extensions.ml @@ -11,6 +11,7 @@ let compare _ _ = 0 let index_of_spec: type a. a Spec.Serialize.compound -> int = function | Basic (index, _, _) -> index | Basic_opt (index, _) -> index + | Basic_req (index, _) -> index | Repeated (index, _, _) -> index | Oneof _ -> failwith "Oneof fields not allowed in extensions" diff --git a/src/ocaml_protoc_plugin/merge.ml b/src/ocaml_protoc_plugin/merge.ml index 7f89f4e..5d8178e 100644 --- a/src/ocaml_protoc_plugin/merge.ml +++ b/src/ocaml_protoc_plugin/merge.ml @@ -1,8 +1,16 @@ (** Merge a two values. Need to match on the spec to merge messages recursivly *) let merge: type t. t Spec.Deserialize.compound -> t -> t -> t = fun spec t t' -> match spec with - | Spec.Deserialize.Basic (_field, Message (_, merge), _) -> merge t t' - | Spec.Deserialize.Basic (_field, _spec, Some default) when t' = default -> t + | Spec.Deserialize.Basic (_field, Message (_, _), _) -> failwith "Messages with defaults cannot happen" + | Spec.Deserialize.Basic (_field, _spec, default) when t' = default -> t | Spec.Deserialize.Basic (_field, _spec, _) -> t' + + (* The spec states that proto2 required fields must be transmitted exactly once. + So merging these fields is not possible. The essentially means that you cannot merge + proto2 messages containing required fields. + In this implementation, we choose to ignore this, and adopt 'keep last' + *) + | Spec.Deserialize.Basic_req (_field, Message (_, merge)) -> merge t t' + | Spec.Deserialize.Basic_req (_field, _spec) -> t' | Spec.Deserialize.Basic_opt (_field, Message (_, merge)) -> begin match t, t' with diff --git a/src/ocaml_protoc_plugin/serialize.ml b/src/ocaml_protoc_plugin/serialize.ml index ea91576..49df326 100644 --- a/src/ocaml_protoc_plugin/serialize.ml +++ b/src/ocaml_protoc_plugin/serialize.ml @@ -120,16 +120,15 @@ let rec write: type a. a compound -> Writer.t -> a -> unit = function *) | Basic (index, spec, default) -> begin let write = write_field spec index in - match default with - | Some default -> - fun writer v -> begin - match v with - | v when v = default -> () - | v -> write v writer - end - | None -> - fun writer v -> write v writer + let writer writer = function + | v when v = default -> () + | v -> write v writer + in + writer end + | Basic_req (index, spec) -> + let write = write_field spec index in + fun writer v -> write v writer | Basic_opt (index, spec) -> begin let write = write_field spec index in fun writer v -> @@ -145,7 +144,7 @@ let rec write: type a. a compound -> Writer.t -> a -> unit = function (* Wonder if we could get the specs before calling v. Wonder what f is? *) (* We could prob. return a list of all possible values + f v -> v. *) let Oneof_elem (index, spec, v) = f v in - write (Basic (index, spec, None)) writer v + write (Basic_req (index, spec)) writer v end let in_extension_ranges extension_ranges index = diff --git a/src/ocaml_protoc_plugin/spec.ml b/src/ocaml_protoc_plugin/spec.ml index 7a87805..dab61c8 100644 --- a/src/ocaml_protoc_plugin/spec.ml +++ b/src/ocaml_protoc_plugin/spec.ml @@ -50,14 +50,25 @@ module Make(T : T) = struct | Oneof_elem : int * 'b spec * ('a, ('b -> 'a), 'b) T.dir -> 'a oneof type _ compound = - | Basic : int * 'a spec * 'a option -> 'a compound + (* A field, where the default value is know (and set). This cannot be used for message types *) + | Basic : int * 'a spec * 'a -> 'a compound + + (* Proto2/proto3 optional fields. *) | Basic_opt : int * 'a spec -> 'a option compound + + (* Proto2 required fields (and oneof fields) *) + | Basic_req : int * 'a spec -> 'a compound + + (* Repeated fields *) | Repeated : int * 'a spec * packed -> 'a list compound | Oneof : ('a, 'a oneof list, 'a -> unit oneof) T.dir -> ([> `not_set ] as 'a) compound type (_, _) compound_list = | Nil : ('a, 'a) compound_list + + (* Nil_ext denotes that the message contains extensions *) | Nil_ext: extension_ranges -> (extensions -> 'a, 'a) compound_list + | Cons : ('a compound) * ('b, 'c) compound_list -> ('a -> 'b, 'c) compound_list module C = struct @@ -97,6 +108,7 @@ module Make(T : T) = struct let repeated (i, s, p) = Repeated (i, s, p) let basic (i, s, d) = Basic (i, s, d) + let basic_req (i, s) = Basic_req (i, s) let basic_opt (i, s) = Basic_opt (i, s) let oneof s = Oneof s let oneof_elem (a, b, c) = Oneof_elem (a, b, c) diff --git a/src/plugin/types.ml b/src/plugin/types.ml index 23b94bd..dc4c28f 100644 --- a/src/plugin/types.ml +++ b/src/plugin/types.ml @@ -303,9 +303,8 @@ let string_of_oneof_elem dir (Oneof_elem (index, spec, (_, deser, ser, _, _))) = let s = match dir with `Deserialize -> deser | `Serialize -> ser in sprintf "oneof_elem (%d, %s, %s)" index spec_string s -let string_of_proto_type: type a. a spec -> a option -> string = fun spec -> function - | Some s -> sprintf "Some (%s)" (string_of_default spec s) - | None -> "None" +let string_of_proto_type: type a. a spec -> a -> string = fun spec default -> + sprintf "(%s)" (string_of_default spec default) let string_of_packed = function | Packed -> "packed" @@ -321,13 +320,17 @@ let c_of_compound: type a. string -> a compound -> c = fun name -> function let deserialize_spec = sprintf "basic (%d, %s, %s)" index (string_of_spec `Deserialize spec) (string_of_proto_type spec default) in let serialize_spec = sprintf "basic (%d, %s, %s)" index (string_of_spec `Serialize spec) (string_of_proto_type spec default) in let modifier = - match spec, default with - | _, None-> Required - | Message _, _ -> Optional - | _, Some v -> No_modifier (string_of_default spec v) + match spec with + | Message _ -> Optional + | _ -> No_modifier (string_of_default spec default) in let type' = { name = type_of_spec spec; modifier } in { name; type'; deserialize_spec; serialize_spec } + | Basic_req (index, spec) -> + let deserialize_spec = sprintf "basic_req (%d, %s)" index (string_of_spec `Deserialize spec) in + let serialize_spec = sprintf "basic_req (%d, %s)" index (string_of_spec `Serialize spec) in + let type' = { name = type_of_spec spec; modifier = Required } in + { name; type'; deserialize_spec; serialize_spec } | Basic_opt (index, spec) -> let deserialize_spec = sprintf "basic_opt (%d, %s)" index (string_of_spec `Deserialize spec) in let serialize_spec = sprintf "basic_opt (%d, %s)" index (string_of_spec `Serialize spec) in @@ -372,13 +375,13 @@ let c_of_field ~params ~syntax ~scope field = (* Required message *) | `Proto2, { label = Some Label.LABEL_REQUIRED; type' = Some TYPE_MESSAGE; type_name; _ } -> let spec = spec_of_message ~scope type_name in - Basic (number, spec, None) + Basic_req (number, spec) |> c_of_compound name (* Enum under proto2 with a default value *) | `Proto2, { label = Some Label.LABEL_OPTIONAL; type' = Some TYPE_ENUM; type_name; default_value = Some default; _ } -> let spec = spec_of_enum ~scope type_name (Some default) in - Basic (number, Enum spec, Some default) + Basic (number, Enum spec, default) |> c_of_compound name (* Enum under proto2 with no default value *) @@ -390,20 +393,20 @@ let c_of_field ~params ~syntax ~scope field = (* Required Enum under proto2 *) | `Proto2, { label = Some Label.LABEL_REQUIRED; type' = Some TYPE_ENUM; type_name; _ } -> let spec = spec_of_enum ~scope type_name None in - Basic (number, Enum spec, None) + Basic_req (number, Enum spec) |> c_of_compound name (* Required fields under proto2 *) | `Proto2, { label = Some Label.LABEL_REQUIRED; type' = Some type'; type_name; _ } -> let Espec spec = spec_of_type ~params ~scope type_name None type' in - Basic (number, spec, None) + Basic_req (number, spec) |> c_of_compound name (* Proto2 optional fields with a default *) | `Proto2, { label = Some Label.LABEL_OPTIONAL; type' = Some type'; type_name; default_value = Some default; _ } -> let Espec spec = spec_of_type ~params ~scope type_name (Some default) type' in let default = make_default spec default in - Basic (number, spec, Some default) + Basic (number, spec, default) |> c_of_compound name (* Proto2 optional fields - no default *) @@ -429,7 +432,7 @@ let c_of_field ~params ~syntax ~scope field = | `Proto3, { label = Some Label.LABEL_OPTIONAL; type' = Some type'; type_name; _} -> let Espec spec = spec_of_type ~params ~scope type_name None type' in let default = default_of_spec spec in - Basic (number, spec, Some default) + Basic (number, spec, default) |> c_of_compound name (* Repeated fields cannot have a default *) @@ -725,40 +728,37 @@ let make ~params ~syntax ~is_cyclic ~is_map_entry ~extension_ranges ~scope ~fiel *) let name = Scope.get_name scope name in - sprintf "let %s = match ((t1%s%s), (t2%s%s)) with" name sep name sep name :: + sprintf "match ((t1%s%s), (t2%s%s)) with"sep name sep name :: List.map ~f:(fun (ctr, type') -> - let spec = sprintf "basic (0, %s, None)" type' in + let spec = sprintf "basic_req (0, %s)" type' in (* Oneof messages are marked as required, as one must be set. *) sprintf " | (%s v1, %s v2) -> %s (Runtime'.Merge.merge Runtime'.Deserialize.C.( %s ) v1 v2)" ctr ctr ctr spec ) ctrs |> append " | (v1, `not_set) -> v1" |> append " | (_, v2) -> v2" - |> append "in" |> String.concat ~sep:"\n" + |> fun value -> name, value | { name; deserialize_spec; _ } -> let name = Scope.get_name scope name in - sprintf "let %s = Runtime'.Merge.merge Runtime'.Deserialize.C.( %s ) t1%s%s t2%s%s in\n" - name deserialize_spec sep name sep name + name, sprintf "Runtime'.Merge.merge Runtime'.Deserialize.C.( %s ) t1%s%s t2%s%s" + deserialize_spec sep name sep name ) - |> append ~cond:has_extensions (sprintf "let extensions' = List.append t1%sextensions' t2%sextensions' in" sep sep) - |> String.concat ~sep:"\n" + |> append ~cond:has_extensions ("extensions'", sprintf "List.append t1%sextensions' t2%sextensions'" sep sep) in let constr = - let names = - List.map ts ~f:(fun c -> Scope.get_name scope c.name) - |> append ~cond:has_extensions "extensions'" - in match as_tuple with | true -> - names + List.map ~f:snd merge_values |> String.concat ~sep:"," |> sprintf "(%s)" | false -> - names - |> String.concat ~sep:"; " - |> sprintf "{ %s }" + List.map merge_values ~f:(fun (name, value) -> + Printf.sprintf "%s = (%s);" name value + ) + |> String.concat ~sep:"\n" + |> sprintf "{\n%s\n }" in - sprintf "fun %s -> \n%s\n%s" args merge_values constr + sprintf "fun %s -> %s" args constr in (* The type contains optional elements. We should not have those *) diff --git a/src/spec/descriptor.ml b/src/spec/descriptor.ml index 33e703b..d57cea8 100644 --- a/src/spec/descriptor.ml +++ b/src/spec/descriptor.ml @@ -649,10 +649,7 @@ end = struct let name' () = "descriptor.google.protobuf.FileDescriptorSet" type t = (FileDescriptorProto.t list) let make ?(file = []) () = (file) - let merge = (fun (t1_file) (t2_file) -> - let file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> FileDescriptorProto.from_proto_exn writer), FileDescriptorProto.merge)), not_packed) ) t1_file t2_file in - - (file)) + let merge = (fun (t1_file) (t2_file) -> (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> FileDescriptorProto.from_proto_exn writer), FileDescriptorProto.merge)), not_packed) ) t1_file t2_file)) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, (message FileDescriptorProto.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -678,32 +675,20 @@ end = struct let name' () = "descriptor.google.protobuf.FileDescriptorProto" type t = { name: string option; package: string option; dependency: string list; message_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; service: ServiceDescriptorProto.t list; extension: FieldDescriptorProto.t list; options: FileOptions.t option; source_code_info: SourceCodeInfo.t option; public_dependency: int list; weak_dependency: int list; syntax: string option } let make ?name ?package ?(dependency = []) ?(message_type = []) ?(enum_type = []) ?(service = []) ?(extension = []) ?options ?source_code_info ?(public_dependency = []) ?(weak_dependency = []) ?syntax () = { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.package t2.package in - - let dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, string, not_packed) ) t1.dependency t2.dependency in - - let message_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.message_type t2.message_type in - - let enum_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type in - - let service = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> ServiceDescriptorProto.from_proto_exn writer), ServiceDescriptorProto.merge)), not_packed) ) t1.service t2.service in - - let extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (7, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FileOptions.from_proto_exn writer), FileOptions.merge))) ) t1.options t2.options in - - let source_code_info = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, (message ((fun writer -> SourceCodeInfo.from_proto_exn writer), SourceCodeInfo.merge))) ) t1.source_code_info t2.source_code_info in - - let public_dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, int32_int, not_packed) ) t1.public_dependency t2.public_dependency in - - let weak_dependency = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (11, int32_int, not_packed) ) t1.weak_dependency t2.weak_dependency in - - let syntax = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (12, string) ) t1.syntax t2.syntax in - - { name; package; dependency; message_type; enum_type; service; extension; options; source_code_info; public_dependency; weak_dependency; syntax }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + package = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.package t2.package); + dependency = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, string, not_packed) ) t1.dependency t2.dependency); + message_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.message_type t2.message_type); + enum_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type); + service = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> ServiceDescriptorProto.from_proto_exn writer), ServiceDescriptorProto.merge)), not_packed) ) t1.service t2.service); + extension = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (7, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FileOptions.from_proto_exn writer), FileOptions.merge))) ) t1.options t2.options); + source_code_info = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, (message ((fun writer -> SourceCodeInfo.from_proto_exn writer), SourceCodeInfo.merge))) ) t1.source_code_info t2.source_code_info); + public_dependency = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, int32_int, not_packed) ) t1.public_dependency t2.public_dependency); + weak_dependency = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (11, int32_int, not_packed) ) t1.weak_dependency t2.weak_dependency); + syntax = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (12, string) ) t1.syntax t2.syntax); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: repeated (3, string, not_packed) ^:: repeated (4, (message DescriptorProto.to_proto'), not_packed) ^:: repeated (5, (message EnumDescriptorProto.to_proto'), not_packed) ^:: repeated (6, (message ServiceDescriptorProto.to_proto'), not_packed) ^:: repeated (7, (message FieldDescriptorProto.to_proto'), not_packed) ^:: basic_opt (8, (message FileOptions.to_proto')) ^:: basic_opt (9, (message SourceCodeInfo.to_proto')) ^:: repeated (10, int32_int, not_packed) ^:: repeated (11, int32_int, not_packed) ^:: basic_opt (12, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -759,14 +744,11 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto.ExtensionRange" type t = { start: int option; end': int option; options: ExtensionRangeOptions.t option } let make ?start ?end' ?options () = { start; end'; options } - let merge = (fun t1 t2 -> - let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in - - let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ExtensionRangeOptions.from_proto_exn writer), ExtensionRangeOptions.merge))) ) t1.options t2.options in - - { start; end'; options }) + let merge = (fun t1 t2 -> { + start = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start); + end' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end'); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ExtensionRangeOptions.from_proto_exn writer), ExtensionRangeOptions.merge))) ) t1.options t2.options); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message ExtensionRangeOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -792,12 +774,10 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto.ReservedRange" type t = { start: int option; end': int option } let make ?start ?end' () = { start; end' } - let merge = (fun t1 t2 -> - let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in - - let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in - - { start; end' }) + let merge = (fun t1 t2 -> { + start = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start); + end' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end'); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -813,28 +793,18 @@ end = struct let name' () = "descriptor.google.protobuf.DescriptorProto" type t = { name: string option; field: FieldDescriptorProto.t list; nested_type: DescriptorProto.t list; enum_type: EnumDescriptorProto.t list; extension_range: ExtensionRange.t list; extension: FieldDescriptorProto.t list; options: MessageOptions.t option; oneof_decl: OneofDescriptorProto.t list; reserved_range: ReservedRange.t list; reserved_name: string list } let make ?name ?(field = []) ?(nested_type = []) ?(enum_type = []) ?(extension_range = []) ?(extension = []) ?options ?(oneof_decl = []) ?(reserved_range = []) ?(reserved_name = []) () = { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let field = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.field t2.field in - - let nested_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.nested_type t2.nested_type in - - let enum_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type in - - let extension_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> ExtensionRange.from_proto_exn writer), ExtensionRange.merge)), not_packed) ) t1.extension_range t2.extension_range in - - let extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, (message ((fun writer -> MessageOptions.from_proto_exn writer), MessageOptions.merge))) ) t1.options t2.options in - - let oneof_decl = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (8, (message ((fun writer -> OneofDescriptorProto.from_proto_exn writer), OneofDescriptorProto.merge)), not_packed) ) t1.oneof_decl t2.oneof_decl in - - let reserved_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (9, (message ((fun writer -> ReservedRange.from_proto_exn writer), ReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range in - - let reserved_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, string, not_packed) ) t1.reserved_name t2.reserved_name in - - { name; field; nested_type; enum_type; extension_range; extension; options; oneof_decl; reserved_range; reserved_name }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + field = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.field t2.field); + nested_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (3, (message ((fun writer -> DescriptorProto.from_proto_exn writer), DescriptorProto.merge)), not_packed) ) t1.nested_type t2.nested_type); + enum_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumDescriptorProto.from_proto_exn writer), EnumDescriptorProto.merge)), not_packed) ) t1.enum_type t2.enum_type); + extension_range = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, (message ((fun writer -> ExtensionRange.from_proto_exn writer), ExtensionRange.merge)), not_packed) ) t1.extension_range t2.extension_range); + extension = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, (message ((fun writer -> FieldDescriptorProto.from_proto_exn writer), FieldDescriptorProto.merge)), not_packed) ) t1.extension t2.extension); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, (message ((fun writer -> MessageOptions.from_proto_exn writer), MessageOptions.merge))) ) t1.options t2.options); + oneof_decl = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (8, (message ((fun writer -> OneofDescriptorProto.from_proto_exn writer), OneofDescriptorProto.merge)), not_packed) ) t1.oneof_decl t2.oneof_decl); + reserved_range = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (9, (message ((fun writer -> ReservedRange.from_proto_exn writer), ReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range); + reserved_name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (10, string, not_packed) ) t1.reserved_name t2.reserved_name); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message FieldDescriptorProto.to_proto'), not_packed) ^:: repeated (3, (message DescriptorProto.to_proto'), not_packed) ^:: repeated (4, (message EnumDescriptorProto.to_proto'), not_packed) ^:: repeated (5, (message ExtensionRange.to_proto'), not_packed) ^:: repeated (6, (message FieldDescriptorProto.to_proto'), not_packed) ^:: basic_opt (7, (message MessageOptions.to_proto')) ^:: repeated (8, (message OneofDescriptorProto.to_proto'), not_packed) ^:: repeated (9, (message ReservedRange.to_proto'), not_packed) ^:: repeated (10, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -860,11 +830,10 @@ end = struct let name' () = "descriptor.google.protobuf.ExtensionRangeOptions" type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in @@ -972,30 +941,19 @@ end = struct let name' () = "descriptor.google.protobuf.FieldDescriptorProto" type t = { name: string option; extendee: string option; number: int option; label: Label.t option; type': Type.t option; type_name: string option; default_value: string option; options: FieldOptions.t option; oneof_index: int option; json_name: string option; proto3_optional: bool option } let make ?name ?extendee ?number ?label ?type' ?type_name ?default_value ?options ?oneof_index ?json_name ?proto3_optional () = { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let extendee = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.extendee t2.extendee in - - let number = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.number t2.number in - - let label = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (enum Label.from_int_exn)) ) t1.label t2.label in - - let type' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, (enum Type.from_int_exn)) ) t1.type' t2.type' in - - let type_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, string) ) t1.type_name t2.type_name in - - let default_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, string) ) t1.default_value t2.default_value in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FieldOptions.from_proto_exn writer), FieldOptions.merge))) ) t1.options t2.options in - - let oneof_index = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, int32_int) ) t1.oneof_index t2.oneof_index in - - let json_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (10, string) ) t1.json_name t2.json_name in - - let proto3_optional = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (17, bool) ) t1.proto3_optional t2.proto3_optional in - - { name; extendee; number; label; type'; type_name; default_value; options; oneof_index; json_name; proto3_optional }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + extendee = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.extendee t2.extendee); + number = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.number t2.number); + label = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (enum Label.from_int_exn)) ) t1.label t2.label); + type' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, (enum Type.from_int_exn)) ) t1.type' t2.type'); + type_name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, string) ) t1.type_name t2.type_name); + default_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, string) ) t1.default_value t2.default_value); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, (message ((fun writer -> FieldOptions.from_proto_exn writer), FieldOptions.merge))) ) t1.options t2.options); + oneof_index = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (9, int32_int) ) t1.oneof_index t2.oneof_index); + json_name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (10, string) ) t1.json_name t2.json_name); + proto3_optional = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (17, bool) ) t1.proto3_optional t2.proto3_optional); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, (enum Label.to_int)) ^:: basic_opt (5, (enum Type.to_int)) ^:: basic_opt (6, string) ^:: basic_opt (7, string) ^:: basic_opt (8, (message FieldOptions.to_proto')) ^:: basic_opt (9, int32_int) ^:: basic_opt (10, string) ^:: basic_opt (17, bool) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1021,12 +979,10 @@ end = struct let name' () = "descriptor.google.protobuf.OneofDescriptorProto" type t = { name: string option; options: OneofOptions.t option } let make ?name ?options () = { name; options } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, (message ((fun writer -> OneofOptions.from_proto_exn writer), OneofOptions.merge))) ) t1.options t2.options in - - { name; options }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, (message ((fun writer -> OneofOptions.from_proto_exn writer), OneofOptions.merge))) ) t1.options t2.options); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, (message OneofOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1072,12 +1028,10 @@ end = struct let name' () = "descriptor.google.protobuf.EnumDescriptorProto.EnumReservedRange" type t = { start: int option; end': int option } let make ?start ?end' () = { start; end' } - let merge = (fun t1 t2 -> - let start = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start in - - let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end' in - - { start; end' }) + let merge = (fun t1 t2 -> { + start = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.start t2.start); + end' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.end' t2.end'); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1093,18 +1047,13 @@ end = struct let name' () = "descriptor.google.protobuf.EnumDescriptorProto" type t = { name: string option; value: EnumValueDescriptorProto.t list; options: EnumOptions.t option; reserved_range: EnumReservedRange.t list; reserved_name: string list } let make ?name ?(value = []) ?options ?(reserved_range = []) ?(reserved_name = []) () = { name; value; options; reserved_range; reserved_name } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let value = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> EnumValueDescriptorProto.from_proto_exn writer), EnumValueDescriptorProto.merge)), not_packed) ) t1.value t2.value in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumOptions.from_proto_exn writer), EnumOptions.merge))) ) t1.options t2.options in - - let reserved_range = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumReservedRange.from_proto_exn writer), EnumReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range in - - let reserved_name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, string, not_packed) ) t1.reserved_name t2.reserved_name in - - { name; value; options; reserved_range; reserved_name }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> EnumValueDescriptorProto.from_proto_exn writer), EnumValueDescriptorProto.merge)), not_packed) ) t1.value t2.value); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumOptions.from_proto_exn writer), EnumOptions.merge))) ) t1.options t2.options); + reserved_range = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (4, (message ((fun writer -> EnumReservedRange.from_proto_exn writer), EnumReservedRange.merge)), not_packed) ) t1.reserved_range t2.reserved_range); + reserved_name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (5, string, not_packed) ) t1.reserved_name t2.reserved_name); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message EnumValueDescriptorProto.to_proto'), not_packed) ^:: basic_opt (3, (message EnumOptions.to_proto')) ^:: repeated (4, (message EnumReservedRange.to_proto'), not_packed) ^:: repeated (5, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1130,14 +1079,11 @@ end = struct let name' () = "descriptor.google.protobuf.EnumValueDescriptorProto" type t = { name: string option; number: int option; options: EnumValueOptions.t option } let make ?name ?number ?options () = { name; number; options } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let number = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.number t2.number in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumValueOptions.from_proto_exn writer), EnumValueOptions.merge))) ) t1.options t2.options in - - { name; number; options }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + number = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.number t2.number); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> EnumValueOptions.from_proto_exn writer), EnumValueOptions.merge))) ) t1.options t2.options); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, (message EnumValueOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1163,14 +1109,11 @@ end = struct let name' () = "descriptor.google.protobuf.ServiceDescriptorProto" type t = { name: string option; method': MethodDescriptorProto.t list; options: ServiceOptions.t option } let make ?name ?(method' = []) ?options () = { name; method'; options } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let method' = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> MethodDescriptorProto.from_proto_exn writer), MethodDescriptorProto.merge)), not_packed) ) t1.method' t2.method' in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ServiceOptions.from_proto_exn writer), ServiceOptions.merge))) ) t1.options t2.options in - - { name; method'; options }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + method' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> MethodDescriptorProto.from_proto_exn writer), MethodDescriptorProto.merge)), not_packed) ) t1.method' t2.method'); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> ServiceOptions.from_proto_exn writer), ServiceOptions.merge))) ) t1.options t2.options); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: repeated (2, (message MethodDescriptorProto.to_proto'), not_packed) ^:: basic_opt (3, (message ServiceOptions.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1196,29 +1139,23 @@ end = struct let name' () = "descriptor.google.protobuf.MethodDescriptorProto" type t = { name: string option; input_type: string option; output_type: string option; options: MethodOptions.t option; client_streaming: bool; server_streaming: bool } let make ?name ?input_type ?output_type ?options ?(client_streaming = false) ?(server_streaming = false) () = { name; input_type; output_type; options; client_streaming; server_streaming } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let input_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.input_type t2.input_type in - - let output_type = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.output_type t2.output_type in - - let options = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ) t1.options t2.options in - - let client_streaming = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, Some (false)) ) t1.client_streaming t2.client_streaming in - - let server_streaming = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, bool, Some (false)) ) t1.server_streaming t2.server_streaming in - - { name; input_type; output_type; options; client_streaming; server_streaming }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + input_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.input_type t2.input_type); + output_type = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.output_type t2.output_type); + options = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ) t1.options t2.options); + client_streaming = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, (false)) ) t1.client_streaming t2.client_streaming); + server_streaming = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, bool, (false)) ) t1.server_streaming t2.server_streaming); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message MethodOptions.to_proto')) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message MethodOptions.to_proto')) ^:: basic (5, bool, (false)) ^:: basic (6, bool, (false)) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name; input_type; output_type; options; client_streaming; server_streaming } -> serialize writer name input_type output_type options client_streaming server_streaming let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name input_type output_type options client_streaming server_streaming -> { name; input_type; output_type; options; client_streaming; server_streaming } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ^:: basic (5, bool, Some (false)) ^:: basic (6, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (3, string) ^:: basic_opt (4, (message ((fun writer -> MethodOptions.from_proto_exn writer), MethodOptions.merge))) ^:: basic (5, bool, (false)) ^:: basic (6, bool, (false)) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1261,60 +1198,39 @@ end = struct let name' () = "descriptor.google.protobuf.FileOptions" type t = { java_package: string option; java_outer_classname: string option; optimize_for: OptimizeMode.t; java_multiple_files: bool; go_package: string option; cc_generic_services: bool; java_generic_services: bool; py_generic_services: bool; java_generate_equals_and_hash: bool option; deprecated: bool; java_string_check_utf8: bool; cc_enable_arenas: bool; objc_class_prefix: string option; csharp_namespace: string option; swift_prefix: string option; php_class_prefix: string option; php_namespace: string option; php_generic_services: bool; php_metadata_namespace: string option; ruby_package: string option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?java_package ?java_outer_classname ?(optimize_for = OptimizeMode.SPEED) ?(java_multiple_files = false) ?go_package ?(cc_generic_services = false) ?(java_generic_services = false) ?(py_generic_services = false) ?java_generate_equals_and_hash ?(deprecated = false) ?(java_string_check_utf8 = false) ?(cc_enable_arenas = true) ?objc_class_prefix ?csharp_namespace ?swift_prefix ?php_class_prefix ?php_namespace ?(php_generic_services = false) ?php_metadata_namespace ?ruby_package ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let java_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.java_package t2.java_package in - - let java_outer_classname = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.java_outer_classname t2.java_outer_classname in - - let optimize_for = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (9, (enum OptimizeMode.from_int_exn), Some (OptimizeMode.SPEED)) ) t1.optimize_for t2.optimize_for in - - let java_multiple_files = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, Some (false)) ) t1.java_multiple_files t2.java_multiple_files in - - let go_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (11, string) ) t1.go_package t2.go_package in - - let cc_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (16, bool, Some (false)) ) t1.cc_generic_services t2.cc_generic_services in - - let java_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (17, bool, Some (false)) ) t1.java_generic_services t2.java_generic_services in - - let py_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (18, bool, Some (false)) ) t1.py_generic_services t2.py_generic_services in - - let java_generate_equals_and_hash = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (20, bool) ) t1.java_generate_equals_and_hash t2.java_generate_equals_and_hash in - - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (23, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let java_string_check_utf8 = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (27, bool, Some (false)) ) t1.java_string_check_utf8 t2.java_string_check_utf8 in - - let cc_enable_arenas = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (31, bool, Some (true)) ) t1.cc_enable_arenas t2.cc_enable_arenas in - - let objc_class_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (36, string) ) t1.objc_class_prefix t2.objc_class_prefix in - - let csharp_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (37, string) ) t1.csharp_namespace t2.csharp_namespace in - - let swift_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (39, string) ) t1.swift_prefix t2.swift_prefix in - - let php_class_prefix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (40, string) ) t1.php_class_prefix t2.php_class_prefix in - - let php_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (41, string) ) t1.php_namespace t2.php_namespace in - - let php_generic_services = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (42, bool, Some (false)) ) t1.php_generic_services t2.php_generic_services in - - let php_metadata_namespace = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (44, string) ) t1.php_metadata_namespace t2.php_metadata_namespace in - - let ruby_package = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (45, string) ) t1.ruby_package t2.ruby_package in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + java_package = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.java_package t2.java_package); + java_outer_classname = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.java_outer_classname t2.java_outer_classname); + optimize_for = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (9, (enum OptimizeMode.from_int_exn), (OptimizeMode.SPEED)) ) t1.optimize_for t2.optimize_for); + java_multiple_files = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, (false)) ) t1.java_multiple_files t2.java_multiple_files); + go_package = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (11, string) ) t1.go_package t2.go_package); + cc_generic_services = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (16, bool, (false)) ) t1.cc_generic_services t2.cc_generic_services); + java_generic_services = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (17, bool, (false)) ) t1.java_generic_services t2.java_generic_services); + py_generic_services = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (18, bool, (false)) ) t1.py_generic_services t2.py_generic_services); + java_generate_equals_and_hash = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (20, bool) ) t1.java_generate_equals_and_hash t2.java_generate_equals_and_hash); + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (23, bool, (false)) ) t1.deprecated t2.deprecated); + java_string_check_utf8 = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (27, bool, (false)) ) t1.java_string_check_utf8 t2.java_string_check_utf8); + cc_enable_arenas = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (31, bool, (true)) ) t1.cc_enable_arenas t2.cc_enable_arenas); + objc_class_prefix = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (36, string) ) t1.objc_class_prefix t2.objc_class_prefix); + csharp_namespace = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (37, string) ) t1.csharp_namespace t2.csharp_namespace); + swift_prefix = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (39, string) ) t1.swift_prefix t2.swift_prefix); + php_class_prefix = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (40, string) ) t1.php_class_prefix t2.php_class_prefix); + php_namespace = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (41, string) ) t1.php_namespace t2.php_namespace); + php_generic_services = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (42, bool, (false)) ) t1.php_generic_services t2.php_generic_services); + php_metadata_namespace = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (44, string) ) t1.php_metadata_namespace t2.php_metadata_namespace); + ruby_package = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (45, string) ) t1.ruby_package t2.ruby_package); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.to_int), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.to_int), (OptimizeMode.SPEED)) ^:: basic (10, bool, (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, (false)) ^:: basic (17, bool, (false)) ^:: basic (18, bool, (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, (false)) ^:: basic (27, bool, (false)) ^:: basic (31, bool, (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } -> serialize writer java_package java_outer_classname optimize_for java_multiple_files go_package cc_generic_services java_generic_services py_generic_services java_generate_equals_and_hash deprecated java_string_check_utf8 cc_enable_arenas objc_class_prefix csharp_namespace swift_prefix php_class_prefix php_namespace php_generic_services php_metadata_namespace ruby_package uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun java_package java_outer_classname optimize_for java_multiple_files go_package cc_generic_services java_generic_services py_generic_services java_generate_equals_and_hash deprecated java_string_check_utf8 cc_enable_arenas objc_class_prefix csharp_namespace swift_prefix php_class_prefix php_namespace php_generic_services php_metadata_namespace ruby_package uninterpreted_option extensions' -> { java_package; java_outer_classname; optimize_for; java_multiple_files; go_package; cc_generic_services; java_generic_services; py_generic_services; java_generate_equals_and_hash; deprecated; java_string_check_utf8; cc_enable_arenas; objc_class_prefix; csharp_namespace; swift_prefix; php_class_prefix; php_namespace; php_generic_services; php_metadata_namespace; ruby_package; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.from_int_exn), Some (OptimizeMode.SPEED)) ^:: basic (10, bool, Some (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, Some (false)) ^:: basic (17, bool, Some (false)) ^:: basic (18, bool, Some (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, Some (false)) ^:: basic (27, bool, Some (false)) ^:: basic (31, bool, Some (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, Some (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic_opt (1, string) ^:: basic_opt (8, string) ^:: basic (9, (enum OptimizeMode.from_int_exn), (OptimizeMode.SPEED)) ^:: basic (10, bool, (false)) ^:: basic_opt (11, string) ^:: basic (16, bool, (false)) ^:: basic (17, bool, (false)) ^:: basic (18, bool, (false)) ^:: basic_opt (20, bool) ^:: basic (23, bool, (false)) ^:: basic (27, bool, (false)) ^:: basic (31, bool, (true)) ^:: basic_opt (36, string) ^:: basic_opt (37, string) ^:: basic_opt (39, string) ^:: basic_opt (40, string) ^:: basic_opt (41, string) ^:: basic (42, bool, (false)) ^:: basic_opt (44, string) ^:: basic_opt (45, string) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1331,28 +1247,23 @@ end = struct let name' () = "descriptor.google.protobuf.MessageOptions" type t = { message_set_wire_format: bool; no_standard_descriptor_accessor: bool; deprecated: bool; map_entry: bool option; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(message_set_wire_format = false) ?(no_standard_descriptor_accessor = false) ?(deprecated = false) ?map_entry ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let message_set_wire_format = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1.message_set_wire_format t2.message_set_wire_format in - - let no_standard_descriptor_accessor = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (2, bool, Some (false)) ) t1.no_standard_descriptor_accessor t2.no_standard_descriptor_accessor in - - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let map_entry = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bool) ) t1.map_entry t2.map_entry in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + message_set_wire_format = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, (false)) ) t1.message_set_wire_format t2.message_set_wire_format); + no_standard_descriptor_accessor = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (2, bool, (false)) ) t1.no_standard_descriptor_accessor t2.no_standard_descriptor_accessor); + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, (false)) ) t1.deprecated t2.deprecated); + map_entry = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bool) ) t1.map_entry t2.map_entry); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, bool, (false)) ^:: basic (2, bool, (false)) ^:: basic (3, bool, (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } -> serialize writer message_set_wire_format no_standard_descriptor_accessor deprecated map_entry uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun message_set_wire_format no_standard_descriptor_accessor deprecated map_entry uninterpreted_option extensions' -> { message_set_wire_format; no_standard_descriptor_accessor; deprecated; map_entry; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: basic (2, bool, Some (false)) ^:: basic (3, bool, Some (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, bool, (false)) ^:: basic (2, bool, (false)) ^:: basic (3, bool, (false)) ^:: basic_opt (7, bool) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1421,34 +1332,26 @@ end = struct let name' () = "descriptor.google.protobuf.FieldOptions" type t = { ctype: CType.t; packed: bool option; deprecated: bool; lazy': bool; jstype: JSType.t; weak: bool; unverified_lazy: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(ctype = CType.STRING) ?packed ?(deprecated = false) ?(lazy' = false) ?(jstype = JSType.JS_NORMAL) ?(weak = false) ?(unverified_lazy = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let ctype = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), Some (CType.STRING)) ) t1.ctype t2.ctype in - - let packed = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.packed t2.packed in - - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let lazy' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, Some (false)) ) t1.lazy' t2.lazy' in - - let jstype = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, (enum JSType.from_int_exn), Some (JSType.JS_NORMAL)) ) t1.jstype t2.jstype in - - let weak = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, Some (false)) ) t1.weak t2.weak in - - let unverified_lazy = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (15, bool, Some (false)) ) t1.unverified_lazy t2.unverified_lazy in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + ctype = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), (CType.STRING)) ) t1.ctype t2.ctype); + packed = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.packed t2.packed); + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, (false)) ) t1.deprecated t2.deprecated); + lazy' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (5, bool, (false)) ) t1.lazy' t2.lazy'); + jstype = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (6, (enum JSType.from_int_exn), (JSType.JS_NORMAL)) ) t1.jstype t2.jstype); + weak = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (10, bool, (false)) ) t1.weak t2.weak); + unverified_lazy = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (15, bool, (false)) ) t1.unverified_lazy t2.unverified_lazy); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, (enum CType.to_int), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.to_int), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, (enum CType.to_int), (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, (false)) ^:: basic (5, bool, (false)) ^:: basic (6, (enum JSType.to_int), (JSType.JS_NORMAL)) ^:: basic (10, bool, (false)) ^:: basic (15, bool, (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } -> serialize writer ctype packed deprecated lazy' jstype weak unverified_lazy uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun ctype packed deprecated lazy' jstype weak unverified_lazy uninterpreted_option extensions' -> { ctype; packed; deprecated; lazy'; jstype; weak; unverified_lazy; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), Some (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: basic (5, bool, Some (false)) ^:: basic (6, (enum JSType.from_int_exn), Some (JSType.JS_NORMAL)) ^:: basic (10, bool, Some (false)) ^:: basic (15, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, (enum CType.from_int_exn), (CType.STRING)) ^:: basic_opt (2, bool) ^:: basic (3, bool, (false)) ^:: basic (5, bool, (false)) ^:: basic (6, (enum JSType.from_int_exn), (JSType.JS_NORMAL)) ^:: basic (10, bool, (false)) ^:: basic (15, bool, (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1465,11 +1368,10 @@ end = struct let name' () = "descriptor.google.protobuf.OneofOptions" type t = { uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1495,24 +1397,21 @@ end = struct let name' () = "descriptor.google.protobuf.EnumOptions" type t = { allow_alias: bool option; deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?allow_alias ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { allow_alias; deprecated; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let allow_alias = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.allow_alias t2.allow_alias in - - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { allow_alias; deprecated; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + allow_alias = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, bool) ) t1.allow_alias t2.allow_alias); + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (3, bool, (false)) ) t1.deprecated t2.deprecated); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic_opt (2, bool) ^:: basic (3, bool, (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { allow_alias; deprecated; uninterpreted_option; extensions' } -> serialize writer allow_alias deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun allow_alias deprecated uninterpreted_option extensions' -> { allow_alias; deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic_opt (2, bool) ^:: basic (3, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic_opt (2, bool) ^:: basic (3, bool, (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1529,22 +1428,20 @@ end = struct let name' () = "descriptor.google.protobuf.EnumValueOptions" type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { deprecated; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, (false)) ) t1.deprecated t2.deprecated); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (1, bool, (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; uninterpreted_option; extensions' } -> serialize writer deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated uninterpreted_option extensions' -> { deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (1, bool, (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1561,22 +1458,20 @@ end = struct let name' () = "descriptor.google.protobuf.ServiceOptions" type t = { deprecated: bool; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { deprecated; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, (false)) ) t1.deprecated t2.deprecated); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (33, bool, (false)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; uninterpreted_option; extensions' } -> serialize writer deprecated uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated uninterpreted_option extensions' -> { deprecated; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (33, bool, (false)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1619,24 +1514,21 @@ end = struct let name' () = "descriptor.google.protobuf.MethodOptions" type t = { deprecated: bool; idempotency_level: IdempotencyLevel.t; uninterpreted_option: UninterpretedOption.t list; extensions': Runtime'.Extensions.t } let make ?(deprecated = false) ?(idempotency_level = IdempotencyLevel.IDEMPOTENCY_UNKNOWN) ?(uninterpreted_option = []) ?(extensions' = Runtime'.Extensions.default) () = { deprecated; idempotency_level; uninterpreted_option; extensions' } - let merge = (fun t1 t2 -> - let deprecated = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ) t1.deprecated t2.deprecated in - - let idempotency_level = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (34, (enum IdempotencyLevel.from_int_exn), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ) t1.idempotency_level t2.idempotency_level in - - let uninterpreted_option = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option in - - let extensions' = List.append t1.extensions' t2.extensions' in - { deprecated; idempotency_level; uninterpreted_option; extensions' }) + let merge = (fun t1 t2 -> { + deprecated = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (33, bool, (false)) ) t1.deprecated t2.deprecated); + idempotency_level = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (34, (enum IdempotencyLevel.from_int_exn), (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ) t1.idempotency_level t2.idempotency_level); + uninterpreted_option = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ) t1.uninterpreted_option t2.uninterpreted_option); + extensions' = (List.append t1.extensions' t2.extensions'); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.to_int), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Serialize.C.( basic (33, bool, (false)) ^:: basic (34, (enum IdempotencyLevel.to_int), (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message UninterpretedOption.to_proto'), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { deprecated; idempotency_level; uninterpreted_option; extensions' } -> serialize writer deprecated idempotency_level uninterpreted_option extensions' let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun deprecated idempotency_level uninterpreted_option extensions' -> { deprecated; idempotency_level; uninterpreted_option; extensions' } in - let spec = Runtime'.Deserialize.C.( basic (33, bool, Some (false)) ^:: basic (34, (enum IdempotencyLevel.from_int_exn), Some (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in + let spec = Runtime'.Deserialize.C.( basic (33, bool, (false)) ^:: basic (34, (enum IdempotencyLevel.from_int_exn), (IdempotencyLevel.IDEMPOTENCY_UNKNOWN)) ^:: repeated (999, (message ((fun writer -> UninterpretedOption.from_proto_exn writer), UninterpretedOption.merge)), not_packed) ^:: nil_ext [ (1000, 536870912) ] ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end @@ -1673,43 +1565,34 @@ end = struct let name' () = "descriptor.google.protobuf.UninterpretedOption.NamePart" type t = { name_part: string; is_extension: bool } let make ~name_part ~is_extension () = { name_part; is_extension } - let merge = (fun t1 t2 -> - let name_part = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, string, None) ) t1.name_part t2.name_part in - - let is_extension = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (2, bool, None) ) t1.is_extension t2.is_extension in - - { name_part; is_extension }) + let merge = (fun t1 t2 -> { + name_part = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_req (1, string) ) t1.name_part t2.name_part); + is_extension = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_req (2, bool) ) t1.is_extension t2.is_extension); + }) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, string, None) ^:: basic (2, bool, None) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic_req (1, string) ^:: basic_req (2, bool) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in fun writer { name_part; is_extension } -> serialize writer name_part is_extension let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun name_part is_extension -> { name_part; is_extension } in - let spec = Runtime'.Deserialize.C.( basic (1, string, None) ^:: basic (2, bool, None) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic_req (1, string) ^:: basic_req (2, bool) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end let name' () = "descriptor.google.protobuf.UninterpretedOption" type t = { name: NamePart.t list; identifier_value: string option; positive_int_value: int option; negative_int_value: int option; double_value: float option; string_value: bytes option; aggregate_value: string option } let make ?(name = []) ?identifier_value ?positive_int_value ?negative_int_value ?double_value ?string_value ?aggregate_value () = { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> NamePart.from_proto_exn writer), NamePart.merge)), not_packed) ) t1.name t2.name in - - let identifier_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.identifier_value t2.identifier_value in - - let positive_int_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, uint64_int) ) t1.positive_int_value t2.positive_int_value in - - let negative_int_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, int64_int) ) t1.negative_int_value t2.negative_int_value in - - let double_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, double) ) t1.double_value t2.double_value in - - let string_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bytes) ) t1.string_value t2.string_value in - - let aggregate_value = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.aggregate_value t2.aggregate_value in - - { name; identifier_value; positive_int_value; negative_int_value; double_value; string_value; aggregate_value }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, (message ((fun writer -> NamePart.from_proto_exn writer), NamePart.merge)), not_packed) ) t1.name t2.name); + identifier_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.identifier_value t2.identifier_value); + positive_int_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, uint64_int) ) t1.positive_int_value t2.positive_int_value); + negative_int_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (5, int64_int) ) t1.negative_int_value t2.negative_int_value); + double_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (6, double) ) t1.double_value t2.double_value); + string_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (7, bytes) ) t1.string_value t2.string_value); + aggregate_value = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (8, string) ) t1.aggregate_value t2.aggregate_value); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (2, (message NamePart.to_proto'), not_packed) ^:: basic_opt (3, string) ^:: basic_opt (4, uint64_int) ^:: basic_opt (5, int64_int) ^:: basic_opt (6, double) ^:: basic_opt (7, bytes) ^:: basic_opt (8, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1755,18 +1638,13 @@ end = struct let name' () = "descriptor.google.protobuf.SourceCodeInfo.Location" type t = { path: int list; span: int list; leading_comments: string option; trailing_comments: string option; leading_detached_comments: string list } let make ?(path = []) ?(span = []) ?leading_comments ?trailing_comments ?(leading_detached_comments = []) () = { path; span; leading_comments; trailing_comments; leading_detached_comments } - let merge = (fun t1 t2 -> - let path = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path in - - let span = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, int32_int, packed) ) t1.span t2.span in - - let leading_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.leading_comments t2.leading_comments in - - let trailing_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.trailing_comments t2.trailing_comments in - - let leading_detached_comments = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, string, not_packed) ) t1.leading_detached_comments t2.leading_detached_comments in - - { path; span; leading_comments; trailing_comments; leading_detached_comments }) + let merge = (fun t1 t2 -> { + path = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path); + span = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (2, int32_int, packed) ) t1.span t2.span); + leading_comments = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, string) ) t1.leading_comments t2.leading_comments); + trailing_comments = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.trailing_comments t2.trailing_comments); + leading_detached_comments = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (6, string, not_packed) ) t1.leading_detached_comments t2.leading_detached_comments); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, int32_int, packed) ^:: repeated (2, int32_int, packed) ^:: basic_opt (3, string) ^:: basic_opt (4, string) ^:: repeated (6, string, not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1782,10 +1660,7 @@ end = struct let name' () = "descriptor.google.protobuf.SourceCodeInfo" type t = (Location.t list) let make ?(location = []) () = (location) - let merge = (fun (t1_location) (t2_location) -> - let location = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Location.from_proto_exn writer), Location.merge)), not_packed) ) t1_location t2_location in - - (location)) + let merge = (fun (t1_location) (t2_location) -> (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Location.from_proto_exn writer), Location.merge)), not_packed) ) t1_location t2_location)) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, (message Location.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1831,16 +1706,12 @@ end = struct let name' () = "descriptor.google.protobuf.GeneratedCodeInfo.Annotation" type t = { path: int list; source_file: string option; begin': int option; end': int option } let make ?(path = []) ?source_file ?begin' ?end' () = { path; source_file; begin'; end' } - let merge = (fun t1 t2 -> - let path = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path in - - let source_file = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.source_file t2.source_file in - - let begin' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.begin' t2.begin' in - - let end' = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, int32_int) ) t1.end' t2.end' in - - { path; source_file; begin'; end' }) + let merge = (fun t1 t2 -> { + path = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, int32_int, packed) ) t1.path t2.path); + source_file = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.source_file t2.source_file); + begin' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.begin' t2.begin'); + end' = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, int32_int) ) t1.end' t2.end'); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, int32_int, packed) ^:: basic_opt (2, string) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, int32_int) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -1856,10 +1727,7 @@ end = struct let name' () = "descriptor.google.protobuf.GeneratedCodeInfo" type t = (Annotation.t list) let make ?(annotation = []) () = (annotation) - let merge = (fun (t1_annotation) (t2_annotation) -> - let annotation = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Annotation.from_proto_exn writer), Annotation.merge)), not_packed) ) t1_annotation t2_annotation in - - (annotation)) + let merge = (fun (t1_annotation) (t2_annotation) -> (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, (message ((fun writer -> Annotation.from_proto_exn writer), Annotation.merge)), not_packed) ) t1_annotation t2_annotation)) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, (message Annotation.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in diff --git a/src/spec/options.ml b/src/spec/options.ml index 7900363..1911ff8 100644 --- a/src/spec/options.ml +++ b/src/spec/options.ml @@ -36,19 +36,16 @@ end = struct let name' () = "options.Options" type t = (bool) let make ?(mangle_names = false) () = (mangle_names) - let merge = (fun (t1_mangle_names) (t2_mangle_names) -> - let mangle_names = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ) t1_mangle_names t2_mangle_names in - - (mangle_names)) + let merge = (fun (t1_mangle_names) (t2_mangle_names) -> (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic (1, bool, (false)) ) t1_mangle_names t2_mangle_names)) let to_proto' = - let spec = Runtime'.Serialize.C.( basic (1, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Serialize.C.( basic (1, bool, (false)) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in serialize let to_proto t = to_proto' (Runtime'.Writer.init ()) t let from_proto_exn = let constructor = fun mangle_names -> (mangle_names) in - let spec = Runtime'.Deserialize.C.( basic (1, bool, Some (false)) ^:: nil ) in + let spec = Runtime'.Deserialize.C.( basic (1, bool, (false)) ^:: nil ) in Runtime'.Deserialize.deserialize spec constructor let from_proto writer = Runtime'.Result.catch (fun () -> from_proto_exn writer) end diff --git a/src/spec/plugin.ml b/src/spec/plugin.ml index 954c730..a049c44 100644 --- a/src/spec/plugin.ml +++ b/src/spec/plugin.ml @@ -186,16 +186,12 @@ end = struct let name' () = "plugin.google.protobuf.compiler.Version" type t = { major: int option; minor: int option; patch: int option; suffix: string option } let make ?major ?minor ?patch ?suffix () = { major; minor; patch; suffix } - let merge = (fun t1 t2 -> - let major = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.major t2.major in - - let minor = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.minor t2.minor in - - let patch = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.patch t2.patch in - - let suffix = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.suffix t2.suffix in - - { major; minor; patch; suffix }) + let merge = (fun t1 t2 -> { + major = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, int32_int) ) t1.major t2.major); + minor = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, int32_int) ) t1.minor t2.minor); + patch = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, int32_int) ) t1.patch t2.patch); + suffix = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (4, string) ) t1.suffix t2.suffix); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, int32_int) ^:: basic_opt (2, int32_int) ^:: basic_opt (3, int32_int) ^:: basic_opt (4, string) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -221,16 +217,12 @@ end = struct let name' () = "plugin.google.protobuf.compiler.CodeGeneratorRequest" type t = { file_to_generate: string list; parameter: string option; compiler_version: Version.t option; proto_file: Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.t list } let make ?(file_to_generate = []) ?parameter ?compiler_version ?(proto_file = []) () = { file_to_generate; parameter; compiler_version; proto_file } - let merge = (fun t1 t2 -> - let file_to_generate = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, string, not_packed) ) t1.file_to_generate t2.file_to_generate in - - let parameter = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.parameter t2.parameter in - - let compiler_version = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> Version.from_proto_exn writer), Version.merge))) ) t1.compiler_version t2.compiler_version in - - let proto_file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.merge)), not_packed) ) t1.proto_file t2.proto_file in - - { file_to_generate; parameter; compiler_version; proto_file }) + let merge = (fun t1 t2 -> { + file_to_generate = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (1, string, not_packed) ) t1.file_to_generate t2.file_to_generate); + parameter = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.parameter t2.parameter); + compiler_version = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (3, (message ((fun writer -> Version.from_proto_exn writer), Version.merge))) ) t1.compiler_version t2.compiler_version); + proto_file = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.merge)), not_packed) ) t1.proto_file t2.proto_file); + }) let to_proto' = let spec = Runtime'.Serialize.C.( repeated (1, string, not_packed) ^:: basic_opt (2, string) ^:: basic_opt (3, (message Version.to_proto')) ^:: repeated (15, (message Imported'modules.Descriptor.Google.Protobuf.FileDescriptorProto.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -300,16 +292,12 @@ end = struct let name' () = "plugin.google.protobuf.compiler.CodeGeneratorResponse.File" type t = { name: string option; insertion_point: string option; content: string option; generated_code_info: Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.t option } let make ?name ?insertion_point ?content ?generated_code_info () = { name; insertion_point; content; generated_code_info } - let merge = (fun t1 t2 -> - let name = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name in - - let insertion_point = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.insertion_point t2.insertion_point in - - let content = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (15, string) ) t1.content t2.content in - - let generated_code_info = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (16, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.merge))) ) t1.generated_code_info t2.generated_code_info in - - { name; insertion_point; content; generated_code_info }) + let merge = (fun t1 t2 -> { + name = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.name t2.name); + insertion_point = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, string) ) t1.insertion_point t2.insertion_point); + content = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (15, string) ) t1.content t2.content); + generated_code_info = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (16, (message ((fun writer -> Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.from_proto_exn writer), Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.merge))) ) t1.generated_code_info t2.generated_code_info); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, string) ^:: basic_opt (15, string) ^:: basic_opt (16, (message Imported'modules.Descriptor.Google.Protobuf.GeneratedCodeInfo.to_proto')) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in @@ -325,14 +313,11 @@ end = struct let name' () = "plugin.google.protobuf.compiler.CodeGeneratorResponse" type t = { error: string option; supported_features: int option; file: File.t list } let make ?error ?supported_features ?(file = []) () = { error; supported_features; file } - let merge = (fun t1 t2 -> - let error = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.error t2.error in - - let supported_features = Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, uint64_int) ) t1.supported_features t2.supported_features in - - let file = Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> File.from_proto_exn writer), File.merge)), not_packed) ) t1.file t2.file in - - { error; supported_features; file }) + let merge = (fun t1 t2 -> { + error = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (1, string) ) t1.error t2.error); + supported_features = (Runtime'.Merge.merge Runtime'.Deserialize.C.( basic_opt (2, uint64_int) ) t1.supported_features t2.supported_features); + file = (Runtime'.Merge.merge Runtime'.Deserialize.C.( repeated (15, (message ((fun writer -> File.from_proto_exn writer), File.merge)), not_packed) ) t1.file t2.file); + }) let to_proto' = let spec = Runtime'.Serialize.C.( basic_opt (1, string) ^:: basic_opt (2, uint64_int) ^:: repeated (15, (message File.to_proto'), not_packed) ^:: nil ) in let serialize = Runtime'.Serialize.serialize spec in diff --git a/test/oneof.proto b/test/oneof.proto index a365527..cb67eb7 100644 --- a/test/oneof.proto +++ b/test/oneof.proto @@ -52,7 +52,7 @@ message Test5 { } message Test6 { - optional int64 i = 1; + int64 i = 1; oneof a { int64 a1 = 10; int64 a2 = 21; diff --git a/test/proto2.proto b/test/proto2.proto index aad73be..fa046fd 100644 --- a/test/proto2.proto +++ b/test/proto2.proto @@ -75,9 +75,29 @@ message MessageDefaults { }; } +// Default on oneofs makes really no sense message Oneof_default { oneof a { int64 i = 1 [default = 5]; int64 j = 2 [default = 7]; }; } + +message NameClash { + message M1 { required int64 t = 1; }; + message M2 { required int64 t = 1; }; + message M3 { required int64 t = 1; }; + message M4 { required int64 t = 1; }; + message M5 { required int64 t = 1; }; + required M1 t = 1; + required M2 T = 2; + required M3 _t = 3; + required M3 _T = 4; + required M4 T_ = 5; + + oneof oneof { + int64 not_set = 10; + int64 Not_set = 11; + int64 Not_Set = 12; + } +}