On Windows systems, the library(unix)
library can only
be used if the whole SWI-Prolog suite is compiled using
Cywin. The other
libraries have been ported to native Windows.
Many useful facilities offered by one or more of the operating systems supported by SWI-Prolog are not supported by the SWI-Prolog kernel distribution. Including these would enlarge the footprint and complicate portability matters while supporting only a limited part of the user-community.
This document describes library(unix)
to deal with the
Unix process API,
library(socket)
to deal with inet-domain TCP and UDP
sockets, library(cgi)
to deal with getting CGI form-data if
SWI-Prolog is used as a CGI scripting language, library(crypt)
to provide password encryption and verification, library(sha)
providing cryptographic hash functions and
library(memfile)
providing in-memorty pseudo files.
The library(unix)
library provides the commonly used
Unix primitives to deal with process management. These primitives are
useful for many tasks, including server management, parallel
computation, exploiting and controlling other processes, etc.
The predicates are modelled closely after their native Unix counterparts. Higher-level primitives, especially to make this library portable to non-Unix systems are desirable. Using these primitives and considering that process manipulation is not a very time-critical operation we anticipate these libraries to be developed in Prolog.
child
. In the original process, Pid
is unified to the process identifier of the created child. Both parent
and child are fully functional Prolog processes running the same
program. The processes share open I/O streams that refer to Unix native
streams, such as files, sockets and pipes. Data is not shared, though on
most Unix systems data is initially shared and duplicated only if one of
the programs attempts to modify the data.
Unix fork() is the only way to create new processes and fork/2 is a simple direct interface to it.
Unix exec() is the only way to start an executable file executing. It is commonly used together with fork/1. For example to start netscape on an URL in the background, do:
run_netscape(URL) :- ( fork(child), exec(netscape(URL)) ; true ).
Using this code, netscape remains part of the process-group of the invoking Prolog process and Prolog does not wait for netscape to terminate. The predicate wait/2 allows waiting for a child, while detach_IO/0 disconnects the child as a deamon process.
exited(ExitCode)
if the child with pid Pid was
terminated by calling exit() (Prolog halt/[0,1]). ExitCode
is the return=status. Status is unified with signaled(Signal)
if the child died due to a software interrupt (see kill/2). Signal
contains the signal number. Finally, if the process suspended execution
due to a signal, Status is unified with stopped(Signal)
.SIG
prefix and mapping to lowercase. E.g. int
is the same as
SIGINT
in C. The meaning of the signal numbers can be found
in the Unix manual.1kill/2 should
support interrupt-names as well.:- use_module(library(unix)). fork_demo(Result) :- pipe(Read, Write), fork(Pid), ( Pid == child -> close(Read), format(Write, '~q.~n', [hello(world)]), flush_output(Write), halt ; close(Write), read(Read, Result), close(Read) ).
Both FromStream and ToStream either refer to a
Prolog stream or an integer descriptor number to refer directly to OS
descriptors. See also demo/pipe.pl
in the
source-distribution of this package.
user_input
,
user_output
and user_error
are closed and
rebound to a Prolog stream that returns end-of-file on any attempt to
read and starts writing to a file named /tmp/pl-out.pid
(where <pid> is the process-id of the calling Prolog)
on any attempt to write. This file is opened only if there is data
available. This is intended for debugging purposes.2More
subtle handling of I/O, especially for debugging is required:
communicate with the syslog deamon and optionally start a debugging
dialog on a newly created (X-)terminal should be considered.
Finally, the process is detached from the current process-group and its
controlling terminal.
The module library(process) implements interaction with child processes and unifies older interfaces such as shell/[1,2], open(pipe(command), ...) etc. This library is modelled after SICStus 4.
The main interface is formed by process_create/3. If the process id is requested the process must be waited for using process_wait/2. Otherwise the process resources are reclaimed automatically.
In addition to the predicates, this module defines a file search path
(see user:file_search_path/2 and absolute_file_name/3)
named path
that locates files on the system's search path
for executables. E.g. the following finds the executable for ls
:
?- absolute_file_name(path(ls), Path, [access(execute)]).
Incompatibilities and current limitations
path
file alias to specify an executable file on the
current PATH. Args is a list of arguments that are handed to
the new process. On Unix systems, each element in the list becomes a
seperate argument in the new process. In Windows, the arguments are
simply concatenated to form the commandline. Each argument itself is
either a primitive or a list of primitives. A primitive is either atomic
or a term file(Spec). Using file(Spec), the system inserts a filename
using the OS filename conventions which is properly quoted if needed.
Options:
true
, detach the process from the terminal (Unix only)
Currently mapped to setsid();
true
, create a window for the process (Windows only)
If the user specifies the process(-PID) option, he must call process_wait/2 to reclaim the process. Without this option, the system will wait for completion of the process after the last pipe stream is closed.
If the process is not waited for, it must succeed with status 0. If not, an process_error is raised.
Windows notes
On Windows this call is an interface to the CreateProcess() API. The commandline consists of the basename of Exe and the arguments formed from Args. Arguments are separated by a single space. If all characters satisfy iswalnum() it is unquoted. If the argument contains a double-quote it is quoted using single quotes. If both single and double quotes appear a domain_error is raised, otherwise double-quote are used.
The CreateProcess() API has many options. Currently only the
CREATE_NO_WINDOW
options is supported through the
window(+Bool) option. If omitted, the default is to use this option if
the application has no console. Future versions are likely to support
more window specific options and replace
win_exec/2.
Examples
First, a very simple example that behaves the same as
shell('ls -l')
, except for error handling:
?- process_create(path(ls), ['-l'], []).
infinite
. If this option is a number, the waits
for a maximum of Timeout seconds and unifies Status with timeout
if the process does not terminate within Timeout. In this case PID
is not invalidated. On Unix systems only timeout 0 and infinite
are supported. A 0-value can be used to poll the status of the process.
term
. Signal
is an integer, Unix signal name (e.g. SIGSTOP
) or the more
Prolog friendly variation one gets after removing SIG
and
downcase the result: stop
. On Windows systems, Signal
is ignored and the process is terminated using the TerminateProcess()
API. On Windows systems PID must be obtained from process_create/3,
while any PID is allowed on Unix systems.
The library(files)
library provides additional
operations on files from SWI-Prolog. It is currently very incomplete.
now
to indicate the current time. Defined
options are:
Here are some example queries. The first retrieves the access-time, while the second sets the last-modified time to the current time.
?- set_time_file(foo, [acess(Access)], []). ?- set_time_file(foo, [], [modified(now)]).
The library(socket)
library provides TCP and UDP
inet-domain sockets from SWI-Prolog, both client and server-side
communication. The interface of this library is very close to the Unix
socket interface, also supported by the MS-Windows winsock API.
SWI-Prolog applications that wish to communicate with multiple sources
have three options:
INET
-domain stream-socket and unifies an
identifier to it with SocketId. On MS-Windows, if the socket
library is not yet initialised, this will also initialise the library.
Adress = 'www.swi-prolog.org':http, tcp_socket(Socket), tcp_connect(Socket, Adress, Read, Write),
This predicate can be hooked by defining the multifile-predicate socket:tcp_connect_hook/4. This hook is specifically intented for proxy negotiation. The code below shows the structure of such a hook. The predicates proxy/1 and proxy_connect/3 must be provided by the user.
:- multifile socket:tcp_connect_hook/4. socket:tcp_connect_hook(Socket, Address, Read, Write) :- proxy(ProxyAdress), tcp_connect(Socket, ProxyAdress), tcp_open_socket(Socket, Read, Write), proxy_connect(Address, Read, Write).
nodelay(true)
true
, disable the Nagle optimization on this socket,
which is enabled by default on almost all modern TCP/IP stacks. The
Nagle optimization joins small packages, which is generally desirable,
but sometimes not. Please note that the underlying TCP_NODELAY setting
to setsockopt() is not available on all platforms and systems may
require additional privileges to change this option. If the option is
not supported, tcp_setopt/2
raises a domain_error exception. See Wikipedia
for details.true
. Only very specific
situations require setting this to false
.
... tcp_fcntl(Stream, setfl. nonblock), ...
As of SWI-Prolog 3.2.4, handling of non-blocking stream is supported.
An attempt to read from a non-blocking stream returns -1 (or
end_of_file
for read/1),
but at_end_of_stream/1
fails. On actual end-of-input, at_end_of_stream/1
succeeds.
ip(Byte1, Byte2, Byte3, Byte4)
.
Otherwise, if Address is bound to a ip/4 term, it is resolved
by gethostbyaddr() and the canonical hostname is unified with HostName.h_name
) of the structure
returned by the latter function.
The typical sequence for generating a server application is defined below:
create_server(Port) :- tcp_socket(Socket), tcp_bind(Socket, Port), tcp_listen(Socket, 5), tcp_open_socket(Socket, AcceptFd, _), <dispatch>
There are various options for <dispatch>. The most commonly used option is to start a Prolog thread to handle the connection. Alternatively, input from multiple clients can be handled in a single thread by listening to these clients using wait_for_input/3. Finally, on Unix systems, we can use fork/1 to handle the connection in a new process. Note that fork/1 and threads do not cooperate well. Combinations can be realised but require good understanding of POSIX thread and fork-semantics.
Below is the typical example using a thread. Note the use of setup_call_cleanup/3 to guarantee that all resources are reclaimed, also in case of failure or exceptions.
dispatch(AcceptFd) :- tcp_accept(AcceptFd, Socket, _Peer), thread_create(process_client(Socket, Peer), _, [ detached(true) ]), dispatch(AcceptFd). process_client(Socket, Peer) :- setup_call_cleanup(tcp_open_socket(Socket, In, Out), handle_service(In, Out), close_connection(In, Out)). close_connection(In, Out) :- close(In, [force(true)]), close(Out, [force(true)]). handle_service(In, Out) :- ...
The skeleton for client-communication is given below.
create_client(Host, Port) :- setup_call_catcher_cleanup(tcp_socket(Socket), tcp_connect(Socket, Host:Port), exception(_), tcp_close_socket(Socket)), setup_call_cleanup(tcp_open_socket(Socket, In, Out), chat_to_server(In, Out), close_connection(In, Out)). close_connection(In, Out) :- close(In, [force(true)]), close(Out, [force(true)]). chat_to_server(In, Out) :- ...
To deal with timeouts and multiple connections, wait_for_input/3 and/or non-blocking streams (see tcp_fcntl/3) can be used.
The library(streampool)
library dispatches input from
multiple streams based on wait_for_input/3.
It is part of the clib package as it is used most of the time together
with the library(socket)
library. On non-Unix systems it
often can only be used with socket streams.
With SWI-Prolog 5.1.x, multi-threading often provides a good
alternative to using this library. In this schema one thread watches the
listening socket waiting for connections and either creates a thread per
connection or processes the accepted connections with a pool of
worker threads. The library library(http/thread_httpd)
provides an example realising a mult-threaded HTTP server.
If Goal is called, there is some input on the associated stream. Goal must be careful not to block as this will block the entire pool.3This is hard to achieve at the moment as none of the Prolog read-commands provide for a timeout.
Below is a very simple example that reads the first line of input and echos it back.
:- use_module(library(streampool)). server(Port) :- tcp_socket(Socket), tcp_bind(Socket, Port), tcp_listen(Socket, 5), tcp_open_socket(Socket, In, _Out), add_stream_to_pool(In, accept(Socket)), stream_pool_main_loop. accept(Socket) :- tcp_accept(Socket, Slave, Peer), tcp_open_socket(Slave, In, Out), add_stream_to_pool(In, client(In, Out, Peer)). client(In, Out, _Peer) :- read_line_to_codes(In, Command), close(In), format(Out, 'Please to meet you: ~s~n', [Command]), close(Out), delete_stream_from_pool(In).
The current library provides limited support for UDP packets. The UDP protocol is a connection-less and unreliable datagram based protocol. That means that messages sent may or may not arrive at the client side and may arrive in a different order as they are sent. UDP messages are often used for streaming media or for service discovery using the broadcasting mechanism.
SOCK_DGRAM
protocol, ready
for UDP connections.atom
, codes
or string
(default).
The typical sequence to receive UDP data is:
receive(Port) :- udp_socket(S), tcp_bind(S, Port), repeat, udp_receive(Socket, Data, From, [as(atom)]), format('Got ~q from ~q~n', [Data, From]), fail.
A simple example to send UDP data is:
send(Host, Port, Message) :- udp_socket(S), udp_send(S, Message, Host:Port, []), tcp_close_socket(S).
A broadcast is achieved by using tcp_setopt(Socket, broadcast)
prior to sending the datagram and using the local network broadcast
address as a ip/4
term.
The normal mechanism to discover a service on the local network is for the client to send a broadcast message to an agreed port. The server receives this message and replies to the client with a message indicating further details to establish the communication.
This library provides high-performance C-based primitives for manipulating URIs. We decided for a C-based implementation for the much better performance on raw character manipulation. Notably, URI handling primitives are used in time-critical parts of RDF processing. This implementation is based on RFC-3986:
http://labs.apache.org/webarch/uri/rfc/rfc3986.html
The URI processing in this library is rather liberal. That is, we break URIs according to the rules, but we do not validate that the components are valid. Also, percent-decoding for IRIs is liberal. It first tries UTF-8; then ISO-Latin-1 and finally accepts %-characters verbatim.
Earlier experience has shown that strict enforcement of the URI syntax results in many errors that are accepted by many other web-document processing tools.
^(([^:/?#]+):)?(//([^/?#]*))?([^?#]*)(\?([^#]*))?(#(.*))? 12 3 4 5 6 7 8 9
Components | is a term uri_components(Scheme, Authority, Path, Search, Fragment). See uri_data/3 for accessing this structure. |
scheme
, authority
, path
, search
and fragment
uri_is_global(URI) :- uri_components(URI, Components), uri_data(Components, scheme, Scheme), nonvar(Scheme).
uri_normalized(URI, Base, NormalizedGlobalURI) :- uri_resolve(URI, Base, GlobalURI), uri_normalized(GlobalURI, NormalizedGlobalURI).
uri_normalized(URI, Base, NormalizedGlobalIRI) :- uri_resolve(URI, Base, GlobalURI), uri_normalized_iri(GlobalURI, NormalizedGlobalIRI).
?- uri_query_components(QS, [a=b, c('d+w'), n-'VU Amsterdam']). QS = 'a=b&c=d%2Bw&n=VU%20Amsterdam'. ?- uri_query_components('a=b&c=d%2Bw&n=VU%20Amsterdam', Q). Q = [a=b, c='d+w', n='VU Amsterdam'].
user
, password
, host
and port
->
Encoded), Component
specifies the URI component where the value is used. It is one of query_value
, fragment
or
path
. Besides alphanumerical characters, the following
characters are passed verbatim (the set is split in logical groups
according to RFC3986).
This is currently a very simple library, providing support for obtaining the form-data for a CGI script:
existence_error
exception is raised.
Below is a very simple CGI script that prints the passed parameters.
To test it, compile this program using the command below, copy it to
your cgi-bin directory (or make it otherwise known as a CGI-script) and
make the query http://myhost.mydomain/cgi-bin/cgidemo?hello=world
% pl -o cgidemo --goal=main --toplevel=halt -c cgidemo.pl
:- use_module(library(cgi)). main :- set_stream(current_output, encoding(utf8)), cgi_get_form(Arguments), format('Content-type: text/html; charset=UTF-8~n~n', []), format('<html>~n', []), format('<head>~n', []), format('<title>Simple SWI-Prolog CGI script</title>~n', []), format('</head>~n~n', []), format('<body>~n', []), format('<p>', []), print_args(Arguments), format('</body>~n</html>~n', []). print_args([]). print_args([A0|T]) :- A0 =.. [Name, Value], format('<b>~w</b>=<em>~w</em><br>~n', [Name, Value]), print_args(T).
Printing an HTML document using format/2
is not a neat way of producing HTML because it is vulnerable to required
escape sequences. A high-level alternative is provided by library(http/html_write)
from the HTTP library.
The startup-time of Prolog is relatively long, in particular if the program is large. In many cases it is much better to use the SWI-Prolog HTTP server library and make the main web-server relay requests to the SWI-Prolog webserver. See the SWI-Prolog HTTP package for details.
The CGI standard is unclear about handling Unicode data. The above two declarations ensure the CGI script will send all data in UTF-8 and thus provide full support of Unicode. It is assumed that browsers generally send form-data using the same encoding as the page in which the form appears, UTF-8 or ISO Latin-1. The current version of cgi_get_form/1 assumes the CGI data is in UTF-8.
MIME (Multipurpose Internet Mail Extensions) is a format for
serializing multiple typed data objects. It was designed for E-mail, but
it is also used for other applications such packaging multiple values
using the HTTP POST request on web-servers. Double Precision, Inc. has
produced the C-libraries rfc822 (mail) and rfc2045 (MIME) for decoding
and manipulating MIME messages. The library(mime)
library
is a Prolog wrapper around the rfc2045 library for decoding MIME
messages.
The general name `mime' is used for this library as it is anticipated to add MIME-creation functionality to this library.
Currently the mime library defines one predicate:
Parsed is a tree structure of mime(Attributes, Data,
PartList)
terms. Currently either Data is the empty
atom or PartList is an empty list.4It
is unclear to me whether a MIME note can contain a mixture of content
and parts, but I believe the answer is `no'.
Data is an atom holding the message data. The library
automatically decodes base64 and quoted-printable
messages. See also the transfer_encoding
attribute below.
PartList is a list of mime/3 terms. Attributes is a list holding a subset of the following arguments. For details please consult the RFC2045 document.
The library(crypt)
library defines crypt/2
for encrypting and testing passwords. The clib package also provides
crytographic hashes as described in section
10
The library supports two encryption formats: traditional Unix
DES-hashes5On non-Unix systems,
crypt() is provided by the NetBSD library. The license header is added
at the end of this document. and FreeBSD compatible MD5
hashes (all platforms). MD5 hashes start with the magic sequence $1$
,
followed by an up to 8 character salt. DES hashes start with a
2 character
salt. Note that a DES hash considers only the first 8
characters. The MD5 considers the whole string.
Salt and algorithm can be forced by instantiating the start of Encrypted with it. This is typically used to force MD5 hashes:
?- append("$1$", _, E), crypt("My password", E), format('~s~n', [E]). $1$qdaDeDZn$ZUxSQEESEHIDCHPNc3fxZ1
Encrypted is always an ASCII string. Plain only supports ISO-Latin-1 passwords in the current implementation.
Plain is either an atom, SWI-Prolog string, list of characters or list of character-codes. It is not advised to use atoms, as this implies the password will be available from the Prolog heap as a defined atom.
The library library(sha)
provides Secure Hash
Algorihms approved by FIPS (Federal Information Processing
Standard). Quoting
Wikipedia: ``The
SHA (Secure Hash Algorithm) hash functions refer to five FIPS-approved
algorithms for computing a condensed digital representation (known as a
message digest) that is, to a high degree of probability, unique for a
given input data sequence (the message). These algorithms are called
`secure' because (in the words of the standard), ``for a given
algorithm, it is computationally infeasible 1) to find a message that
corresponds to a given message digest, or 2) to find two different
messages that produce the same message digest. Any change to a message
will, with a very high probability, result in a different message
digest.''
The current library supports all 5 approved algorithms, both computing the hash-key from data and the hash Message Authentication Code (HMAC).
Input is text, represented as an atom, packed string object or code-list. Note that these functions operate on byte-sequences and therefore are not meaningful on Unicode text. The result is returned as a list of byte-values. This is the most general format that is comfortable supported by standard Prolog and can easily be transformed in other formats. Commonly used text formats are ASCII created by encoding each byte as two hexadecimal digits and ASCII created using base64 encoding. Representation as a large integer can be desirable for computational processing.
sha1
(default), sha224
, sha256
,
sha384
or sha512
Key and Data are either an atom, packed string
or list of character codes. HMAC is unified with a list of
integers representing the authentication code. Options is the
same as for
sha_hash/3,
but currently only sha1
and sha256
are
supported.
The underlying SHA-2 library is an unmodified copy created by Dr Brian Gladman, Worcester, UK. It is distributed under the license conditions below.
The free distribution and use of this software in both source and binary form is allowed (with or without changes) provided that:
ALTERNATIVELY, provided that this notice is retained in full, this product may be distributed under the terms of the GNU General Public License (GPL), in which case the provisions of the GPL apply INSTEAD OF those given above.
The library(memfile)
provides an alternative to
temporary files, intended for temporary buffering of data. Memory files
in general are faster than temporary files and do not suffer from
security riscs or naming conflicts associated with temporary-file
management. They do assume proper memory management by the hosting OS
and cannot be used to pass data to external processes using a file-name.
There is no limit to the number of memory streams, nor the size of them. However, memory-streams cannot have multiple streams at the same time (i.e. cannot be opened for reading and writing at the same time).
These predicates are first of all intended for building higher-level primitives. See also sformat/3, atom_to_term/3, term_to_atom/2 and the XPCE primitive pce_open/3.
read
or write
. The resulting Stream must be closed
using close/1.octet
,
turning the memoryfile into binary mode. Please study SWI-Prolog Unicode
and encoding issues before using this option.
true
(default false
and the memory file is
opened for reading, discard the file (see free_memory_file/1)
if the input is closed. This is used to realise open_chars_stream/2
in library(charsio).
write
yields a permission error.utf8
.The library(time)
provides timing and alarm functions.
The resolution of the alarm depends on the underlying implementation, which is based on pthread_cond_timedwait() (on Windows on the pthread emulation thereof). Long-running foreign predicates that do not call PL_handle_signals() may further delay the alarm. The relation to blocking system calls (sleep, reading from slow devices, etc.) is undefined and varies between implementations.
Options is a list of Name(Value)
terms. Defined options are:
true
(default false
), the timer is removed
automatically after fireing. Otherwise it must be destroyed explicitly
using remove_alarm/1.
false
(default true
), the timer is
allocated but not scheduled for execution. It must be started later
using install_alarm/1.
alarm(Time, Callable, Id,[])
.install(false)
or stopped using uninstall_alarm/1.done
if the alarm has been called, next
if it
is the next to be fired and scheduled otherwise.time_limit_exceeded
. See catch/3.
Please note that this predicate uses alarm/4 and therefore its effect on long-running foreign code and system calls is undefined. Blocking I/O can be handled using the timeout option of read_term/3.
The library(rlimit)
library provides an interface to the
POSIX getrlimit()/setrlimit() API that control the maximum
resource-usage of a process or group of processes. This call is
especially useful for servers such as CGI scripts and inetd-controlled
servers to avoid an uncontrolled script claiming too much resources.
cpu
CPU time in seconds fsize
Maximum filesize data
max data size stack
max stack size core
max core file size rss
max resident set size nproc
max number of processes nofile
max number of open files memlock
max locked-in-memory address
When the process hits a limit POSIX systems normally send the process a signal that terminates it. These signals may be catched using SWI-Prolog's on_signal/3 primitive. The code below illustrates this behaviour. Please note that asynchronous signal handling is dangerous, especially when using threads. 100% fail-safe operation cannot be guaranteed, but this procedure will inform the user properly `most of the time'.
rlimit_demo :- rlimit(cpu, _, 2), on_signal(xcpu, _, cpu_exceeded), ( repeat, fail ). cpu_exceeded(_Sig) :- format(user_error, 'CPU time exceeded~n', []), halt(1).
* Copyright (c) 1989, 1993 * The Regents of the University of California. All rights reserved. * * This code is derived from software contributed to Berkeley by * Tom Truscott. * * Redistribution and use in source and binary forms, with or without * modification, are permitted provided that the following conditions * are met: * 1. Redistributions of source code must retain the above copyright * notice, this list of conditions and the following disclaimer. * 2. Redistributions in binary form must reproduce the above copyright * notice, this list of conditions and the following disclaimer in the * documentation and/or other materials provided with the distribution. * 3. Neither the name of the University nor the names of its contributors * may be used to endorse or promote products derived from this software * without specific prior written permission. * * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE * ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF * SUCH DAMAGE.