View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2002-2019, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(win_menu,
   38          [ init_win_menus/0
   39          ]).   40:- autoload(library(apply),[maplist/4]).   41:- autoload(library(edit),[edit/1]).   42:- autoload(library(lists),[select/3,append/3]).   43:- autoload(library(pce),[get/8]).   44:- autoload(library(www_browser),[expand_url_path/2,www_open_url/1]).   45
   46
   47:- set_prolog_flag(generate_debug_info, false).   48:- op(200, fy, @).   49:- op(990, xfx, :=).

Console window menu

This library sets up the menu of swipl-win.exe. It is called from the system initialisation file plwin-win.rc, predicate gui_setup_/0. */

   57:- if(current_prolog_flag(console_menu_version, qt)).   58% The traditional swipl-win.exe predefines some menus.  The Qt version
   59% does not.  Here, we predefine the same menus to make the remainder
   60% compatiple.
   61menu('&File',
   62     [ 'E&xit' = pqConsole:quit_console
   63     ],
   64     [
   65     ]).
   66menu('&Edit',
   67     [ '&Copy'  = pqConsole:copy,
   68       '&Paste' = pqConsole:paste
   69     ],
   70     []).
   71menu('&Settings',
   72     [ '&Font ...' = pqConsole:select_font,
   73       '&Colors ...' = pqConsole:select_ANSI_term_colors
   74     ],
   75     []).
   76menu('&Run',
   77     [ '&Interrupt' = interrupt,
   78       '&New thread' = interactor
   79     ],
   80     []).
   81
   82menu(File,
   83     [ '&Consult ...' = action(user:load_files(+file(open,
   84                                                     'Load file into Prolog'),
   85                                               [silent(false)])),
   86       '&Edit ...'    = action(user:edit(+file(open,
   87                                               'Edit existing file'))),
   88       '&New ...'     = action(edit_new(+file(save,
   89                                              'Create new Prolog source'))),
   90       --
   91     | MRU
   92     ], [before_item('E&xit')]) :-
   93    File = '&File',
   94    findall(Mru=true, mru_info(File, Mru, _, _, _), MRU, MRUTail),
   95    MRUTail = [ --,
   96                '&Reload modified files' = user:make,
   97                --,
   98                '&Navigator ...' = prolog_ide(open_navigator),
   99                --
  100              ].
  101
  102:- else.  103
  104menu('&File',
  105     [ '&Consult ...' = action(user:load_files(+file(open,
  106                                                     'Load file into Prolog'),
  107                                               [silent(false)])),
  108       '&Edit ...'    = action(user:edit(+file(open,
  109                                               'Edit existing file'))),
  110       '&New ...'     = action(edit_new(+file(save,
  111                                              'Create new Prolog source'))),
  112       --,
  113       '&Reload modified files' = user:make,
  114       --,
  115       '&Navigator ...' = prolog_ide(open_navigator),
  116       --
  117     ],
  118     [ before_item('&Exit')
  119     ]).
  120:- endif.  121
  122menu('&Settings',
  123     [ --,
  124       '&User init file ...'  = prolog_edit_preferences(prolog),
  125       '&GUI preferences ...' = prolog_edit_preferences(xpce)
  126     ],
  127     []).
  128menu('&Debug',
  129     [ %'&Trace'             = trace,
  130       %'&Debug mode'        = debug,
  131       %'&No debug mode'     = nodebug,
  132       '&Edit spy points ...' = user:prolog_ide(open_debug_status),
  133       '&Edit exceptions ...' = user:prolog_ide(open_exceptions(@on)),
  134       '&Threads monitor ...' = user:prolog_ide(thread_monitor),
  135       'Debug &messages ...'  = user:prolog_ide(debug_monitor),
  136       'Cross &referencer ...'= user:prolog_ide(xref),
  137       --,
  138       '&Graphical debugger' = user:guitracer
  139     ],
  140     [ before_menu(-)
  141     ]).
  142menu('&Help',
  143     [ '&About ...'                             = about,
  144       '&Help ...'                              = help,
  145       'Browse &PlDoc ...'                      = doc_browser,
  146       --,
  147       'SWI-Prolog website ...'                 = www_open(swipl),
  148       '  &Manual ...'                          = www_open(swipl_man),
  149       '  &FAQ ...'                             = www_open(swipl_faq),
  150       '  &Quick Start ...'                     = www_open(swipl_quick),
  151       '  Mailing &List ...'                    = www_open(swipl_mail),
  152       '  &Download ...'                        = www_open(swipl_download),
  153       '  &Extension packs ...'                 = www_open(swipl_pack),
  154       --,
  155       '&XPCE (GUI) Manual ...'                 = manpce,
  156       --,
  157       '&Check installation'                    = check_installation,
  158       'Submit &Bug report ...'                 = www_open(swipl_bugs)
  159     ],
  160     [ before_menu(-)
  161     ]).
  162
  163
  164init_win_menus :-
  165    (   menu(Menu, Items, Options),
  166        (   memberchk(before_item(Before), Options)
  167        ->  true
  168        ;   Before = (-)
  169        ),
  170        (   memberchk(before_menu(BM), Options)
  171        ->  true
  172        ;   BM = (-)
  173        ),
  174        win_insert_menu(Menu, BM),
  175        (   '$member'(Item, Items),
  176            (   Item = (Label = Action)
  177            ->  true
  178            ;   Item == --
  179            ->  Label = --
  180            ),
  181            win_insert_menu_item(Menu, Label, Before, Action),
  182            fail
  183        ;   true
  184        ),
  185        fail
  186    ;   current_prolog_flag(associated_file, File),
  187        add_to_mru(load, File)
  188    ;   insert_associated_file
  189    ),
  190    refresh_mru.
  191
  192associated_file(File) :-
  193    current_prolog_flag(associated_file, File),
  194    !.
  195associated_file(File) :-
  196    '$cmd_option_val'(script_file, OsFiles),
  197    OsFiles = [OsFile],
  198    !,
  199    prolog_to_os_filename(File, OsFile).
  200
  201insert_associated_file :-
  202    associated_file(File),
  203    !,
  204    file_base_name(File, Base),
  205    atom_concat('Edit &', Base, Label),
  206    win_insert_menu_item('&File', Label, '&New ...', edit(file(File))).
  207insert_associated_file.
  208
  209
  210:- if(current_predicate(win_has_menu/0)).  211:- initialization
  212   (   win_has_menu
  213   ->  init_win_menus
  214   ;   true
  215   ).  216:- endif.  217
  218                 /*******************************
  219                 *            ACTIONS           *
  220                 *******************************/
  221
  222edit_new(File) :-
  223    call(edit(file(File))).         % avoid autoloading
  224
  225www_open(Id) :-
  226    Spec =.. [Id, '.'],
  227    call(expand_url_path(Spec, URL)),
  228    print_message(informational, opening_url(URL)),
  229    call(www_open_url(URL)),        % avoid autoloading
  230    print_message(informational, opened_url(URL)).
  231
  232:- if(current_predicate(win_message_box/2)).  233
  234about :-
  235    message_to_string(about, AboutSWI),
  236    (   current_prolog_flag(console_menu_version, qt)
  237    ->  message_to_string(about_qt, AboutQt),
  238        format(atom(About), '<p>~w\n<p>~w', [AboutSWI, AboutQt])
  239    ;   About = AboutSWI
  240    ),
  241    atomic_list_concat(Lines, '\n', About),
  242    atomic_list_concat(Lines, '<br>', AboutHTML),
  243    win_message_box(
  244        AboutHTML,
  245        [ title('About swipl-win'),
  246          image(':/swipl.png'),
  247          min_width(700)
  248        ]).
  249
  250:- else.  251
  252about :-
  253    print_message(informational, about).
  254
  255:- endif.  256
  257load(Path) :-
  258    (   \+ current_prolog_flag(associated_file, _)
  259    ->  file_directory_name(Path, Dir),
  260        working_directory(_, Dir),
  261        set_prolog_flag(associated_file, Path)
  262    ;   true
  263    ),
  264    user:load_files(Path).
  265
  266
  267                 /*******************************
  268                 *       HANDLE CALLBACK        *
  269                 *******************************/
  270
  271action(Action) :-
  272    strip_module(Action, Module, Plain),
  273    Plain =.. [Name|Args],
  274    gather_args(Args, Values),
  275    Goal =.. [Name|Values],
  276    call(Module:Goal).
  277
  278gather_args([], []).
  279gather_args([+H0|T0], [H|T]) :-
  280    !,
  281    gather_arg(H0, H),
  282    gather_args(T0, T).
  283gather_args([H|T0], [H|T]) :-
  284    gather_args(T0, T).
  285
  286:- if(current_prolog_flag(console_menu_version, qt)).  287
  288gather_arg(file(open, Title), File) :-
  289    !,
  290    source_types_desc(Desc),
  291    pqConsole:getOpenFileName(Title, _, Desc, File),
  292    add_to_mru(edit, File).
  293
  294gather_arg(file(save, Title), File) :-
  295    source_types_desc(Desc),
  296    pqConsole:getSaveFileName(Title, _, Desc, File),
  297    add_to_mru(edit, File).
  298
  299source_types_desc(Desc) :-
  300    findall(Pattern, prolog_file_pattern(Pattern), Patterns),
  301    atomic_list_concat(Patterns, ' ', Atom),
  302    format(atom(Desc), 'Prolog Source (~w)', [Atom]).
  303
  304:- else.  305
  306gather_arg(file(Mode, Title), File) :-
  307    findall(tuple('Prolog Source', Pattern),
  308            prolog_file_pattern(Pattern),
  309            Tuples),
  310    '$append'(Tuples, [tuple('All files', '*.*')], AllTuples),
  311    Filter =.. [chain|AllTuples],
  312    current_prolog_flag(hwnd, HWND),
  313    working_directory(CWD, CWD),
  314    call(get(@display, win_file_name,       % avoid autoloading
  315             Mode, Filter, Title,
  316             directory := CWD,
  317             owner := HWND,
  318             File)).
  319
  320:- endif.  321
  322prolog_file_pattern(Pattern) :-
  323    user:prolog_file_type(Ext, prolog),
  324    atom_concat('*.', Ext, Pattern).
  325
  326
  327:- if(current_prolog_flag(windows, true)).  328
  329                 /*******************************
  330                 *          APPLICATION         *
  331                 *******************************/
 init_win_app
If Prolog is started using --win_app, try to change directory to <My Documents>\Prolog.
  338init_win_app :-
  339    current_prolog_flag(associated_file, _),
  340    !.
  341init_win_app :-
  342    '$cmd_option_val'(win_app, true),
  343    !,
  344    catch(my_prolog, E, print_message(warning, E)).
  345init_win_app.
  346
  347my_prolog :-
  348    win_folder(personal, MyDocs),
  349    atom_concat(MyDocs, '/Prolog', PrologDir),
  350    (   ensure_dir(PrologDir)
  351    ->  working_directory(_, PrologDir)
  352    ;   working_directory(_, MyDocs)
  353    ).
  354
  355
  356ensure_dir(Dir) :-
  357    exists_directory(Dir),
  358    !.
  359ensure_dir(Dir) :-
  360    catch(make_directory(Dir), E, (print_message(warning, E), fail)).
  361
  362
  363:- initialization
  364   init_win_app.  365
  366:- endif. /*windows*/
  367
  368
  369                 /*******************************
  370                 *             MacOS            *
  371                 *******************************/
  372
  373:- if(current_prolog_flag(console_menu_version, qt)).  374
  375:- multifile
  376    prolog:file_open_event/1.  377
  378:- create_prolog_flag(app_open_first, load, []).  379:- create_prolog_flag(app_open,       edit, []).
 prolog:file_open_event(+Name)
Called when opening a file from the MacOS finder. The action depends on whether this is the first file or not, and defined by one of these flags:

On the first open event, the working directory of the process is changed to the directory holding the file. Action is one of the following:

load
Load the file into Prolog
edit
Open the file in the editor
new_instance
Open the file in a new instance of Prolog and load it there.
  401prolog:file_open_event(Path) :-
  402    (   current_prolog_flag(associated_file, _)
  403    ->  current_prolog_flag(app_open, Action)
  404    ;   current_prolog_flag(app_open_first, Action),
  405        file_directory_name(Path, Dir),
  406        working_directory(_, Dir),
  407        set_prolog_flag(associated_file, Path),
  408        insert_associated_file
  409    ),
  410    must_be(oneof([edit,load,new_instance]), Action),
  411    file_open_event(Action, Path).
  412
  413file_open_event(edit, Path) :-
  414    edit(Path).
  415file_open_event(load, Path) :-
  416    add_to_mru(load, Path),
  417    user:load_files(Path).
  418:- if(current_prolog_flag(apple, true)).  419file_open_event(new_instance, Path) :-
  420    current_app(Me),
  421    print_message(informational, new_instance(Path)),
  422    process_create(path(open), [ '-n', '-a', Me, Path ], []).
  423:- else.  424file_open_event(new_instance, Path) :-
  425    current_prolog_flag(executable, Exe),
  426    process_create(Exe, [Path], [process(_Pid)]).
  427:- endif.  428
  429
  430:- if(current_prolog_flag(apple, true)).  431current_app(App) :-
  432    current_prolog_flag(executable, Exe),
  433    file_directory_name(Exe, MacOSDir),
  434    atom_concat(App, '/Contents/MacOS', MacOSDir).
 go_home_on_plain_app_start is det
On Apple, we start in the users home dir if the application is started by opening the app directly.
  441go_home_on_plain_app_start :-
  442    current_prolog_flag(os_argv, [_Exe]),
  443    current_app(App),
  444    file_directory_name(App, Above),
  445    working_directory(PWD, PWD),
  446    same_file(PWD, Above),
  447    expand_file_name(~, [Home]),
  448    !,
  449    working_directory(_, Home).
  450go_home_on_plain_app_start.
  451
  452:- initialization
  453    go_home_on_plain_app_start.  454
  455:- endif.  456:- endif.  457
  458:- if(current_predicate(win_current_preference/3)).  459
  460mru_info('&File', 'Edit &Recent', 'MRU2',    path, edit).
  461mru_info('&File', 'Load &Recent', 'MRULoad', path, load).
  462
  463add_to_mru(Action, File) :-
  464    mru_info(_Top, _Menu, PrefGroup, PrefKey, Action),
  465    (   win_current_preference(PrefGroup, PrefKey, CPs), nonvar(CPs)
  466    ->  (   select(File, CPs, Rest)
  467        ->  Updated = [File|Rest]
  468        ;   length(CPs, Len),
  469            Len > 10
  470        ->  append(CPs1, [_], CPs),
  471            Updated = [File|CPs1]
  472        ;   Updated = [File|CPs]
  473        )
  474    ;   Updated = [File]
  475    ),
  476    win_set_preference(PrefGroup, PrefKey, Updated),
  477    refresh_mru.
  478
  479refresh_mru :-
  480    (   mru_info(FileMenu, Menu, PrefGroup, PrefKey, Action),
  481        win_current_preference(PrefGroup, PrefKey, CPs),
  482        maplist(action_path_menu(Action), CPs, Labels, Actions),
  483        win_insert_menu_item(FileMenu, Menu/Labels, -, Actions),
  484        fail
  485    ;   true
  486    ).
  487
  488action_path_menu(ActionItem, Path, Label, win_menu:Action) :-
  489    file_base_name(Path, Label),
  490    Action =.. [ActionItem, Path].
  491
  492:- else.  493
  494add_to_mru(_, _).
  495refresh_mru.
  496
  497:- endif.  498
  499
  500                 /*******************************
  501                 *            MESSAGES          *
  502                 *******************************/
  503
  504:- multifile
  505    prolog:message/3.  506
  507prolog:message(opening_url(Url)) -->
  508    [ 'Opening ~w ... '-[Url], flush ].
  509prolog:message(opened_url(_Url)) -->
  510    [ at_same_line, 'ok' ].
  511prolog:message(new_instance(Path)) -->
  512    [ 'Opening new Prolog instance for ~p'-[Path] ].
  513:- if(current_prolog_flag(console_menu_version, qt)).  514prolog:message(about_qt) -->
  515    [ 'Qt-based console by Carlo Capelli' ].
  516:- endif.