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