Skip to content

Commit 99c04a5

Browse files
committed
ENHANCED: uri_file_name/2, mode (+,-): Allow for file://host/...
If host is the same as gethostname/1 reports.
1 parent 7191057 commit 99c04a5

File tree

1 file changed

+13
-4
lines changed

1 file changed

+13
-4
lines changed

uri.pl

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,10 @@
5656
uri_iri/2 % ?URI, ?IRI
5757
]).
5858
:- autoload(library(error), [domain_error/2]).
59+
:- if(exists_source(library(socket))).
60+
:- autoload(library(socket), [gethostname/1]).
61+
:- endif.
62+
5963
:- use_foreign_library(foreign(uri)).
6064

6165
/** <module> Process URIs
@@ -286,10 +290,8 @@
286290
!,
287291
uri_components(URI, Components),
288292
uri_data(scheme, Components, File), File == file,
289-
( uri_data(authority, Components, '')
290-
-> true
291-
; uri_data(authority, Components, localhost)
292-
),
293+
uri_data(authority, Components, Host),
294+
my_host(Host),
293295
uri_data(path, Components, FileNameEnc),
294296
uri_encoded(path, FileName0, FileNameEnc),
295297
delete_leading_slash(FileName0, FileName).
@@ -304,6 +306,13 @@
304306
uri_data(path, Components, PathEnc),
305307
uri_components(URI, Components).
306308

309+
my_host('') :- !.
310+
my_host(localhost) :- !.
311+
:- if(exists_source(library(socket))).
312+
my_host(Host) :-
313+
gethostname(Host).
314+
:- endif.
315+
307316
%! ensure_leading_slash(+WinPath, -Path).
308317
%! delete_leading_slash(+Path, -WinPath).
309318
%

0 commit comments

Comments
 (0)