diff options
-rw-r--r-- | ocamldoc/odoc_cross.ml | 14 | ||||
-rw-r--r-- | ocamldoc/odoc_html.ml | 19 | ||||
-rw-r--r-- | ocamldoc/odoc_info.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_info.mli | 6 | ||||
-rw-r--r-- | ocamldoc/odoc_latex.ml | 23 | ||||
-rw-r--r-- | ocamldoc/odoc_man.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_misc.ml | 6 | ||||
-rw-r--r-- | ocamldoc/odoc_search.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_texi.ml | 16 | ||||
-rw-r--r-- | ocamldoc/odoc_text.ml | 45 | ||||
-rw-r--r-- | ocamldoc/odoc_text_lexer.mll | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_text_parser.mly | 74 | ||||
-rw-r--r-- | ocamldoc/odoc_types.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_types.mli | 5 | ||||
-rw-r--r-- | test/ocamldoc/t1.ml | 6 |
15 files changed, 114 insertions, 110 deletions
diff --git a/ocamldoc/odoc_cross.ml b/ocamldoc/odoc_cross.ml index c5686338a..a310d4569 100644 --- a/ocamldoc/odoc_cross.ml +++ b/ocamldoc/odoc_cross.ml @@ -611,7 +611,7 @@ let rec assoc_comments_text_elements parent_name module_list t_ele = | Subscript t -> Subscript (assoc_comments_text parent_name module_list t) | Title (n, l_opt, t) -> Title (n, l_opt, (assoc_comments_text parent_name module_list t)) | Link (s, t) -> Link (s, (assoc_comments_text parent_name module_list t)) - | Ref (initial_name, None) -> + | Ref (initial_name, None, text_option) -> ( let rec iter_parent ?parent_name name = let res = @@ -647,12 +647,12 @@ let rec assoc_comments_text_elements parent_name module_list t_ele = (name, Some kind) in match res with - | (name, Some k) -> Ref (name, Some k) + | (name, Some k) -> Ref (name, Some k, text_option) | (_, None) -> match parent_name with None -> Odoc_messages.pwarning (Odoc_messages.cross_element_not_found initial_name); - Ref (initial_name, None) + Ref (initial_name, None, text_option) | Some p -> let parent_name = match Name.father p with @@ -663,12 +663,12 @@ let rec assoc_comments_text_elements parent_name module_list t_ele = in iter_parent ~parent_name initial_name ) - | Ref (initial_name, Some kind) -> + | Ref (initial_name, Some kind, text_option) -> ( let rec iter_parent ?parent_name name = let v = (name, Some kind) in if was_verified v then - Ref (name, Some kind) + Ref (name, Some kind, text_option) else let res = match kind with @@ -708,12 +708,12 @@ let rec assoc_comments_text_elements parent_name module_list t_ele = (name, None) in match res with - | (name, Some k) -> Ref (name, Some k) + | (name, Some k) -> Ref (name, Some k, text_option) | (_, None) -> match parent_name with None -> Odoc_messages.pwarning (not_found_of_kind kind initial_name); - Ref (initial_name, None) + Ref (initial_name, None, text_option) | Some p -> let parent_name = match Name.father p with diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml index dd32d64ae..1d58787df 100644 --- a/ocamldoc/odoc_html.ml +++ b/ocamldoc/odoc_html.ml @@ -244,7 +244,8 @@ class virtual text = | Odoc_info.Title (n, l_opt, t) -> self#html_of_Title b n l_opt t | Odoc_info.Latex s -> self#html_of_Latex b s | Odoc_info.Link (s, t) -> self#html_of_Link b s t - | Odoc_info.Ref (name, ref_opt) -> self#html_of_Ref b name ref_opt + | Odoc_info.Ref (name, ref_opt, text_opt) -> + self#html_of_Ref b name ref_opt text_opt | Odoc_info.Superscript t -> self#html_of_Superscript b t | Odoc_info.Subscript t -> self#html_of_Subscript b t | Odoc_info.Module_list l -> self#html_of_Module_list b l @@ -394,10 +395,15 @@ class virtual text = self#html_of_text b t; bs b "</a>" - method html_of_Ref b name ref_opt = + method html_of_Ref b name ref_opt text_opt = match ref_opt with None -> - self#html_of_text_element b (Odoc_info.Code name) + let text = + match text_opt with + None -> [Odoc_info.Code name] + | Some t -> t + in + self#html_of_text b text | Some kind -> let h name = Odoc_info.Code (Odoc_info.use_hidden_modules name) in let (target, text) = @@ -416,8 +422,13 @@ class virtual text = | Odoc_info.RK_section t -> (Naming.complete_label_target name, Odoc_info.Italic [Raw (Odoc_info.string_of_text t)]) in + let text = + match text_opt with + None -> [text] + | Some text -> text + in bs b ("<a href=\""^target^"\">"); - self#html_of_text_element b text; + self#html_of_text b text; bs b "</a>" method html_of_Superscript b t = diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml index a39e4ad6c..1f288b17a 100644 --- a/ocamldoc/odoc_info.ml +++ b/ocamldoc/odoc_info.ml @@ -43,7 +43,7 @@ and text_element = Odoc_types.text_element = | Title of int * string option * text | Latex of string | Link of string * text - | Ref of string * ref_kind option + | Ref of string * ref_kind option * text option | Superscript of text | Subscript of text | Module_list of string list diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli index 97c44db91..63e3ba23f 100644 --- a/ocamldoc/odoc_info.mli +++ b/ocamldoc/odoc_info.mli @@ -45,8 +45,10 @@ and text_element = Odoc_types.text_element = (** Style number, optional label, and text. *) | Latex of string (** A string for latex. *) | Link of string * text (** A reference string and the link text. *) - | Ref of string * ref_kind option - (** A reference to an element. Complete name and kind. *) + | Ref of string * ref_kind option * text option + (** A reference to an element. Complete name and kind. + An optional text can be given to display this text instead + of the element name.*) | Superscript of text (** Superscripts. *) | Subscript of text (** Subscripts. *) | Module_list of string list diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml index 14f5aeab7..d46cb0e66 100644 --- a/ocamldoc/odoc_latex.ml +++ b/ocamldoc/odoc_latex.ml @@ -238,7 +238,8 @@ class text = | Odoc_info.Title (n, l_opt, t) -> self#latex_of_Title fmt n l_opt t | Odoc_info.Latex s -> self#latex_of_Latex fmt s | Odoc_info.Link (s, t) -> self#latex_of_Link fmt s t - | Odoc_info.Ref (name, ref_opt) -> self#latex_of_Ref fmt name ref_opt + | Odoc_info.Ref (name, ref_opt, text_opt) -> + self#latex_of_Ref fmt name ref_opt text_opt | Odoc_info.Superscript t -> self#latex_of_Superscript fmt t | Odoc_info.Subscript t -> self#latex_of_Subscript fmt t | Odoc_info.Module_list _ -> () @@ -344,11 +345,15 @@ class text = ps fmt s ; ps fmt "}]" - method latex_of_Ref fmt name ref_opt = + method latex_of_Ref fmt name ref_opt text_opt = match ref_opt with None -> - self#latex_of_text_element fmt - (Odoc_info.Code (Odoc_info.use_hidden_modules name)) + self#latex_of_text fmt + (match text_opt with + None -> + [Odoc_info.Code (Odoc_info.use_hidden_modules name)] + | Some t -> t + ) | Some (RK_section _) -> self#latex_of_text_element fmt (Latex ("["^(self#make_ref (self#label ~no_:false (Name.simple name)))^"]")) @@ -366,11 +371,13 @@ class text = | Odoc_info.RK_method -> self#method_label | Odoc_info.RK_section _ -> assert false in + let text = + match text_opt with + None -> [Odoc_info.Code (Odoc_info.use_hidden_modules name)] + | Some t -> t + in self#latex_of_text fmt - [ - Odoc_info.Code (Odoc_info.use_hidden_modules name) ; - Latex ("["^(self#make_ref (f_label name))^"]") - ] + (text @ [Latex ("["^(self#make_ref (f_label name))^"]")]) method latex_of_Superscript fmt t = ps fmt "$^{"; diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml index 8296e5080..748ce5b25 100644 --- a/ocamldoc/odoc_man.ml +++ b/ocamldoc/odoc_man.ml @@ -273,7 +273,7 @@ class man = () | Odoc_info.Link (s, t) -> self#man_of_text2 b t - | Odoc_info.Ref (name, _) -> + | Odoc_info.Ref (name, _, _) -> self#man_of_text_element b (Odoc_info.Code (Odoc_info.use_hidden_modules name)) | Odoc_info.Superscript t -> diff --git a/ocamldoc/odoc_misc.ml b/ocamldoc/odoc_misc.ml index ac2e45828..16e13668e 100644 --- a/ocamldoc/odoc_misc.ml +++ b/ocamldoc/odoc_misc.ml @@ -124,7 +124,9 @@ let rec string_of_text t = | Odoc_types.Latex s -> "{% "^s^" %}" | Odoc_types.Link (s, t) -> "["^s^"]"^(string_of_text t) - | Odoc_types.Ref (name, _) -> + | Odoc_types.Ref (name, _, Some text) -> + Printf.sprintf "[%s]" (string_of_text text) + | Odoc_types.Ref (name, _, None) -> iter (Odoc_types.Code name) | Odoc_types.Superscript t -> "^{"^(string_of_text t)^"}" @@ -274,7 +276,7 @@ let rec text_no_title_no_list t = | Odoc_types.Module_list l -> list_concat (Odoc_types.Raw ", ") (List.map - (fun s -> Odoc_types.Ref (s, Some Odoc_types.RK_module)) + (fun s -> Odoc_types.Ref (s, Some Odoc_types.RK_module, None)) l ) | Odoc_types.Index_list -> [] diff --git a/ocamldoc/odoc_search.ml b/ocamldoc/odoc_search.ml index 3329475d5..a140cfe31 100644 --- a/ocamldoc/odoc_search.ml +++ b/ocamldoc/odoc_search.ml @@ -66,7 +66,7 @@ module Search = | T.CodePre _ | T.Latex _ | T.Verbatim _ - | T.Ref (_, _) -> [] + | T.Ref (_, _, _) -> [] | T.Bold t | T.Italic t | T.Center t diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml index ec7d50c70..1e65ddd8d 100644 --- a/ocamldoc/odoc_texi.ml +++ b/ocamldoc/odoc_texi.ml @@ -294,7 +294,7 @@ class text = | Block t -> self#texi_of_Block t | Title (n, _, t) -> self#texi_of_Title n t | Link (s, t) -> self#texi_of_Link s t - | Ref (name, kind) ->self#texi_of_Ref name kind + | Ref (name, kind, _) ->self#texi_of_Ref name kind | Superscript t -> self#texi_of_Superscript t | Subscript t -> self#texi_of_Subscript t | Odoc_info.Module_list _ -> "" @@ -716,7 +716,7 @@ class texi = then " = " ^ (resolve_alias_name m) else "" ) ] ] ; ( if is_alias_there m - then [ Ref (resolve_alias_name m, Some RK_module) ; + then [ Ref (resolve_alias_name m, Some RK_module, None) ; Newline ; ] else [] ) ; ( if is_alias m @@ -745,7 +745,7 @@ class texi = then " = " ^ (resolve_alias_name mt) else "" ) ] ] ; ( if is_alias_there mt - then [ Ref (resolve_alias_name mt, Some RK_module_type) ; + then [ Ref (resolve_alias_name mt, Some RK_module_type, None) ; Newline ; ] else [] ) ; ( if is_alias mt @@ -764,10 +764,10 @@ class texi = [ Raw im.im_name ] | Some (Mod { m_name = name }) -> [ Raw name ; Raw "\n " ; - Ref (name, Some RK_module) ] + Ref (name, Some RK_module, None) ] | Some (Modtype { mt_name = name }) -> [ Raw name ; Raw "\n " ; - Ref (name, Some RK_module_type) ] + Ref (name, Some RK_module_type, None) ] ) @ [ Newline ] @ (self#text_of_info im.im_info) @@ -782,7 +782,7 @@ class texi = let t = [ self#fixedblock [ Newline ; minus ; Raw "class " ; Raw (Name.simple c.cl_name) ] ; - Ref (c.cl_name, Some RK_class) ; Newline ; + Ref (c.cl_name, Some RK_class, None) ; Newline ; Newline ] @ (self#text_of_info c.cl_info) in self#texi_of_text t @@ -792,7 +792,7 @@ class texi = let t = [ self#fixedblock [ Newline ; minus ; Raw "class type " ; Raw (Name.simple ct.clt_name) ] ; - Ref (ct.clt_name, Some RK_class_type) ; Newline ; + Ref (ct.clt_name, Some RK_class_type, None) ; Newline ; Newline ] @ (self#text_of_info ct.clt_info) in self#texi_of_text t @@ -836,7 +836,7 @@ class texi = | Cl _ -> Some RK_class | Cltype _ -> Some RK_class_type in (Code inh.ic_name) :: - (Ref (inh.ic_name, kind)) :: + (Ref (inh.ic_name, kind, None)) :: ( match inh.ic_text with | None -> [] | Some t -> Newline :: t) diff --git a/ocamldoc/odoc_text.ml b/ocamldoc/odoc_text.ml index 656321326..e643ca615 100644 --- a/ocamldoc/odoc_text.ml +++ b/ocamldoc/odoc_text.ml @@ -114,24 +114,33 @@ module Texter = p b "{{:%s}" s; p_text b t ; p b "}" - | Ref (s,None) -> - p b "{!%s}" s - | Ref (s, Some k) -> - ( - let sk = match k with - RK_module -> "module" - | RK_module_type -> "modtype" - | RK_class -> "class" - | RK_class_type -> "classtype" - | RK_value -> "val" - | RK_type -> "type" - | RK_exception -> "exception" - | RK_attribute -> "attribute" - | RK_method -> "method" - | RK_section _ -> "section" - in - p b "{!%s:%s}" sk s - ) + | Ref (name, kind_opt, text_opt) -> + begin + p b "%s{!%s%s}" + (match text_opt with None -> "" | Some _ -> "{") + (match kind_opt with + None -> "" + | Some k -> + let s = + match k with + RK_module -> "module" + | RK_module_type -> "modtype" + | RK_class -> "class" + | RK_class_type -> "classtype" + | RK_value -> "val" + | RK_type -> "type" + | RK_exception -> "exception" + | RK_attribute -> "attribute" + | RK_method -> "method" + | RK_section _ -> "section" + in + s^":" + ) + name; + match text_opt with + None -> () + | Some t -> p_text b t; p b "}" + end | Superscript t -> p b "{^" ; p_text b t ; p b "}" | Subscript t -> p b "{_" ; p_text b t ; p b "}" | Module_list l -> diff --git a/ocamldoc/odoc_text_lexer.mll b/ocamldoc/odoc_text_lexer.mll index d7dba4c30..73b5a1d7d 100644 --- a/ocamldoc/odoc_text_lexer.mll +++ b/ocamldoc/odoc_text_lexer.mll @@ -768,7 +768,7 @@ rule main = parse if !latex_mode or (!open_brackets >= 1) or !code_pre_mode or !ele_ref_mode then Char (Lexing.lexeme lexbuf) else - ERROR + LBRACE } | _ { diff --git a/ocamldoc/odoc_text_parser.mly b/ocamldoc/odoc_text_parser.mly index 41bebea6f..fe2fa7c9e 100644 --- a/ocamldoc/odoc_text_parser.mly +++ b/ocamldoc/odoc_text_parser.mly @@ -27,7 +27,6 @@ let remove_trailing_blanks s = let print_DEBUG s = print_string s; print_newline () %} -%token ERROR %token END %token <int * string option> Title %token BOLD @@ -49,6 +48,7 @@ let print_DEBUG s = print_string s; print_newline () %token END_VERB %token LATEX %token END_LATEX +%token LBRACE %token ELE_REF %token VAL_REF @@ -97,6 +97,20 @@ text_element_list: | text_element text_element_list { $1 :: $2 } ; +ele_ref_kind: + ELE_REF { None } +| VAL_REF { Some RK_value } +| TYP_REF { Some RK_type } +| EXC_REF { Some RK_exception } +| MOD_REF { Some RK_module } +| MODT_REF { Some RK_module_type } +| CLA_REF { Some RK_class } +| CLT_REF { Some RK_class_type } +| ATT_REF { Some RK_attribute } +| MET_REF { Some RK_method } +| SEC_REF { Some (RK_section [])} +; + text_element: Title text END { let n, l_opt = $1 in Title (n, l_opt, $2) } | BOLD text END { Bold $2 } @@ -112,61 +126,17 @@ text_element: | ENUM list END { Enum $2 } | CODE string END_CODE { Code $2 } | CODE_PRE string END_CODE_PRE { CodePre $2 } -| ELE_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, None) - } -| VAL_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_value) - } -| TYP_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_type) - } -| EXC_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_exception) - } -| MOD_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_module) - } -| MODT_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_module_type) - } -| CLA_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_class) - } -| CLT_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_class_type) - } -| ATT_REF string END { - let s2 = remove_beginning_blanks $2 in - let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_attribute) - } -| MET_REF string END { +| ele_ref_kind string END { let s2 = remove_beginning_blanks $2 in let s3 = remove_trailing_blanks s2 in - Ref (s3, Some RK_method) + Ref (s3, $1, None) } -| SEC_REF string END { - let s2 = remove_beginning_blanks $2 in +| LBRACE ele_ref_kind string END text END { + let s2 = remove_beginning_blanks $3 in let s3 = remove_trailing_blanks s2 in - Ref (s3, Some (RK_section [])) - } + Ref (s3, $2, Some $5) + } + | MOD_LIST_REF string END { let s2 = remove_beginning_blanks $2 in let s3 = remove_trailing_blanks s2 in diff --git a/ocamldoc/odoc_types.ml b/ocamldoc/odoc_types.ml index 68b3c4c9c..9a99cd624 100644 --- a/ocamldoc/odoc_types.ml +++ b/ocamldoc/odoc_types.ml @@ -41,7 +41,7 @@ and text_element = | Title of int * string option * text | Latex of string | Link of string * text - | Ref of string * ref_kind option + | Ref of string * ref_kind option * text option | Superscript of text | Subscript of text | Module_list of string list diff --git a/ocamldoc/odoc_types.mli b/ocamldoc/odoc_types.mli index f5b416ae5..d5d7e0e1c 100644 --- a/ocamldoc/odoc_types.mli +++ b/ocamldoc/odoc_types.mli @@ -45,8 +45,9 @@ and text_element = (** Style number, optional label, and text. *) | Latex of string (** A string for latex. *) | Link of string * text (** A reference string and the link text. *) - | Ref of string * ref_kind option - (** A reference to an element. Complete name and kind. *) + | Ref of string * ref_kind option * text option + (** A reference to an element. Complete name and kind. An optional + text can be given to display this text instead of the element name.*) | Superscript of text (** Superscripts. *) | Subscript of text (** Subscripts. *) | Module_list of string list diff --git a/test/ocamldoc/t1.ml b/test/ocamldoc/t1.ml index 6caf3d7af..95882948c 100644 --- a/test/ocamldoc/t1.ml +++ b/test/ocamldoc/t1.ml @@ -1,5 +1,7 @@ (** Testing display of types. - + - {{!M}lien vers le module [M]} + - {{!type:MT.t}lien vers le type [MT.t]} + {!M} @test_types_display *) @@ -7,7 +9,7 @@ let x = 1 module M = struct - let y = 2 + let y = 2 end |