Skip to content

Commit 50e6a8a

Browse files
Jan WielemakerJan Wielemaker
Jan Wielemaker
authored and
Jan Wielemaker
committed
AUTOLOAD: Add explicit autoload/2 statements to all libraries provided
by this package.
1 parent 052d178 commit 50e6a8a

15 files changed

+66
-47
lines changed

cgi.pl

+2-2
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2000-2011, University of Amsterdam
6+
Copyright (c) 2000-2020, University of Amsterdam
7+
CWI, Amsterdam
78
All rights reserved.
89
910
Redistribution and use in source and binary forms, with or without
@@ -35,7 +36,6 @@
3536
:- module(cgi,
3637
[ cgi_get_form/1 % -ListOf Name(Value)
3738
]).
38-
:- use_module(library(shlib)).
3939

4040
:- use_foreign_library(foreign(cgi), install_cgi).
4141

crypt.pl

+4-4
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2000-2011, University of Amsterdam
6+
Copyright (c) 2000-2020, University of Amsterdam
77
All rights reserved.
88
99
Redistribution and use in source and binary forms, with or without
@@ -38,7 +38,7 @@
3838

3939
:- use_foreign_library(foreign(crypt), install_crypt).
4040

41-
% crypt(+Passwd, ?Encripted).
41+
%! crypt(+Passwd, ?Encripted).
4242
%
43-
% Used to test an encrypted passwd or create one. In the latter
44-
% case, the first 2 letter must be instantiated
43+
% Used to test an encrypted passwd or create one. In the latter case,
44+
% the first 2 letter must be instantiated

filesex.pl

+7-3
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2002-2018, University of Amsterdam
6+
Copyright (c) 2002-2020, University of Amsterdam
77
VU University Amsterdam
88
CWI, Amsterdam
99
All rights reserved.
@@ -47,8 +47,12 @@
4747
delete_directory_and_contents/1, % +Dir
4848
delete_directory_contents/1 % +Dir
4949
]).
50-
:- use_module(library(apply)).
51-
:- use_module(library(error)).
50+
:- autoload(library(apply),[maplist/2,maplist/3,foldl/4]).
51+
:- autoload(library(error),
52+
[permission_error/3,must_be/2,domain_error/2]).
53+
:- autoload(library(lists),[member/2]).
54+
:- autoload(library(nb_set),[empty_nb_set/1,add_nb_set/3]).
55+
5256

5357
/** <module> Extended operations on files
5458

mallocinfo.pl

+3-3
Original file line numberDiff line numberDiff line change
@@ -35,9 +35,9 @@
3535
:- module(malloc_info,
3636
[
3737
]).
38-
:- use_module(library(apply)).
39-
:- use_module(library(lists)).
40-
:- use_module(library(sgml)).
38+
:- autoload(library(apply),[maplist/3,partition/4]).
39+
:- autoload(library(lists),[selectchk/3]).
40+
:- autoload(library(sgml),[load_xml/3]).
4141

4242
:- use_foreign_library(foreign(mallocinfo)).
4343

memfile.pl

+2-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2001-2014, University of Amsterdam
6+
Copyright (c) 2001-2020, University of Amsterdam
7+
CWI, Amsterdam
78
All rights reserved.
89
910
Redistribution and use in source and binary forms, with or without

process.pl

+4-4
Original file line numberDiff line numberDiff line change
@@ -49,10 +49,10 @@
4949

5050
process_set_method/1 % +CreateMethod
5151
]).
52-
:- use_module(library(shlib)).
53-
:- use_module(library(option)).
54-
:- use_module(library(error)).
55-
:- use_module(library(apply)).
52+
:- autoload(library(apply),[maplist/3]).
53+
:- autoload(library(error),[must_be/2,existence_error/2]).
54+
:- autoload(library(option),[select_option/3]).
55+
5656

5757
:- use_foreign_library(foreign(process)).
5858

prolog_server.pl

+13-2
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,9 @@
33
Author: Jan Wielemaker & Steve Prior
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2004-2011, University of Amsterdam
6+
Copyright (c) 2004-2020, University of Amsterdam
77
VU University Amsterdam
8+
CWI, Amsterdam
89
All rights reserved.
910
1011
Redistribution and use in source and binary forms, with or without
@@ -37,7 +38,17 @@
3738
[ prolog_server/2 % +Port, +Options
3839
]).
3940

40-
:- use_module(library(socket)).
41+
:- autoload(library(lists),[member/2]).
42+
:- autoload(library(socket),
43+
[ tcp_socket/1,
44+
tcp_setopt/2,
45+
tcp_bind/2,
46+
tcp_listen/2,
47+
tcp_accept/3,
48+
tcp_open_socket/3,
49+
tcp_host_to_address/2
50+
]).
51+
4152

4253
%! prolog_server(?Port, +Options)
4354
%

prolog_stream.pl

-1
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,6 @@
3535
:- module(prolog_stream,
3636
[ open_prolog_stream/4 % +Module, +Mode, -Stream, +Data
3737
]).
38-
:- use_module(library(shlib)).
3938
:- use_foreign_library(foreign(prolog_stream)).
4039

4140
/** <module> A stream with Prolog callbacks

sha.pl

-2
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,6 @@
4141
file_sha1/2, % +File, -SHA1
4242
hash_atom/2 % +Hash, -HexAtom
4343
]).
44-
:- use_module(library(shlib)).
45-
4644
:- use_foreign_library(foreign(sha4pl)).
4745

4846
/** <module> SHA secure hashes

socket.pl

+4-4
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2000-2018, University of Amsterdam
6+
Copyright (c) 2000-2020, University of Amsterdam
77
VU University Amsterdam
88
CWI, Amsterdam
99
All rights reserved.
@@ -59,9 +59,9 @@
5959

6060
negotiate_socks_connection/2% +DesiredEndpoint, +StreamPair
6161
]).
62-
:- use_module(library(shlib)).
63-
:- use_module(library(debug)).
64-
:- use_module(library(lists)).
62+
:- autoload(library(debug),[debug/3]).
63+
:- autoload(library(lists),[last/2]).
64+
6565

6666
/** <module> Network socket (TCP and UDP) library
6767

streaminfo.pl

+4-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2009-2015, University of Amsterdam
6+
Copyright (c) 2009-2020, University of Amsterdam
7+
CWI, Amsterdam
78
All rights reserved.
89
910
Redistribution and use in source and binary forms, with or without
@@ -35,6 +36,8 @@
3536
:- module(stream_info,
3637
[ stream_info/1 % +Stream
3738
]).
39+
:- autoload(library(error),[existence_error/2]).
40+
:- autoload(library(lists),[member/2]).
3841

3942
:- use_foreign_library(foreign(streaminfo)).
4043

streampool.pl

+1-1
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@
4040
dispatch_stream_pool/1, % +TimeOut
4141
stream_pool_main_loop/0
4242
]).
43-
:- use_module(library(debug)).
43+
:- autoload(library(debug),[debug/3]).
4444

4545
:- meta_predicate
4646
add_stream_to_pool(+, 0).

syslog.pl

+3-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2013, VU University Amsterdam
6+
Copyright (c) 2013-2020, VU University Amsterdam
7+
CWI Amsterdam
78
All rights reserved.
89
910
Redistribution and use in source and binary forms, with or without
@@ -38,6 +39,7 @@
3839
syslog/3, % +Priority, +Format, +Args
3940
closelog/0
4041
]).
42+
:- autoload(library(lists),[member/2]).
4143

4244
/** <module> Unix syslog interface
4345

udp_broadcast.pl

+19-7
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
55
WWW: http://www.swi-prolog.org
66
Copyright (c) 2012-2013, Jeffrey Rosenwald
7-
2018, CWI Amsterdam
7+
2018-2020, CWI Amsterdam
88
All rights reserved.
99
1010
Redistribution and use in source and binary forms, with or without
@@ -41,12 +41,24 @@
4141
udp_peer_del/2, % +Scope, ?IP
4242
udp_peer/2 % +Scope, -IP
4343
]).
44-
:- use_module(library(socket)).
45-
:- use_module(library(broadcast)).
46-
:- use_module(library(option)).
47-
:- use_module(library(apply)).
48-
:- use_module(library(debug)).
49-
:- use_module(library(error)).
44+
:- autoload(library(apply),[maplist/2,maplist/3]).
45+
:- autoload(library(backcomp),[thread_at_exit/1]).
46+
:- autoload(library(broadcast),
47+
[broadcast_request/1,broadcast/1,listening/3,listen/3]).
48+
:- autoload(library(debug),[debug/3]).
49+
:- autoload(library(error),
50+
[must_be/2,syntax_error/1,domain_error/2,existence_error/2]).
51+
:- autoload(library(option),[option/3]).
52+
:- autoload(library(socket),
53+
[ tcp_close_socket/1,
54+
udp_socket/1,
55+
tcp_bind/2,
56+
tcp_getopt/2,
57+
tcp_setopt/2,
58+
udp_receive/4,
59+
udp_send/4
60+
]).
61+
5062

5163
% :- debug(udp(broadcast)).
5264

unix.pl

-11
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,6 @@
4545
detach_IO/1, % +Stream
4646
environ/1 % -[Name=Value]
4747
]).
48-
:- use_module(library(shlib)).
4948

5049
/** <module> Unix specific operations
5150
@@ -102,16 +101,6 @@
102101
context(_, running_threads(Others))))
103102
).
104103

105-
:- if(\+current_predicate(set_prolog_gc_thread/1)).
106-
set_prolog_gc_thread(stop) :-
107-
( catch(thread_signal(gc, abort),
108-
error(existence_error(thread, _), _),
109-
fail)
110-
-> thread_join(gc)
111-
; true
112-
).
113-
:- endif.
114-
115104
other_thread(T) :-
116105
thread_self(Me),
117106
thread_property(T, status(Status)),

0 commit comments

Comments
 (0)