~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_gui.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
94
94
 
95
95
  {ok, Host} = inet:gethostname(),
96
96
  %% --------- Top Window --------------
97
 
  TopWin = gs:window(GS, [{title, "Dialyzer "++?VSN++" @ "++Host},
 
97
  TopWin = gs:window(GS, [{title, "Dialyzer " ++ ?VSN ++ " @ " ++ Host},
98
98
                          {configure, true},
99
99
                          {default, listbox, {bg, white}},
100
100
                          {default, editor, {bg, white}},
131
131
  %% --------- Options --------------
132
132
  gs:label(Packer, [{label, {text, "Analysis Options"}}, 
133
133
                    {height, 20}, {pack_xy, {2, 2}}]),
134
 
  ModePacker = gs:frame(Packer, [{packer_x, [{fixed, 75},{fixed, 120}]},
135
 
                                 {packer_y, [{fixed, 20},{fixed, 20},
 
134
  ModePacker = gs:frame(Packer, [{packer_x, [{fixed, 75}, {fixed, 120}]},
 
135
                                 {packer_y, [{fixed, 20}, {fixed, 20},
136
136
                                             {fixed, 20},
137
137
                                             %%{stretch, 1}, % empty space
138
138
                                             {fixed, 20}, {fixed, 20}, 
364
364
 
365
365
-spec gui_loop(#gui_state{}) -> ?RET_NOTHING_SUSPICIOUS.
366
366
 
367
 
gui_loop(State = #gui_state{}) ->
368
 
  TopWin = State#gui_state.top,
369
 
  Packer = State#gui_state.packer,
370
 
  ChosenBox = State#gui_state.chosen_box,
371
 
  File = State#gui_state.file_box,
372
 
  DirEntry = State#gui_state.dir_entry,
373
 
  Run = State#gui_state.run,
374
 
  AddFile = State#gui_state.add_file,
375
 
  AddAll = State#gui_state.add_all,
376
 
  AddRec = State#gui_state.add_rec,
377
 
  DelFile = State#gui_state.del_file,
378
 
  ClearChosen = State#gui_state.clear_chosen,
379
 
  ClearLog = State#gui_state.clear_log,
380
 
  ClearWarn = State#gui_state.clear_warn,
381
 
  Stop = State#gui_state.stop,
382
 
  Log = State#gui_state.log,
383
 
  BackendPid = State#gui_state.backend_pid,
384
 
 
 
367
gui_loop(#gui_state{add_all = AddAll, add_file = AddFile, add_rec = AddRec,
 
368
                    backend_pid = BackendPid, chosen_box = ChosenBox,
 
369
                    clear_chosen = ClearChosen, clear_log = ClearLog,
 
370
                    clear_warn = ClearWarn, del_file = DelFile,
 
371
                    dir_entry = DirEntry, file_box = File, log = Log,
 
372
                    menu = Menu, packer = Packer, run = Run, stop = Stop,
 
373
                    top = TopWin, warnings_box = Warn} = State) ->
385
374
  %% --- Menu ---
386
 
  Menu = State#gui_state.menu,
387
375
  Quit = Menu#menu.file_quit,
388
376
  Manual = Menu#menu.help_manual,
389
377
  HelpWarnings = Menu#menu.help_warnings,
444
432
    {gs, Stop, click, _, _} ->
445
433
      config_gui_stop(State),
446
434
      BackendPid ! {self(), stop},
447
 
      update_editor(State#gui_state.log, "\n***** Analysis stopped ****\n"),
 
435
      update_editor(Log, "\n***** Analysis stopped ****\n"),
448
436
      gui_loop(State);
449
437
    %% ----- Menu -----
450
438
    {gs, Quit, click, _, _} ->
494
482
      free_editor(State, "Analysis done", Msg),
495
483
      gui_loop(State);
496
484
    {BackendPid, log, LogMsg} ->
497
 
      update_editor(State#gui_state.log, LogMsg),
 
485
      update_editor(Log, LogMsg),
498
486
      gui_loop(State);
499
487
    {BackendPid, warnings, Warnings} ->
500
 
      WarningString = lists:flatten([dialyzer:format_warning(W) 
501
 
                                     || W <- Warnings]),
502
 
      update_editor(State#gui_state.warnings_box, WarningString),
 
488
      WarnString = lists:flatten([dialyzer:format_warning(W) || W <- Warnings]),
 
489
      update_editor(Warn, WarnString),
503
490
      gui_loop(State);
504
491
    {BackendPid, done, _NewPlt, NewDocPlt} ->
505
492
      message(State, "Analysis done"),
514
501
      config_gui_stop(State),
515
502
      gui_loop(State);
516
503
    _Other ->
517
 
      %io:format("Received ~p\n", [Other]),
 
504
      %% io:format("Received ~p\n", [Other]),
518
505
      gui_loop(State)
519
506
  end.
520
507
 
555
542
                       end
556
543
                   end, Files),
557
544
  NewAcc = ordsets:union(ordsets:from_list(SubDirs), Acc),
558
 
  all_subdirs(T++SubDirs, NewAcc);
 
545
  all_subdirs(T ++ SubDirs, NewAcc);
559
546
all_subdirs([], Acc) ->
560
547
  Acc.
561
548
 
601
588
                (filelib:is_dir(X) andalso
602
589
                 contains_files(X, Extension))
603
590
        end,
604
 
  lists:filter(Fun, Mods).
 
591
  ordsets:filter(Fun, Mods).
605
592
 
606
593
contains_files(Dir, Extension) ->
607
594
  {ok, Files} = file:list_dir(Dir),
625
612
 
626
613
%% ---- Other ----
627
614
 
628
 
change_dir_or_add_file(S = #gui_state{file_wd = FWD, mode = Mode,
629
 
                                      dir_entry = Dir,
630
 
                                      chosen_box = CBox, file_box = File},
 
615
change_dir_or_add_file(#gui_state{file_wd = FWD, mode = Mode, dir_entry = Dir,
 
616
                                  chosen_box = CBox, file_box = File} = State,
631
617
                       Text) ->
632
618
  NewWDorFile =
633
619
    case Text of
640
626
      gs:config(Dir, [{text, NewWDorFile}]),
641
627
      {ok, List} = file:list_dir(NewWDorFile),
642
628
      gs:config(File, [{items, [".."|lists:sort(List)]}]),
643
 
      S#gui_state{file_wd = NewWDorFile};
 
629
      State#gui_state{file_wd = NewWDorFile};
644
630
    false ->
645
631
      case gs:read(Mode#mode.start_byte_code, select) of
646
632
        true -> 
654
640
            RealFiles -> add_files(RealFiles, CBox, src_code)
655
641
          end
656
642
      end,
657
 
      S
 
643
      State
658
644
  end.
659
645
 
660
646
butlast([H1, H2 | T]) ->
664
650
butlast([]) ->
665
651
  ["/"].
666
652
 
667
 
change_dir_absolute(S = #gui_state{file_wd = FWD, dir_entry = Dir,
668
 
                                   file_box = File}, 
 
653
change_dir_absolute(#gui_state{file_wd = FWD, dir_entry = Dir,
 
654
                               file_box = File} = State, 
669
655
                    Text) ->
670
656
  case filelib:is_dir(Text) of
671
657
    true ->
673
659
      gs:config(Dir, [{text, WD}]),
674
660
      {ok, List} = file:list_dir(WD),
675
661
      gs:config(File, [{items, [".."|lists:sort(List)]}]),
676
 
      S#gui_state{file_wd = WD};
 
662
      State#gui_state{file_wd = WD};
677
663
    false ->
678
 
      S
 
664
      State
679
665
  end.
680
666
 
681
667
init_warnings([{Tag, GSItem}|Left], LegalWarnings) ->
697
683
  gs:config(State#gui_state.add_rec, Disabled),
698
684
  gs:config(State#gui_state.clear_warn, Disabled),
699
685
  gs:config(State#gui_state.clear_log, Disabled),
700
 
 
701
686
  Menu = State#gui_state.menu,
702
687
  gs:config(Menu#menu.file_save_warn, Disabled),
703
688
  gs:config(Menu#menu.file_save_log, Disabled),
706
691
  gs:config(Menu#menu.plt_empty, Disabled),
707
692
  gs:config(Menu#menu.plt_search_doc, Disabled),
708
693
  gs:config(Menu#menu.plt_show_doc, Disabled),
709
 
 
710
694
  Mode = State#gui_state.mode,
711
695
  gs:config(Mode#mode.start_byte_code, Disabled),
712
696
  gs:config(Mode#mode.start_src_code, Disabled).
723
707
  gs:config(State#gui_state.add_rec, Enabled),
724
708
  gs:config(State#gui_state.clear_warn, Enabled),
725
709
  gs:config(State#gui_state.clear_log, Enabled),
726
 
 
727
710
  Menu = State#gui_state.menu,
728
711
  gs:config(Menu#menu.file_save_warn, Enabled),
729
712
  gs:config(Menu#menu.file_save_log, Enabled),
732
715
  gs:config(Menu#menu.plt_empty, Enabled),
733
716
  gs:config(Menu#menu.plt_search_doc, Enabled),
734
717
  gs:config(Menu#menu.plt_show_doc, Enabled),
735
 
 
736
718
  Mode = State#gui_state.mode,
737
719
  gs:config(Mode#mode.start_byte_code, Enabled),
738
720
  gs:config(Mode#mode.start_src_code, Enabled).
818
800
      dialog_loop(Ok, Cancel, Win, TopWin)
819
801
  end.
820
802
 
821
 
maybe_quit(State = #gui_state{top = TopWin}) ->
 
803
maybe_quit(#gui_state{top = TopWin} = State) ->
822
804
  case dialog(State, "Do you really want to quit?", "Yes", "No") of
823
805
    true ->
824
806
      flush(),
938
920
  gs:config(WinPacker, WH),
939
921
  {Win, Entry, OkButton, CancelButton}.
940
922
 
941
 
save_loop(State, OkButton, CancelButton, Entry, Save, Editor) ->
942
 
  TopWin = State#gui_state.top,
 
923
save_loop(#gui_state{top = TopWin} = State,
 
924
          OkButton, CancelButton, Entry, Save, Editor) ->
943
925
  receive
944
926
    {gs, OkButton, click, _, _} ->
945
927
      File = gs:read(Entry, text),
973
955
 
974
956
%% ---- Plt Menu ----
975
957
 
976
 
search_doc_plt(#gui_state{gs = GS, top=TopWin} = State) ->
 
958
search_doc_plt(#gui_state{gs = GS, top = TopWin} = State) ->
977
959
  WH = [{width, 400}, {height, 100}],
978
960
  WHB = [{width, 120}, {height, 30}],
979
961
  Title = io_lib:format("Search the PLT", []),
1032
1014
  catch error:_ -> list_to_atom(String)
1033
1015
  end.
1034
1016
 
1035
 
show_doc_plt(State) ->
1036
 
  case State#gui_state.doc_plt of
1037
 
    undefined -> error_sms(State, "No analysis has been made yet!\n");
1038
 
    PLT ->
1039
 
      String = dialyzer_plt:get_specs(PLT),
1040
 
      free_editor(State, "Content of PLT", String)
 
1017
show_doc_plt(#gui_state{doc_plt = DocPLT} = State) ->
 
1018
  case DocPLT =:= undefined of
 
1019
    true -> error_sms(State, "No analysis has been made yet!\n");
 
1020
    false ->
 
1021
      free_editor(State, "Content of PLT", dialyzer_plt:get_specs(DocPLT))
1041
1022
  end.
1042
1023
 
1043
 
free_editor(State, Title, Contents0) ->
 
1024
free_editor(#gui_state{gs = GS, top = TopWin}, Title, Contents0) ->
1044
1025
  Contents = lists:flatten(Contents0),
1045
1026
  Tokens = string:tokens(Contents, "\n"),
1046
1027
  NofLines = length(Tokens),
1049
1030
  Height = if Height0 > 500 -> 500; true -> Height0 end,
1050
1031
  Width0 = LongestLine * 7 + 60,
1051
1032
  Width = if Width0 > 800 -> 800; true -> Width0 end,
1052
 
  GS = State#gui_state.gs,
1053
1033
  WH = [{width, Width}, {height, Height}],
1054
1034
  Win = gs:window(GS, [{title, Title}, {configure, true},
1055
1035
                       {default, editor, {bg, white}} | WH]),
1064
1044
  gs:config(Editor, {enable, false}),
1065
1045
  gs:config(Win, {map, true}),
1066
1046
  gs:config(Frame, WH),
1067
 
  TopWin = State#gui_state.top,
1068
1047
  show_info_loop(TopWin, Win, Frame, Button).
1069
1048
 
1070
1049
%% ---- Common ----
1082
1061
      show_info_loop(TopWin, Win, Frame, Button)
1083
1062
  end.
1084
1063
 
1085
 
include_dialog(State, Parent) ->
1086
 
  GS = State#gui_state.gs,
 
1064
include_dialog(#gui_state{gs = GS, options = Options}, Parent) ->
1087
1065
  WH = [{width, 300}, {height, 400}],
1088
1066
  Title = io_lib:format("Include Directories", []),
1089
1067
  Win = gs:window(GS, [{title, Title}, {configure, true},
1101
1079
                                   {packer_y, {fixed, 30}}]),
1102
1080
  AddButton = gs:button(ButtonPacker1, [{label, {text, "Add"}}, 
1103
1081
                                        {pack_xy, {1,1}}]),
1104
 
  Options = State#gui_state.options,
1105
1082
  Dirs = [io_lib:format("~s", [X]) || X <- Options#options.include_dirs],
1106
1083
  DirBox = gs:listbox(Frame, [{pack_xy, {1,4}}, {vscroll, right},
1107
1084
                                {bg, white}, {configure, true},
1364
1341
      byte_code -> filter_mods(Files, ".beam")
1365
1342
    end,
1366
1343
  FilteredDirs = [X || X <- Files, filelib:is_dir(X)],
1367
 
  case FilteredMods ++ FilteredDirs of
 
1344
  case ordsets:union(FilteredMods, FilteredDirs) of
1368
1345
    [] -> error;
1369
1346
    Set -> {ok, Set}
1370
1347
  end.