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)  2006-2015, University of Amsterdam
   7                              VU University Amsterdam
   8    All rights reserved.
   9
  10    Redistribution and use in source and binary forms, with or without
  11    modification, are permitted provided that the following conditions
  12    are met:
  13
  14    1. Redistributions of source code must retain the above copyright
  15       notice, this list of conditions and the following disclaimer.
  16
  17    2. Redistributions in binary form must reproduce the above copyright
  18       notice, this list of conditions and the following disclaimer in
  19       the documentation and/or other materials provided with the
  20       distribution.
  21
  22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
  23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
  24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
  25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
  26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
  27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
  28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
  29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
  30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
  31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
  32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
  33    POSSIBILITY OF SUCH DAMAGE.
  34*/
  35
  36:- module(www_browser,
  37          [ www_open_url/1,             % +UrlOrSpec
  38            expand_url_path/2           % +Spec, -URL
  39          ]).
  40:- use_module(library(lists)).
  41:- if(exists_source(library(process))).
  42:- use_module(library(process)).
  43:- endif.
  44
  45:- multifile
  46    known_browser/2.
  47
  48/** <module> Open a URL in the users browser
  49
  50This library deals with the highly platform   specific task of opening a
  51web  page.  In  addition,   is   provides    a   mechanism   similar  to
  52absolute_file_name/3 that expands compound terms   to concrete URLs. For
  53example, the SWI-Prolog home page can be opened using:
  54
  55  ==
  56  ?- www_open_url(swipl(.)).
  57  ==
  58*/
  59
  60%!  www_open_url(+Url)
  61%
  62%   Open URL in running version of the users' browser or start a new
  63%   browser.  This predicate tries the following steps:
  64%
  65%     1. If a prolog flag (see set_prolog_flag/2) =browser= is set
  66%     and this is the name of a known executable, use this.
  67%
  68%     2. On Windows, use win_shell(open, URL)
  69%
  70%     3. Find a generic `open' comment.  Candidates are =xdg-open=,
  71%     =open= or =|gnome-open|=.
  72%
  73%     4. If a environment variable =BROWSER= is set
  74%     and this is the name of a known executable, use this.
  75%
  76%     5. Try to find a known browser.
  77%
  78%     @tbd  Figure out the right tool in step 3 as it is not
  79%           uncommon that multiple are installed.
  80
  81www_open_url(Spec) :-                   % user configured
  82    expand_url_path(Spec, URL),
  83    open_url(URL).
  84
  85open_url(URL) :-
  86    current_prolog_flag(browser, Browser),
  87    has_command(Browser),
  88    !,
  89    run_browser(Browser, URL).
  90:- if(current_predicate(win_shell/2)).
  91open_url(URL) :-                        % Windows shell
  92    win_shell(open, URL).
  93:- endif.
  94open_url(URL) :-                        % Unix `open document'
  95    open_command(Open),
  96    has_command(Open),
  97    !,
  98    run_command(Open, [URL], fg).
  99open_url(URL) :-                        % user configured
 100    getenv('BROWSER', Browser),
 101    has_command(Browser),
 102    !,
 103    run_browser(Browser, URL).
 104open_url(URL) :-                        % something we know
 105    known_browser(Browser, _),
 106    has_command(Browser),
 107    !,
 108    run_browser(Browser, URL).
 109
 110open_command(open) :-                   % Apples open command
 111    current_prolog_flag(apple, true).
 112open_command('xdg-open').               % Free desktop
 113open_command('gnome-open').             % Gnome (deprecated in favour of xdg-open
 114open_command(open).                     % Who knows
 115
 116%!  run_browser(+Browser, +URL) is det.
 117%
 118%   Open a page using a browser.
 119
 120run_browser(Browser, URL) :-
 121    run_command(Browser, [URL], bg).
 122
 123%!  run_command(+Command, +Args, +Background)
 124%
 125%   Run OS command Command using Args,   silencing  the error output
 126%   because many browsers are rather verbose.
 127
 128:- if(current_predicate(process_create/3)).
 129run_command(Command, Args, fg) :-
 130    !,
 131    process_create(path(Command), Args, [stderr(null)]).
 132:- endif.
 133:- if(current_prolog_flag(unix, true)).
 134run_command(Command, [Arg], fg) :-
 135    format(string(Cmd), "\"~w\" \"~w\" &> /dev/null", [Command, Arg]),
 136    shell(Cmd).
 137run_command(Command, [Arg], bg) :-
 138    format(string(Cmd), "\"~w\" \"~w\" &> /dev/null &", [Command, Arg]),
 139    shell(Cmd).
 140:- else.
 141run_command(Command, [Arg], fg) :-
 142    format(string(Cmd), "\"~w\" \"~w\"", [Command, Arg]),
 143    shell(Cmd).
 144run_command(Command, [Arg], bg) :-
 145    format(string(Cmd), "\"~w\" \"~w\" &", [Command, Arg]),
 146    shell(Cmd).
 147:- endif.
 148
 149%!  known_browser(+FileBaseName, -Compatible)
 150%
 151%   True if browser FileBaseName has a remote protocol compatible to
 152%   Compatible.
 153
 154known_browser(firefox,   netscape).
 155known_browser(mozilla,   netscape).
 156known_browser(netscape,  netscape).
 157known_browser(konqueror, -).
 158known_browser(opera,     -).
 159
 160
 161%!  has_command(+Command)
 162%
 163%   Succeeds if Command is in  $PATH.   Works  for Unix systems. For
 164%   Windows we have to test for executable extensions.
 165
 166:- dynamic
 167    command_cache/2.
 168:- volatile
 169    command_cache/2.
 170
 171has_command(Command) :-
 172    command_cache(Command, Path),
 173    !,
 174    Path \== (-).
 175has_command(Command) :-
 176    (   getenv('PATH', Path),
 177        (   current_prolog_flag(windows, true)
 178        ->  Sep = (;)
 179        ;   Sep = (:)
 180        ),
 181        atomic_list_concat(Parts, Sep, Path),
 182        member(Part, Parts),
 183        prolog_to_os_filename(PlPart, Part),
 184        atomic_list_concat([PlPart, Command], /, Exe),
 185        access_file(Exe, execute)
 186    ->  assert(command_cache(Command, Exe))
 187    ;   assert(command_cache(Command, -)),
 188        fail
 189    ).
 190
 191
 192                 /*******************************
 193                 *            NET PATHS         *
 194                 *******************************/
 195
 196%!  url_path(+Alias, -Expansion) is nondet.
 197%
 198%   Define URL path aliases. This multifile  predicate is defined in
 199%   module =user=. Expansion is either a URL, or a term Alias(Sub).
 200
 201:- multifile
 202    user:url_path/2.
 203
 204user:url_path(swipl,          'http://www.swi-prolog.org').
 205user:url_path(swipl_book,     'http://books.google.nl/books/about/\c
 206                               SWI_Prolog_Reference_Manual_6_2_2.html?\c
 207                               id=q6R3Q3B-VC4C&redir_esc=y').
 208
 209user:url_path(swipl_faq,      swipl('FAQ')).
 210user:url_path(swipl_man,      swipl('pldoc/doc_for?object=manual')).
 211user:url_path(swipl_mail,     swipl('Mailinglist.html')).
 212user:url_path(swipl_download, swipl('Download.html')).
 213user:url_path(swipl_pack,     swipl('pack/list')).
 214user:url_path(swipl_bugs,     swipl('bugzilla/')).
 215user:url_path(swipl_quick,    swipl('man/quickstart.html')).
 216
 217%!  expand_url_path(+Spec, -URL)
 218%
 219%   Expand URL specifications similar   to absolute_file_name/3. The
 220%   predicate url_path/2 plays the role of file_search_path/2.
 221%
 222%   @error  existence_error(url_path, Spec) if the location is not
 223%           defined.
 224
 225expand_url_path(URL, URL) :-
 226    atomic(URL),
 227    !.                 % Allow atom and string
 228expand_url_path(Spec, URL) :-
 229    Spec =.. [Path, Local],
 230    (   user:url_path(Path, Spec2)
 231    ->  expand_url_path(Spec2, URL0),
 232        (   Local == '.'
 233        ->  URL = URL0
 234        ;   sub_atom(Local, 0, _, _, #)
 235        ->  atom_concat(URL0, Local, URL)
 236        ;   atomic_list_concat([URL0, Local], /, URL)
 237        )
 238    ;   throw(error(existence_error(url_path, Path), expand_url_path/2))
 239    ).