35
36:- module(www_browser,
37 [ www_open_url/1, 38 expand_url_path/2 39 ]). 40:- autoload(library(lists),[member/2]). 41
42:- if(exists_source(library(process))). 43:- autoload(library(process), [process_create/3]). 44:- endif. 45
46:- multifile
47 known_browser/2.
85www_open_url(Spec) :- 86 expand_url_path(Spec, URL),
87 open_url(URL).
88
89open_url(URL) :-
90 current_prolog_flag(browser, Browser),
91 expand_browser_flag(Browser, Command, Mode),
92 has_command(Command),
93 !,
94 run_command(Command, [URL], Mode).
95:- if(current_predicate(win_shell/2)). 96open_url(URL) :- 97 win_shell(open, URL),
98 !.
99:- endif. 100open_url(URL) :- 101 open_command(Open),
102 has_command(Open),
103 !,
104 run_command(Open, [URL], fg).
105open_url(URL) :- 106 getenv('BROWSER', Browser),
107 has_command(Browser),
108 !,
109 run_browser(Browser, URL).
110open_url(URL) :- 111 known_browser(Browser, _),
112 has_command(Browser),
113 !,
114 run_browser(Browser, URL).
115
116expand_browser_flag(Command-Mode, Command, Mode) :- !.
117expand_browser_flag(Command, Command, bg) :- atomic(Command).
118
119open_command(open) :- 120 current_prolog_flag(apple, true).
121open_command('xdg-open'). 122open_command('gnome-open'). 123open_command(open).
129run_browser(Browser, URL) :-
130 run_command(Browser, [URL], bg).
137:- if(current_predicate(process_create/3)). 138run_command(Command, Args, fg) :-
139 !,
140 process_create(path(Command), Args, [stderr(null)]).
141:- endif. 142:- if(current_prolog_flag(unix, true)). 143run_command(Command, [Arg], fg) :-
144 format(string(Cmd), "\"~w\" \"~w\" &> /dev/null", [Command, Arg]),
145 shell(Cmd).
146run_command(Command, [Arg], bg) :-
147 format(string(Cmd), "\"~w\" \"~w\" &> /dev/null &", [Command, Arg]),
148 shell(Cmd).
149:- else. 150run_command(Command, [Arg], fg) :-
151 format(string(Cmd), "\"~w\" \"~w\"", [Command, Arg]),
152 shell(Cmd).
153run_command(Command, [Arg], bg) :-
154 format(string(Cmd), "\"~w\" \"~w\" &", [Command, Arg]),
155 shell(Cmd).
156:- endif.
163known_browser(firefox, netscape).
164known_browser(mozilla, netscape).
165known_browser(netscape, netscape).
166known_browser(konqueror, -).
167known_browser(opera, -).
175:- dynamic
176 command_cache/2. 177:- volatile
178 command_cache/2. 179
180has_command(Command) :-
181 command_cache(Command, Path),
182 !,
183 Path \== (-).
184has_command(Command) :-
185 ( getenv('PATH', Path),
186 ( current_prolog_flag(windows, true)
187 -> Sep = (;)
188 ; Sep = (:)
189 ),
190 atomic_list_concat(Parts, Sep, Path),
191 member(Part, Parts),
192 prolog_to_os_filename(PlPart, Part),
193 atomic_list_concat([PlPart, Command], /, Exe),
194 access_file(Exe, execute)
195 -> assert(command_cache(Command, Exe))
196 ; assert(command_cache(Command, -)),
197 fail
198 ).
199
200
201
210:- multifile
211 user:url_path/2. 212
213user:url_path(swipl, 'http://www.swi-prolog.org').
214user:url_path(swipl_book, 'http://books.google.nl/books/about/\c
215 SWI_Prolog_Reference_Manual_6_2_2.html?\c
216 id=q6R3Q3B-VC4C&redir_esc=y').
217
218user:url_path(swipl_faq, swipl('FAQ')).
219user:url_path(swipl_man, swipl('pldoc/doc_for?object=manual')).
220user:url_path(swipl_mail, swipl('Mailinglist.html')).
221user:url_path(swipl_download, swipl('Download.html')).
222user:url_path(swipl_pack, swipl('pack/list')).
223user:url_path(swipl_bugs, swipl('bug.html')).
224user:url_path(swipl_quick, swipl('man/quickstart.html')).
234expand_url_path(URL, URL) :-
235 atomic(URL),
236 !. 237expand_url_path(Spec, URL) :-
238 Spec =.. [Path, Local],
239 ( user:url_path(Path, Spec2)
240 -> expand_url_path(Spec2, URL0),
241 ( Local == '.'
242 -> URL = URL0
243 ; sub_atom(Local, 0, _, _, #)
244 -> atom_concat(URL0, Local, URL)
245 ; atomic_list_concat([URL0, Local], /, URL)
246 )
247 ; throw(error(existence_error(url_path, Path), expand_url_path/2))
248 )
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:
*/