35
36:- module(www_browser,
37 [ www_open_url/1, 38 expand_url_path/2 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.
84www_open_url(Spec) :- 85 expand_url_path(Spec, URL),
86 open_url(URL).
87
88open_url(URL) :-
89 current_prolog_flag(browser, Browser),
90 expand_browser_flag(Browser, Command, Mode),
91 has_command(Command),
92 !,
93 run_command(Command, [URL], Mode).
94:- if(current_predicate(win_shell/2)). 95open_url(URL) :- 96 win_shell(open, URL).
97:- endif. 98open_url(URL) :- 99 open_command(Open),
100 has_command(Open),
101 !,
102 run_command(Open, [URL], fg).
103open_url(URL) :- 104 getenv('BROWSER', Browser),
105 has_command(Browser),
106 !,
107 run_browser(Browser, URL).
108open_url(URL) :- 109 known_browser(Browser, _),
110 has_command(Browser),
111 !,
112 run_browser(Browser, URL).
113
114expand_browser_flag(Command-Mode, Command, Mode) :- !.
115expand_browser_flag(Command, Command, bg) :- atomic(Command).
116
117open_command(open) :- 118 current_prolog_flag(apple, true).
119open_command('xdg-open'). 120open_command('gnome-open'). 121open_command(open).
127run_browser(Browser, URL) :-
128 run_command(Browser, [URL], bg).
135:- if(current_predicate(process_create/3)). 136run_command(Command, Args, fg) :-
137 !,
138 process_create(path(Command), Args, [stderr(null)]).
139:- endif. 140:- if(current_prolog_flag(unix, true)). 141run_command(Command, [Arg], fg) :-
142 format(string(Cmd), "\"~w\" \"~w\" &> /dev/null", [Command, Arg]),
143 shell(Cmd).
144run_command(Command, [Arg], bg) :-
145 format(string(Cmd), "\"~w\" \"~w\" &> /dev/null &", [Command, Arg]),
146 shell(Cmd).
147:- else. 148run_command(Command, [Arg], fg) :-
149 format(string(Cmd), "\"~w\" \"~w\"", [Command, Arg]),
150 shell(Cmd).
151run_command(Command, [Arg], bg) :-
152 format(string(Cmd), "\"~w\" \"~w\" &", [Command, Arg]),
153 shell(Cmd).
154:- endif.
161known_browser(firefox, netscape).
162known_browser(mozilla, netscape).
163known_browser(netscape, netscape).
164known_browser(konqueror, -).
165known_browser(opera, -).
173:- dynamic
174 command_cache/2. 175:- volatile
176 command_cache/2. 177
178has_command(Command) :-
179 command_cache(Command, Path),
180 !,
181 Path \== (-).
182has_command(Command) :-
183 ( getenv('PATH', Path),
184 ( current_prolog_flag(windows, true)
185 -> Sep = (;)
186 ; Sep = (:)
187 ),
188 atomic_list_concat(Parts, Sep, Path),
189 member(Part, Parts),
190 prolog_to_os_filename(PlPart, Part),
191 atomic_list_concat([PlPart, Command], /, Exe),
192 access_file(Exe, execute)
193 -> assert(command_cache(Command, Exe))
194 ; assert(command_cache(Command, -)),
195 fail
196 ).
197
198
199
208:- multifile
209 user:url_path/2. 210
211user:url_path(swipl, 'http://www.swi-prolog.org').
212user:url_path(swipl_book, 'http://books.google.nl/books/about/\c
213 SWI_Prolog_Reference_Manual_6_2_2.html?\c
214 id=q6R3Q3B-VC4C&redir_esc=y').
215
216user:url_path(swipl_faq, swipl('FAQ')).
217user:url_path(swipl_man, swipl('pldoc/doc_for?object=manual')).
218user:url_path(swipl_mail, swipl('Mailinglist.html')).
219user:url_path(swipl_download, swipl('Download.html')).
220user:url_path(swipl_pack, swipl('pack/list')).
221user:url_path(swipl_bugs, swipl('bugzilla/')).
222user:url_path(swipl_quick, swipl('man/quickstart.html')).
232expand_url_path(URL, URL) :-
233 atomic(URL),
234 !. 235expand_url_path(Spec, URL) :-
236 Spec =.. [Path, Local],
237 ( user:url_path(Path, Spec2)
238 -> expand_url_path(Spec2, URL0),
239 ( Local == '.'
240 -> URL = URL0
241 ; sub_atom(Local, 0, _, _, #)
242 -> atom_concat(URL0, Local, URL)
243 ; atomic_list_concat([URL0, Local], /, URL)
244 )
245 ; throw(error(existence_error(url_path, Path), expand_url_path/2))
246 )
Open a URL in the users browser
This library deals with the highly platform specific task of opening a web page. In addition, is provides a mechanism similar to absolute_file_name/3 that expands compound terms to concrete URLs. For example, the SWI-Prolog home page can be opened using:
*/