summaryrefslogtreecommitdiffstats
path: root/testsuite/tests/tool-ocamldoc
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/tool-ocamldoc')
-rw-r--r--testsuite/tests/tool-ocamldoc/odoc_test.ml14
-rw-r--r--testsuite/tests/tool-ocamldoc/t01.ml3
-rw-r--r--testsuite/tests/tool-ocamldoc/t01.reference5
3 files changed, 21 insertions, 1 deletions
diff --git a/testsuite/tests/tool-ocamldoc/odoc_test.ml b/testsuite/tests/tool-ocamldoc/odoc_test.ml
index 918cadc40..9e34bb2a1 100644
--- a/testsuite/tests/tool-ocamldoc/odoc_test.ml
+++ b/testsuite/tests/tool-ocamldoc/odoc_test.ml
@@ -53,7 +53,19 @@ class string_gen =
p fmt "# manifest (Odoc_info.string_of_type_expr):\n<[%s]>\n"
(match t.ty_manifest with
None -> "None"
- | Some e -> Odoc_info.string_of_type_expr e
+ | Some (Other e) -> Odoc_info.string_of_type_expr e
+ | Some (Object_type fields) ->
+ let b = Buffer.create 256 in
+ Buffer.add_string b "<";
+ List.iter
+ (fun fd ->
+ Printf.bprintf b " %s: %s ;"
+ fd.of_name
+ (Odoc_info.string_of_type_expr fd.of_type)
+ )
+ fields;
+ Buffer.add_string b " >";
+ Buffer.contents b
);
);
diff --git a/testsuite/tests/tool-ocamldoc/t01.ml b/testsuite/tests/tool-ocamldoc/t01.ml
index d253be43d..ee291b900 100644
--- a/testsuite/tests/tool-ocamldoc/t01.ml
+++ b/testsuite/tests/tool-ocamldoc/t01.ml
@@ -16,4 +16,7 @@ module type MT = sig
(string * string * string) ->
(string * string * string) -> unit
val y : int
+
+ type obj_type =
+ < foo : int ; bar : float -> string ; gee : int -> (int * string) >
end
diff --git a/testsuite/tests/tool-ocamldoc/t01.reference b/testsuite/tests/tool-ocamldoc/t01.reference
index 72345ffec..d5159bdfc 100644
--- a/testsuite/tests/tool-ocamldoc/t01.reference
+++ b/testsuite/tests/tool-ocamldoc/t01.reference
@@ -23,6 +23,8 @@
string * string * string ->
string * string * string -> string * string * string -> unit
val y : int
+ type obj_type =
+ < bar : float -> string; foo : int; gee : int -> int * string >
end]>
# type T01.MT.t:
# manifest (Odoc_info.string_of_type_expr):
@@ -31,3 +33,6 @@ end]>
string ->
string * string * string ->
string * string * string -> string * string * string -> unit]>
+# type T01.MT.obj_type:
+# manifest (Odoc_info.string_of_type_expr):
+<[< bar: float -> string ; foo: int ; gee: int -> int * string ; >]>