géénration plus correcte des classes et class types en latex et man, en affichant les types

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4581 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Maxence Guesdon 2002-04-03 12:56:09 +00:00
parent 7e3504e7c4
commit 2754916479
4 changed files with 166 additions and 143 deletions

View File

@ -1303,10 +1303,12 @@ class html =
cta.cta_name
| Some (Cltype (clt, _)) ->
let (html_file, _) = Naming.html_files clt.clt_name in
"<a href=\""^html_file^"\">"^clt.clt_name^"</a>"
let rel = Name.get_relative father clt.clt_name in
"<a href=\""^html_file^"\">"^rel^"</a>"
| Some (Cl cl) ->
let (html_file, _) = Naming.html_files cl.cl_name in
"<a href=\""^html_file^"\">"^cl.cl_name^"</a>"
let rel = Name.get_relative father cl.cl_name in
"<a href=\""^html_file^"\">"^rel^"</a>"
)
| Class_signature _ ->
self#html_of_code ~with_pre: false Odoc_messages.object_end

View File

@ -487,16 +487,12 @@ class latex =
| Some (Modtype mt) -> mt.mt_name)
] )
(** Return a well-formatted code string for the given [class_kind].
This method uses [Format.str_formatter].*)
method pre_of_class_kind father acc ?(with_def_syntax=true) ckind =
(** Return a well-formatted code string for the given [class_kind].*)
method pre_of_class_kind f father ckind =
let p = Format.fprintf in
let f = Format.str_formatter in
p f "%s%s" acc (if with_def_syntax then " = " else "");
match ckind with
match ckind with
Class_structure _ ->
p f "%s" Odoc_messages.object_end ;
Format.flush_str_formatter ()
p f "%s" Odoc_messages.object_end
| Class_apply capp ->
p f "%s"
@ -506,8 +502,7 @@ class latex =
);
List.iter
(fun s -> p f " (%s)" s)
capp.capp_params_code;
Format.flush_str_formatter ()
capp.capp_params_code
| Class_constr cco ->
(match cco.cco_type_parameters with
@ -520,34 +515,20 @@ class latex =
p f "%s"
(match cco.cco_class with
None -> cco.cco_name
| Some (Cl cl) -> cl.cl_name
| Some (Cltype (clt, _)) -> clt.clt_name
);
Format.flush_str_formatter ()
| Some (Cl cl) -> Name.get_relative father cl.cl_name
| Some (Cltype (clt, _)) -> Name.get_relative father clt.clt_name
)
| Class_constraint (ck, ctk) ->
p f "(" ;
let s = self#pre_of_class_kind father
(Format.flush_str_formatter ())
~with_def_syntax: false ck
in
p f "%s : " s;
let s2 = self#pre_of_class_type_kind father
(Format.flush_str_formatter ())
ctk
in
p f "%s)" s2 ;
Format.flush_str_formatter ()
self#pre_of_class_kind f father ck ;
p f " : " ;
self#pre_of_class_type_kind f father ctk ;
p f ")"
(** Return well-formatted string for the given [class_type_kind].
This method uses [Format.str_formatter].*)
method pre_of_class_type_kind father acc ?def_syntax ctkind =
(** Return well-formatted string for the given [class_type_kind].*)
method pre_of_class_type_kind f father ctkind =
let p = Format.fprintf in
let f = Format.str_formatter in
p f "%s%s" acc
(match def_syntax with
None -> ""
| Some s -> " "^s^" ");
match ctkind with
Class_type cta ->
(
@ -562,38 +543,61 @@ class latex =
(
match cta.cta_class with
None -> cta.cta_name
| Some (Cltype (clt, _)) -> clt.clt_name
| Some (Cl cl) -> cl.cl_name
);
Format.flush_str_formatter ()
| Some (Cltype (clt, _)) -> Name.get_relative father clt.clt_name
| Some (Cl cl) -> Name.get_relative father cl.cl_name
)
| Class_signature _ ->
p f "%s" Odoc_messages.object_end ;
Format.flush_str_formatter ()
p f "%s" Odoc_messages.object_end
(** Return a string for the given parameter,
and eventually its label. Note that we must remove
the option constructor if we print an optional argument.*)
method string_of_parameter m p =
let (pi,label) = p in
let (slabel, t) =
let t = Parameter.typ p in
match label with
"" -> ("", t)
| s ->
if is_optional label then
(s^":", Odoc_info.remove_option t)
else
(s^":", t)
in
slabel ^ (self#normal_type m t)
(** Return the LaTeX code for the given class. *)
method latex_of_class ?(with_link=true) c =
Odoc_info.reset_type_names () ;
let buf = Buffer.create 32 in
let f = Format.formatter_of_buffer buf in
let father = Name.father c.cl_name in
let t =
let s =
Format.fprintf Format.str_formatter "class %s"
(if c.cl_virtual then "virtual " else "");
(
match c.cl_type_parameters with
[] -> ()
| l ->
Format.fprintf Format.str_formatter "[" ;
let s1 = self#normal_type_list father ", " l in
Format.fprintf Format.str_formatter "%s] " s1
);
Format.fprintf Format.str_formatter "%s%s"
(Name.simple c.cl_name)
(match c.cl_parameters with [] -> "" | _ -> " ...");
Format.flush_str_formatter ()
in
(CodePre (self#pre_of_class_kind father s c.cl_kind)) ::
Format.fprintf f "class %s"
(if c.cl_virtual then "virtual " else "");
(
match c.cl_type_parameters with
[] -> ()
| l ->
Format.fprintf f "[" ;
let s1 = self#normal_type_list father ", " l in
Format.fprintf f "%s] " s1
);
Format.fprintf f "%s : " (Name.simple c.cl_name);
List.iter
(fun param ->
Format.fprintf f "%s -> "
(self#string_of_parameter father param)
)
c.cl_parameters;
self#pre_of_class_kind f father c.cl_kind ;
Format.pp_print_flush f ();
(CodePre (Buffer.contents buf)) ::
(
if with_link
then [Odoc_info.Latex (" ["^(self#make_ref c.cl_name)^"]")]
@ -605,23 +609,25 @@ class latex =
(** Return the LaTeX code for the given class type. *)
method latex_of_class_type ?(with_link=true) ct =
Odoc_info.reset_type_names () ;
let buf = Buffer.create 32 in
let f = Format.formatter_of_buffer buf in
let father = Name.father ct.clt_name in
let t =
let s =
Format.fprintf Format.str_formatter "class type %s"
(if ct.clt_virtual then "virtual " else "");
(
match ct.clt_type_parameters with
Format.fprintf f "class type %s"
(if ct.clt_virtual then "virtual " else "");
(
match ct.clt_type_parameters with
[] -> ()
| l ->
Format.fprintf Format.str_formatter "[" ;
let s1 = self#normal_type_list father ", " l in
Format.fprintf Format.str_formatter "%s] " s1
);
Format.fprintf Format.str_formatter "%s" (Name.simple ct.clt_name);
Format.flush_str_formatter ()
in
(CodePre (self#pre_of_class_type_kind father s ~def_syntax: "=" ct.clt_kind)) ::
| l ->
Format.fprintf f "[" ;
let s1 = self#normal_type_list father ", " l in
Format.fprintf f "%s] " s1
);
Format.fprintf f "%s = " (Name.simple ct.clt_name);
self#pre_of_class_type_kind f father ct.clt_kind ;
Format.pp_print_flush f ();
(CodePre (Buffer.contents buf)) ::
(
if with_link
then [Odoc_info.Latex (" ["^(self#make_ref ct.clt_name)^"]")]

View File

@ -382,6 +382,23 @@ class man =
)
)^"\n"
(** Groff for the given parameter,
and eventually its label. Note that we must remove
the option constructor if we print an optional argument.*)
method man_of_parameter m p =
let (pi,label) = p in
let (slabel, t) =
let t = Parameter.typ p in
match label with
"" -> ("", t)
| s ->
if is_optional label then
(s^":", Odoc_info.remove_option t)
else
(s^":", t)
in
slabel ^ (self#man_of_type_expr m t)
(** Groff for the description of a function parameter. *)
method man_of_parameter_description p =
match Parameter.names p with
@ -429,14 +446,12 @@ class man =
)^"\n\n"
(** Groff string for a [class_kind]. *)
method man_of_class_kind ?(with_def_syntax=true) ckind =
method man_of_class_kind ckind =
match ckind with
Class_structure _ ->
(if with_def_syntax then " = " else "")^
(self#man_of_code Odoc_messages.object_end)
self#man_of_code Odoc_messages.object_end
| Class_apply capp ->
(if with_def_syntax then " = " else "")^
(
match capp.capp_class with
None -> capp.capp_name
@ -449,7 +464,6 @@ class man =
capp.capp_params_code))
| Class_constr cco ->
(if with_def_syntax then " = " else "")^
(
match cco.cco_type_parameters with
[] -> ""
@ -458,34 +472,27 @@ class man =
(
match cco.cco_class with
None -> cco.cco_name
| Some (Cl cl) -> cl.cl_name^" "
| Some (Cltype (clt, _)) -> clt.clt_name^" "
| Some (Cl cl) -> "\n.B "^cl.cl_name^"\n"
| Some (Cltype (clt, _)) -> "\n.B "^clt.clt_name^"\n"
)
| Class_constraint (ck, ctk) ->
(if with_def_syntax then " = " else "")^
"( "^(self#man_of_class_kind ~with_def_syntax: false ck)^
"( "^(self#man_of_class_kind ck)^
" : "^
(self#man_of_class_type_kind ctk)^
" )"
(** Groff string for the given [class_type_kind].*)
method man_of_class_type_kind ?def_syntax ctkind =
method man_of_class_type_kind ctkind =
match ctkind with
Class_type cta ->
(match def_syntax with
None -> ""
| Some s -> " "^s^" ")^
(
match cta.cta_class with
None -> cta.cta_name
| Some (Cltype (clt, _)) -> clt.clt_name
| Some (Cl cl) -> cl.cl_name
| Some (Cltype (clt, _)) -> "\n.B "^clt.clt_name^"\n"
| Some (Cl cl) -> "\n.B "^cl.cl_name^"\n"
)
| Class_signature _ ->
(match def_syntax with
None -> ""
| Some s -> " "^s^" ")^
(self#man_of_code Odoc_messages.object_end)
self#man_of_code Odoc_messages.object_end
(** Groff string for a [module_kind]. *)
method man_of_module_kind ?(with_def_syntax=true) k =
@ -552,32 +559,42 @@ class man =
(** Groff string for a class. *)
method man_of_class c =
let buf = Buffer.create 32 in
let p = Printf.bprintf in
Odoc_info.reset_type_names () ;
".I class "^
(if c.cl_virtual then "virtual " else "")^
let father = Name.father c.cl_name in
p buf ".I class %s"
(if c.cl_virtual then "virtual " else "");
(
match c.cl_type_parameters with
[] -> ""
| l -> "["^(Odoc_misc.string_of_type_list ", " l)^".I ] "
)^
(Name.simple c.cl_name)^
(match c.cl_parameters with [] -> "" | _ -> " ... ")^
(self#man_of_class_kind c.cl_kind)^
"\n.sp\n"^(self#man_of_info c.cl_info)^"\n.sp\n"
[] -> ()
| l -> p buf "[%s.I] " (Odoc_misc.string_of_type_list ", " l)
);
p buf "%s : " (Name.simple c.cl_name);
List.iter
(fun param -> p buf "%s-> " (self#man_of_parameter father param))
c.cl_parameters;
p buf "%s" (self#man_of_class_kind c.cl_kind);
p buf "\n.sp\n%s\n.sp\n" (self#man_of_info c.cl_info);
Buffer.contents buf
(** Groff string for a class type. *)
method man_of_class_type ct =
let buf = Buffer.create 32 in
let p = Printf.bprintf in
Odoc_info.reset_type_names () ;
".I class type "^
(if ct.clt_virtual then "virtual " else "")^
p buf ".I class type %s"
(if ct.clt_virtual then "virtual " else "");
(
match ct.clt_type_parameters with
[] -> ""
| l -> "["^(Odoc_misc.string_of_type_list ", " l)^".I ] "
)^
(Name.simple ct.clt_name)^
(self#man_of_class_type_kind ~def_syntax: ":" ct.clt_kind)^
"\n.sp\n"^(self#man_of_info ct.clt_info)^"\n.sp\n"
[] -> ()
| l -> p buf "[%s.I ] " (Odoc_misc.string_of_type_list ", " l)
);
p buf "%s = " (Name.simple ct.clt_name);
p buf "%s" (self#man_of_class_type_kind ct.clt_kind);
p buf "\n.sp\n%s\n.sp\n" (self#man_of_info ct.clt_info);
Buffer.contents buf
(** Groff string for a module. *)
method man_of_module m =
@ -638,15 +655,9 @@ class man =
".SH "^Odoc_messages.clas^"\n"^
Odoc_messages.clas^" "^cl.cl_name^"\n"^
".SH "^Odoc_messages.documentation^"\n"^
".sp\n"^
Odoc_messages.clas^"\n"^
(if cl.cl_virtual then ".B virtual \n" else "")^
".B \""^(Name.simple cl.cl_name)^"\"\n"^
(self#man_of_class_kind cl.cl_kind )^
"\n.sp\n"^
(self#man_of_info cl.cl_info)^"\n"^
".sp\n"
);
output_string chanout (self#man_of_class cl);
(* parameters *)
output_string chanout
@ -696,15 +707,10 @@ class man =
".SH "^Odoc_messages.class_type^"\n"^
Odoc_messages.class_type^" "^ct.clt_name^"\n"^
".SH "^Odoc_messages.documentation^"\n"^
".sp\n"^
Odoc_messages.class_type^"\n"^
(if ct.clt_virtual then ".B virtual \n" else "")^
".B \""^(Name.simple ct.clt_name)^"\"\n"^
(self#man_of_class_type_kind ~def_syntax: ":" ct.clt_kind )^
"\n.sp\n"^
(self#man_of_info ct.clt_info)^"\n"^
".sp\n"
);
output_string chanout (self#man_of_class_type ct);
(* a large blank *)
output_string chanout "\n.sp\n.sp\n";
(*

View File

@ -289,6 +289,23 @@ class virtual to_text =
[Latex ("\\index{"^(self#label s_name)^"@\\verb`"^(self#label ~no_:false s_name)^"`}\n")] @
(self#text_of_info e.ex_info)
(** Return [text] value for the given parameter,
and eventually its label. Note that we must remove
the option constructor if we print an optional argument.*)
method text_of_parameter m p =
let (pi,label) = p in
let (slabel, t) =
let t = Parameter.typ p in
match label with
"" -> ([], t)
| s ->
if is_optional label then
([Code (s^":")], Odoc_info.remove_option t)
else
([Code (s^":")], t)
in
slabel @ (self#text_of_type_expr m t)
(** Return [text] value for the description of a function parameter. *)
method text_of_parameter_description p =
match Parameter.names p with
@ -365,16 +382,14 @@ class virtual to_text =
]
(** Return [text] value for the given [class_kind].*)
method text_of_class_kind father ?(with_def_syntax=true) ckind =
method text_of_class_kind father ckind =
match ckind with
Class_structure _ ->
[Code ((if with_def_syntax then " = " else "")^
Odoc_messages.object_end)
]
[Code Odoc_messages.object_end]
| Class_apply capp ->
[Code
((if with_def_syntax then " = " else "")^
(
(
match capp.capp_class with
None -> capp.capp_name
@ -389,7 +404,6 @@ class virtual to_text =
]
| Class_constr cco ->
(if with_def_syntax then [Code " = "] else [])@
(
match cco.cco_type_parameters with
[] -> []
@ -401,28 +415,23 @@ class virtual to_text =
[Code (
match cco.cco_class with
None -> cco.cco_name
| Some (Cl cl) -> cl.cl_name
| Some (Cltype (clt,_)) -> clt.clt_name
| Some (Cl cl) -> Name.get_relative father cl.cl_name
| Some (Cltype (clt,_)) -> Name.get_relative father clt.clt_name
)
]
| Class_constraint (ck, ctk) ->
(if with_def_syntax then [Code " = "] else [])@
[Code "( "] @
(self#text_of_class_kind father ~with_def_syntax: false ck) @
(self#text_of_class_kind father ck) @
[Code " : "] @
(self#text_of_class_type_kind father ctk) @
[Code " )"]
(** Return [text] value for the given [class_type_kind].*)
method text_of_class_type_kind father ?def_syntax ctkind =
method text_of_class_type_kind father ctkind =
match ctkind with
Class_type cta ->
(match def_syntax with
None -> []
| Some s -> [Code (" "^s^" ")]
) @
(
match cta.cta_type_parameters with
[] -> []
@ -434,14 +443,14 @@ class virtual to_text =
(
match cta.cta_class with
None -> [ Code cta.cta_name ]
| Some (Cltype (clt, _)) -> [Code clt.clt_name]
| Some (Cl cl) -> [Code cl.cl_name]
| Some (Cltype (clt, _)) ->
let rel = Name.get_relative father clt.clt_name in
[Code rel]
| Some (Cl cl) ->
let rel = Name.get_relative father cl.cl_name in
[Code rel]
)
| Class_signature _ ->
(match def_syntax with
None -> []
| Some s -> [Code (" "^s^" ")]
) @
[Code Odoc_messages.object_end]
(** Return [text] value for a [module_kind]. *)