added field ex_code to exceptions
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5657 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
e64970f29d
commit
62e030d764
3
Changes
3
Changes
|
@ -128,7 +128,8 @@ Emacs mode:
|
|||
saved by option -dtypes.
|
||||
|
||||
OCamldoc:
|
||||
- new ty_code field for types, to keep code of type (with option -keep-code)
|
||||
- new ty_code field for types, to keep code of a type (with option -keep-code)
|
||||
- new ex_code field for types, to keep code of an exception (with option -keep-code)
|
||||
- handling recursive modules
|
||||
- handling private types
|
||||
- some fixes in html generation
|
||||
|
|
|
@ -1048,6 +1048,8 @@ module Analyser =
|
|||
raise (Failure (Odoc_messages.exception_not_found_in_typedtree complete_name))
|
||||
in
|
||||
let new_env = Odoc_env.add_exception env complete_name in
|
||||
let loc_start = loc.Location.loc_start.Lexing.pos_cnum in
|
||||
let loc_end = loc.Location.loc_end.Lexing.pos_cnum in
|
||||
let new_ex =
|
||||
{
|
||||
ex_name = complete_name ;
|
||||
|
@ -1055,6 +1057,13 @@ module Analyser =
|
|||
ex_args = List.map (Odoc_env.subst_type new_env) tt_excep_decl ;
|
||||
ex_alias = None ;
|
||||
ex_loc = { loc_impl = Some (!file_name, loc.Location.loc_start.Lexing.pos_cnum) ; loc_inter = None } ;
|
||||
ex_code =
|
||||
(
|
||||
if !Odoc_args.keep_code then
|
||||
Some (get_string_of_file loc_start loc_end)
|
||||
else
|
||||
None
|
||||
) ;
|
||||
}
|
||||
in
|
||||
(0, new_env, [ Element_exception new_ex ])
|
||||
|
@ -1077,6 +1086,7 @@ module Analyser =
|
|||
ex_alias = Some { ea_name = (Odoc_env.full_exception_name env (Name.from_path tt_path)) ;
|
||||
ea_ex = None ; } ;
|
||||
ex_loc = { loc_impl = Some (!file_name, loc.Location.loc_start.Lexing.pos_cnum) ; loc_inter = None } ;
|
||||
ex_code = None ;
|
||||
}
|
||||
in
|
||||
(0, new_env, [ Element_exception new_ex ])
|
||||
|
|
|
@ -25,5 +25,6 @@ and t_exception = {
|
|||
ex_args : Types.type_expr list ; (** the types of the parameters *)
|
||||
ex_alias : exception_alias option ;
|
||||
mutable ex_loc : Odoc_types.location ;
|
||||
mutable ex_code : string option ;
|
||||
}
|
||||
|
||||
|
|
|
@ -177,6 +177,7 @@ module Exception :
|
|||
ex_args : Types.type_expr list ; (** The types of the parameters. *)
|
||||
ex_alias : exception_alias option ; (** [None] when the exception is not a rebind. *)
|
||||
mutable ex_loc : location ;
|
||||
mutable ex_code : string option ;
|
||||
}
|
||||
end
|
||||
|
||||
|
|
|
@ -474,6 +474,7 @@ let rec merge_module_types merge_options mli ml =
|
|||
(
|
||||
ex.ex_info <- merge_info_opt merge_options ex.ex_info ex2.ex_info;
|
||||
ex.ex_loc <- { ex.ex_loc with loc_impl = ex2.ex_loc.loc_impl } ;
|
||||
ex.ex_code <- (match ex.ex_code with None -> ex2.ex_code | _ -> ex.ex_code) ;
|
||||
true
|
||||
)
|
||||
else
|
||||
|
@ -694,6 +695,7 @@ and merge_modules merge_options mli ml =
|
|||
(
|
||||
ex.ex_info <- merge_info_opt merge_options ex.ex_info ex2.ex_info;
|
||||
ex.ex_loc <- { ex.ex_loc with loc_impl = ex.ex_loc.loc_impl } ;
|
||||
ex.ex_code <- (match ex.ex_code with None -> ex2.ex_code | _ -> ex.ex_code) ;
|
||||
true
|
||||
)
|
||||
else
|
||||
|
|
|
@ -552,7 +552,14 @@ module Analyser =
|
|||
ex_info = comment_opt ;
|
||||
ex_args = List.map (Odoc_env.subst_type env) types_excep_decl ;
|
||||
ex_alias = None ;
|
||||
ex_loc = { loc_impl = None ; loc_inter = Some (!file_name, pos_start_ele) }
|
||||
ex_loc = { loc_impl = None ; loc_inter = Some (!file_name, pos_start_ele) } ;
|
||||
ex_code =
|
||||
(
|
||||
if !Odoc_args.keep_code then
|
||||
Some (get_string_of_file pos_start_ele (pos_end_ele + pos_limit))
|
||||
else
|
||||
None
|
||||
) ;
|
||||
}
|
||||
in
|
||||
let (maybe_more, info_after_opt) =
|
||||
|
|
Loading…
Reference in New Issue