diff options
Diffstat (limited to 'ocamldoc/odoc_sig.ml')
-rw-r--r-- | ocamldoc/odoc_sig.ml | 206 |
1 files changed, 103 insertions, 103 deletions
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml index d089a05b1..36b3b1411 100644 --- a/ocamldoc/odoc_sig.ml +++ b/ocamldoc/odoc_sig.ml @@ -181,18 +181,18 @@ module Analyser = (0, acc) | (name, core_type_list, loc) :: [] -> let s = get_string_of_file - loc.Location.loc_end.Lexing.pos_cnum - pos_limit - in + loc.Location.loc_end.Lexing.pos_cnum + pos_limit + in let (len, comment_opt) = My_ir.just_after_special !file_name s in (len, acc @ [ (name, comment_opt) ]) | (name, core_type_list, loc) :: (name2, core_type_list2, loc2) :: q -> - let pos_end_first = loc.Location.loc_end.Lexing.pos_cnum in - let pos_start_second = loc2.Location.loc_start.Lexing.pos_cnum in - let s = get_string_of_file pos_end_first pos_start_second in - let (_,comment_opt) = My_ir.just_after_special !file_name s in - f (acc @ [name, comment_opt]) + let pos_end_first = loc.Location.loc_end.Lexing.pos_cnum in + let pos_start_second = loc2.Location.loc_start.Lexing.pos_cnum in + let s = get_string_of_file pos_end_first pos_start_second in + let (_,comment_opt) = My_ir.just_after_special !file_name s in + f (acc @ [name, comment_opt]) ((name2, core_type_list2, loc2) :: q) in f [] cons_core_type_list_list @@ -531,8 +531,8 @@ module Analyser = 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_code = - ( + ex_code = + ( if !Odoc_args.keep_code then Some (get_string_of_file pos_start_ele pos_end_ele) else @@ -595,7 +595,7 @@ module Analyser = in (* get the type kind with the associated comments *) let type_kind = get_type_kind new_env name_comment_list sig_type_decl.Types.type_kind in - let loc_start = type_decl.Parsetree.ptype_loc.Location.loc_start.Lexing.pos_cnum in + let loc_start = type_decl.Parsetree.ptype_loc.Location.loc_start.Lexing.pos_cnum in let new_end = type_decl.Parsetree.ptype_loc.Location.loc_end.Lexing.pos_cnum + maybe_more in (* associate the comments to each constructor and build the [Type.t_type] *) let new_type = @@ -603,12 +603,12 @@ module Analyser = ty_name = Name.concat current_module_name name ; ty_info = assoc_com ; ty_parameters = - List.map2 (fun p (co,cn,_) -> - (Odoc_env.subst_type new_env p, - co, cn) - ) - sig_type_decl.Types.type_params - sig_type_decl.Types.type_variance; + List.map2 (fun p (co,cn,_) -> + (Odoc_env.subst_type new_env p, + co, cn) + ) + sig_type_decl.Types.type_params + sig_type_decl.Types.type_variance; ty_kind = type_kind ; ty_manifest = (match sig_type_decl.Types.type_manifest with @@ -619,12 +619,12 @@ module Analyser = loc_inter = Some (!file_name,loc_start) ; }; ty_code = - ( - if !Odoc_args.keep_code then - Some (get_string_of_file loc_start new_end) - else - None - ) ; + ( + if !Odoc_args.keep_code then + Some (get_string_of_file loc_start new_end) + else + None + ) ; } in let (maybe_more2, info_after_opt) = @@ -662,15 +662,15 @@ module Analyser = raise (Failure (Odoc_messages.module_not_found current_module_name name)) in let module_kind = analyse_module_kind env complete_name module_type sig_module_type in - let code_intf = - if !Odoc_args.keep_code then - let loc = module_type.Parsetree.pmty_loc in - let st = loc.Location.loc_start.Lexing.pos_cnum in - let en = loc.Location.loc_end.Lexing.pos_cnum in - Some (get_string_of_file st en) - else - None - in + let code_intf = + if !Odoc_args.keep_code then + let loc = module_type.Parsetree.pmty_loc in + let st = loc.Location.loc_start.Lexing.pos_cnum in + let en = loc.Location.loc_end.Lexing.pos_cnum in + Some (get_string_of_file st en) + else + None + in let new_module = { m_name = complete_name ; @@ -681,9 +681,9 @@ module Analyser = m_kind = module_kind ; m_loc = { loc_impl = None ; loc_inter = Some (!file_name, pos_start_ele) } ; m_top_deps = [] ; - m_code = None ; - m_code_intf = code_intf ; - m_text_only = false ; + m_code = None ; + m_code_intf = code_intf ; + m_text_only = false ; } in let (maybe_more, info_after_opt) = @@ -701,7 +701,7 @@ module Analyser = (maybe_more, new_env2, [ Element_module new_module ]) | Parsetree.Psig_recmodule decls -> - (* we start by extending the environment *) + (* we start by extending the environment *) let new_env = List.fold_left (fun acc_env -> fun (name, _) -> @@ -713,13 +713,13 @@ module Analyser = with Not_found -> raise (Failure (Odoc_messages.module_not_found current_module_name name)) in - match sig_module_type with + match sig_module_type with (* A VOIR : cela peut-il être Tmty_ident ? dans ce cas, on aurait pas la signature *) Types.Tmty_signature s -> - Odoc_env.add_signature e complete_name ~rel: name s - | _ -> - print_DEBUG "not a Tmty_signature"; - e + Odoc_env.add_signature e complete_name ~rel: name s + | _ -> + print_DEBUG "not a Tmty_signature"; + e ) env decls @@ -729,8 +729,8 @@ module Analyser = [] -> (acc_maybe_more, []) | (name, modtype) :: q -> - let complete_name = Name.concat current_module_name name in - let loc_start = modtype.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in + let complete_name = Name.concat current_module_name name in + let loc_start = modtype.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in let loc_end = modtype.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in let (assoc_com, ele_comments) = if first then @@ -738,7 +738,7 @@ module Analyser = else get_comments_in_module last_pos - loc_start + loc_start in let pos_limit2 = match q with @@ -752,18 +752,18 @@ module Analyser = raise (Failure (Odoc_messages.module_not_found current_module_name name)) in (* associate the comments to each constructor and build the [Type.t_type] *) - let module_kind = analyse_module_kind new_env complete_name modtype sig_module_type in - let code_intf = - if !Odoc_args.keep_code then - let loc = modtype.Parsetree.pmty_loc in - let st = loc.Location.loc_start.Lexing.pos_cnum in - let en = loc.Location.loc_end.Lexing.pos_cnum in - Some (get_string_of_file st en) - else - None - in - let new_module = - { + let module_kind = analyse_module_kind new_env complete_name modtype sig_module_type in + let code_intf = + if !Odoc_args.keep_code then + let loc = modtype.Parsetree.pmty_loc in + let st = loc.Location.loc_start.Lexing.pos_cnum in + let en = loc.Location.loc_end.Lexing.pos_cnum in + Some (get_string_of_file st en) + else + None + in + let new_module = + { m_name = complete_name ; m_type = sig_module_type; m_info = assoc_com ; @@ -772,17 +772,17 @@ module Analyser = m_kind = module_kind ; m_loc = { loc_impl = None ; loc_inter = Some (!file_name, pos_start_ele) } ; m_top_deps = [] ; - m_code = None ; - m_code_intf = code_intf ; - m_text_only = false ; - } - in - let (maybe_more, info_after_opt) = - My_ir.just_after_special + m_code = None ; + m_code_intf = code_intf ; + m_text_only = false ; + } + in + let (maybe_more, info_after_opt) = + My_ir.just_after_special !file_name (get_string_of_file loc_end pos_limit2) - in - new_module.m_info <- merge_infos new_module.m_info info_after_opt ; + in + new_module.m_info <- merge_infos new_module.m_info info_after_opt ; let (maybe_more2, eles) = f maybe_more @@ -869,13 +869,13 @@ module Analyser = | Parsetree.Pmty_with (mt, _) -> f mt.Parsetree.pmty_desc in - let name = (f module_type.Parsetree.pmty_desc) in - let full_name = Odoc_env.full_module_or_module_type_name env name in + let name = (f module_type.Parsetree.pmty_desc) in + let full_name = Odoc_env.full_module_or_module_type_name env name in let im = { im_name = full_name ; im_module = None ; - im_info = comment_opt; + im_info = comment_opt; } in (0, env, [ Element_included_module im ]) (* A VOIR : étendre l'environnement ? avec quoi ? *) @@ -1057,28 +1057,28 @@ module Analyser = | Parsetree.Pmty_functor (_,pmodule_type2, module_type2) -> ( - let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in + let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in let loc_end = pmodule_type2.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in - let mp_type_code = get_string_of_file loc_start loc_end in - print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code); + let mp_type_code = get_string_of_file loc_start loc_end in + print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code); match sig_module_type with Types.Tmty_functor (ident, param_module_type, body_module_type) -> - let mp_kind = analyse_module_type_kind env - current_module_name pmodule_type2 param_module_type - in + let mp_kind = analyse_module_type_kind env + current_module_name pmodule_type2 param_module_type + in let param = { mp_name = Name.from_ident ident ; mp_type = Odoc_env.subst_module_type env param_module_type ; - mp_type_code = mp_type_code ; - mp_kind = mp_kind ; + mp_type_code = mp_type_code ; + mp_kind = mp_kind ; } in - let k = analyse_module_type_kind env - current_module_name - module_type2 - body_module_type - in + let k = analyse_module_type_kind env + current_module_name + module_type2 + body_module_type + in Module_type_functor (param, k) | _ -> @@ -1100,7 +1100,7 @@ module Analyser = and analyse_module_kind env current_module_name module_type sig_module_type = match module_type.Parsetree.pmty_desc with Parsetree.Pmty_ident longident -> - let k = analyse_module_type_kind env current_module_name module_type sig_module_type in + let k = analyse_module_type_kind env current_module_name module_type sig_module_type in Module_with ( k, "" ) | Parsetree.Pmty_signature signature -> @@ -1124,26 +1124,26 @@ module Analyser = ( match sig_module_type with Types.Tmty_functor (ident, param_module_type, body_module_type) -> - let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in + let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in let loc_end = pmodule_type2.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in - let mp_type_code = get_string_of_file loc_start loc_end in - print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code); - let mp_kind = analyse_module_type_kind env - current_module_name pmodule_type2 param_module_type - in + let mp_type_code = get_string_of_file loc_start loc_end in + print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code); + let mp_kind = analyse_module_type_kind env + current_module_name pmodule_type2 param_module_type + in let param = { mp_name = Name.from_ident ident ; mp_type = Odoc_env.subst_module_type env param_module_type ; - mp_type_code = mp_type_code ; - mp_kind = mp_kind ; + mp_type_code = mp_type_code ; + mp_kind = mp_kind ; } in let k = analyse_module_kind env - current_module_name - module_type2 - body_module_type - in + current_module_name + module_type2 + body_module_type + in Module_functor (param, k) | _ -> @@ -1279,7 +1279,7 @@ module Analyser = raise (Failure "analyse_class_type_kind pas de correspondance dans le match") let analyse_signature source_file input_file - (ast : Parsetree.signature) (signat : Types.signature) = + (ast : Parsetree.signature) (signat : Types.signature) = let complete_source_file = try let curdir = Sys.getcwd () in @@ -1301,13 +1301,13 @@ module Analyser = in let (len,info_opt) = My_ir.first_special !file_name !file in let elements = - analyse_parsetree Odoc_env.empty signat mod_name len (String.length !file) ast + analyse_parsetree Odoc_env.empty signat mod_name len (String.length !file) ast in let code_intf = - if !Odoc_args.keep_code then - Some !file - else - None + if !Odoc_args.keep_code then + Some !file + else + None in { m_name = mod_name ; @@ -1318,9 +1318,9 @@ module Analyser = m_kind = Module_struct elements ; m_loc = { loc_impl = None ; loc_inter = Some (!file_name, 0) } ; m_top_deps = [] ; - m_code = None ; - m_code_intf = code_intf ; - m_text_only = false ; + m_code = None ; + m_code_intf = code_intf ; + m_text_only = false ; } end |