diff options
author | Alain Frisch <alain@frisch.fr> | 2014-10-14 15:51:30 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2014-10-14 15:51:30 +0000 |
commit | e3ad818fb5f8ddc7b477779a6da69ccac0f00f4f (patch) | |
tree | 9016f709d251804278be1a75f518787aa571904b /ocamldoc/odoc_str.ml | |
parent | a4e637ea622cf33b4c0870a98c6b1db0090f8e38 (diff) | |
parent | 8da19ea098b270230a9f1e1d252350bd69cbf8ee (diff) |
Reintegrate-merge constructors_with_record5 branch.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15556 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'ocamldoc/odoc_str.ml')
-rw-r--r-- | ocamldoc/odoc_str.ml | 71 |
1 files changed, 43 insertions, 28 deletions
diff --git a/ocamldoc/odoc_str.ml b/ocamldoc/odoc_str.ml index 7d99ff107..1536640e5 100644 --- a/ocamldoc/odoc_str.ml +++ b/ocamldoc/odoc_str.ml @@ -171,13 +171,27 @@ let bool_of_private = function | Asttypes.Private -> true | _ -> false +let field_doc_str = function + | None -> "" + | Some t -> Printf.sprintf "(* %s *)" (Odoc_misc.string_of_info t) + +let string_of_record l = + let module M = Odoc_type in + let module P = Printf in + P.sprintf "{\n%s\n}" ( + String.concat "\n" ( + List.map (fun field -> + P.sprintf " %s%s : %s;%s" + (if field.M.rf_mutable then "mutable " else "") field.M.rf_name + (Odoc_print.string_of_type_expr field.M.rf_type) + (field_doc_str field.M.rf_text) + ) l + ) + ) + let string_of_type t = let module M = Odoc_type in let module P = Printf in - let field_doc_str = function - | None -> "" - | Some t -> P.sprintf "(* %s *)" (Odoc_misc.string_of_info t) - in let priv = bool_of_private t.M.ty_private in let parameters_str = String.concat " " ( @@ -215,16 +229,19 @@ let string_of_type t = | None -> "" | Some t -> P.sprintf "(* %s *)" (Odoc_misc.string_of_info t) in - let string_of_parameters lst = - String.concat " * " ( - List.map (fun t -> "("^Odoc_print.string_of_type_expr t^")") lst - ) + let string_of_parameters = function + | M.Cstr_tuple l -> + String.concat " * " ( + List.map (fun t -> "("^Odoc_print.string_of_type_expr t^")") l + ) + | M.Cstr_record l -> + string_of_record l in P.sprintf " | %s%s%s" cons.M.vc_name ( match cons.M.vc_args, cons.M.vc_ret with - | [], None -> "" + | M.Cstr_tuple [], None -> "" | li, None -> " of " ^ (string_of_parameters li) - | [], Some r -> " : " ^ Odoc_print.string_of_type_expr r + | M.Cstr_tuple [], Some r -> " : " ^ Odoc_print.string_of_type_expr r | li, Some r -> P.sprintf " : %s -> %s" (string_of_parameters li) (Odoc_print.string_of_type_expr r) @@ -237,16 +254,8 @@ let string_of_type t = "= .." (* FIXME MG: when introducing new constuctors next time, thanks to setup a minimal correct output *) | M.Type_record l -> - P.sprintf "= %s{\n%s\n}\n" (if priv then "private " else "") ( - String.concat "\n" ( - List.map (fun field -> - P.sprintf " %s%s : %s;%s" - (if field.M.rf_mutable then "mutable " else "") field.M.rf_name - (Odoc_print.string_of_type_expr field.M.rf_type) - (field_doc_str field.M.rf_text) - ) l - ) - ) + P.sprintf "= %s{\n%s\n}\n" (if priv then "private " else "") + (string_of_record l) in P.sprintf "type %s %s %s%s%s" parameters_str (Name.simple t.M.ty_name) manifest_str type_kind_str @@ -256,6 +265,7 @@ let string_of_type t = let string_of_type_extension te = let module M = Odoc_extension in + let module T = Odoc_type in "type " ^(String.concat "" (List.map @@ -272,19 +282,21 @@ let string_of_type_extension te = " | " ^(Name.simple x.M.xt_name) ^(match x.M.xt_args, x.M.xt_ret with - | [], None -> "" - | l, None -> + | T.Cstr_tuple [], None -> "" + | T.Cstr_tuple l, None -> " of " ^ (String.concat " * " (List.map (fun t -> "("^Odoc_print.string_of_type_expr t^")") l)) - | [], Some r -> " : " ^ Odoc_print.string_of_type_expr r - | l, Some r -> + | T.Cstr_tuple [], Some r -> " : " ^ Odoc_print.string_of_type_expr r + | T.Cstr_tuple l, Some r -> " : " ^ (String.concat " * " (List.map (fun t -> "("^Odoc_print.string_of_type_expr t^")") l)) ^ " -> " ^ Odoc_print.string_of_type_expr r + | T.Cstr_record _, _ -> + assert false ) ^(match x.M.xt_alias with None -> "" @@ -309,23 +321,26 @@ let string_of_type_extension te = ) let string_of_exception e = + let module T = Odoc_type in let module M = Odoc_exception in "exception "^(Name.simple e.M.ex_name)^ (match e.M.ex_args, e.M.ex_ret with - [], None -> "" - | l,None -> + T.Cstr_tuple [], None -> "" + | T.Cstr_tuple l,None -> " of "^ (String.concat " * " (List.map (fun t -> "("^(Odoc_print.string_of_type_expr t)^")") l)) - | [],Some r -> + | T.Cstr_tuple [],Some r -> " : "^ (Odoc_print.string_of_type_expr r) - | l,Some r -> + | T.Cstr_tuple l,Some r -> " : "^ (String.concat " * " (List.map (fun t -> "("^(Odoc_print.string_of_type_expr t)^")") l))^ " -> "^ (Odoc_print.string_of_type_expr r) + | T.Cstr_record _, _ -> + assert false )^ (match e.M.ex_alias with None -> "" |