~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to otherlibs/labltk/browser/searchpos.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
12
12
(*                                                                       *)
13
13
(*************************************************************************)
14
14
 
15
 
(* $Id: searchpos.ml 8907 2008-07-09 14:03:08Z mauny $ *)
 
15
(* $Id: searchpos.ml 10227 2010-04-02 12:53:33Z xleroy $ *)
16
16
 
17
17
open StdLabels
18
18
open Support
130
130
      add_found_sig (`Type, lid) ~env ~loc:t.ptyp_loc
131
131
  | Ptyp_alias (t, _)
132
132
  | Ptyp_poly (_, t) -> search_pos_type ~pos ~env t
 
133
  | Ptyp_package (_, stl) ->
 
134
     List.iter stl ~f:(fun (_, ty) -> search_pos_type ty ~pos ~env)
133
135
  end
134
136
 
135
137
let rec search_pos_class_type cl ~pos ~env =
178
180
        search_pos_type t2 ~pos ~env
179
181
      end
180
182
  end
181
 
  
 
183
 
182
184
let rec search_pos_signature l ~pos ~env =
183
185
  ignore (
184
186
  List.fold_left l ~init:env ~f:
203
205
      | Psig_exception (_, l) ->
204
206
          List.iter l ~f:(search_pos_type ~pos ~env);
205
207
          add_found_sig (`Type, Lident "exn") ~env ~loc:pt.psig_loc
206
 
      | Psig_module (_, t) -> 
 
208
      | Psig_module (_, t) ->
207
209
          search_pos_module t ~pos ~env
208
210
      | Psig_recmodule decls ->
209
211
          List.iter decls ~f:(fun (_, t) -> search_pos_module t ~pos ~env)
216
218
      | Psig_class_type l ->
217
219
          List.iter l
218
220
            ~f:(fun ci -> search_pos_class_type ci.pci_expr ~pos ~env)
219
 
      (* The last cases should not happen in generated interfaces *) 
 
221
      (* The last cases should not happen in generated interfaces *)
220
222
      | Psig_open lid -> add_found_sig (`Module, lid) ~env ~loc:pt.psig_loc
221
223
      | Psig_include t -> search_pos_module t ~pos ~env
222
224
      end;
235
237
        search_pos_module m ~pos ~env;
236
238
        List.iter l ~f:
237
239
          begin function
238
 
              _, Pwith_type t -> search_pos_type_decl t ~pos ~env 
 
240
              _, Pwith_type t -> search_pos_type_decl t ~pos ~env
239
241
            | _ -> ()
240
242
          end
 
243
    | Pmty_typeof md -> 
 
244
        ()   (* TODO? *)
241
245
    end
242
246
  end
243
247
 
392
396
        let l =
393
397
          match e with
394
398
            Syntaxerr.Unclosed(l,_,_,_) -> l
 
399
          | Syntaxerr.Applicative_path l -> l
395
400
          | Syntaxerr.Other l -> l
396
401
        in
397
402
        Jg_text.tag_and_see  tw ~start:(tpos l.loc_start.Lexing.pos_cnum)
435
440
 
436
441
and view_module path ~env =
437
442
  match find_module path env with
438
 
    Tmty_signature sign -> 
 
443
    Tmty_signature sign ->
439
444
      !view_defined_ref (Searchid.longident_of_path path) ~env
440
445
  | modtype ->
441
446
      let id = ident_of_path path ~default:"M" in
704
709
        add_found_str (`Class (path, cl.cl_type))
705
710
          ~env:!start_env ~loc:cl.cl_loc
706
711
    | Tclass_structure cls ->
707
 
        search_pos_class_structure ~pos cls
 
712
        search_pos_class_structure ~pos cls
708
713
    | Tclass_fun (pat, iel, cl, _) ->
709
714
        search_pos_pat pat ~pos ~env:pat.pat_env;
710
715
        List.iter iel ~f:(fun (_,exp) -> search_pos_expr exp ~pos);
812
817
  | Texp_lazy exp ->
813
818
      search_pos_expr exp ~pos
814
819
  | Texp_object (cls, _, _) ->
815
 
        search_pos_class_structure ~pos cls
 
820
      search_pos_class_structure ~pos cls
 
821
  | Texp_pack modexp ->
 
822
      search_pos_module_expr modexp ~pos
816
823
  end;
817
824
  add_found_str (`Exp(`Expr, exp.exp_type)) ~env:exp.exp_env ~loc:exp.exp_loc
818
825
  end
857
864
    | Tmod_apply (a, b, _) ->
858
865
        search_pos_module_expr a ~pos; search_pos_module_expr b ~pos
859
866
    | Tmod_constraint (m, _, _) -> search_pos_module_expr m ~pos
 
867
    | Tmod_unpack (e, _) -> search_pos_expr e ~pos
860
868
    end;
861
869
    add_found_str (`Module (Pident (Ident.create "M"), m.mod_type))
862
870
      ~env:m.mod_env ~loc:m.mod_loc