swish/commit

New upstream files

authorJan Wielemaker
Thu May 3 14:01:37 2018 +0200
committerJan Wielemaker
Thu May 3 14:01:37 2018 +0200
commit1880853342a2fc93a4d61f0d0564082eae1088cc
treef57f49dd90be19633ceff6e4f60f1724ac9bbb81
parentb51a3c60c14bc904699adffb200b6dea19283c3c
Diff style: patch stat
diff --git a/lib/swish/pack/pcache/pack.pl b/lib/swish/pack/pcache/pack.pl
new file mode 100644
index 0000000..0d0f436
--- /dev/null
+++ b/lib/swish/pack/pcache/pack.pl
@@ -0,0 +1,9 @@
+name(pcache).
+version('0.1.0').
+requires(rocksdb).
+requires(prolog >= '7.5.14').
+title('Persistent answer cache').
+keywords([cache, memoize, persistency]).
+author( 'Jan Wielemaker', 'jan@swi-prolog.org' ).
+home('https://github.com/JanWielemaker/pcache' ).
+download('https://github.com/JanWielemaker/pcache/releases/*.zip').
diff --git a/lib/swish/pack/pcache/prolog/signature.pl b/lib/swish/pack/pcache/prolog/signature.pl
new file mode 100644
index 0000000..d2ec584
--- /dev/null
+++ b/lib/swish/pack/pcache/prolog/signature.pl
@@ -0,0 +1,462 @@
+/*  Part of SWI-Prolog
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2017, VU University Amsterdam
+    All rights reserved.
+
+    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.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS 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
+    COPYRIGHT OWNER 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.
+*/
+
+:- module(prolog_signature,
+          [ goal_signature/2,           % :Goal, -Signature
+            goal_signature/3,           % :Goal, -Signature, -Vars
+            goal_provenance/2,          % :Goal, -Provenance
+            deep_predicate_hash/2,      % :Head, -Hash
+            predicate_callees/2,        % :Head, -Callees
+            predicate_dependencies/2,   % :Head, -Dependencies
+
+            sig_clean_cache/0,
+            sig_clean_cache/1           % +Module
+          ]).
+:- use_module(library(prolog_codewalk)).
+:- use_module(library(ordsets)).
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(pairs)).
+:- use_module(library(solution_sequences)).
+
+:- meta_predicate
+    goal_signature(:, -),
+    goal_signature(:, -, -),
+    goal_provenance(:, -),
+    predicate_callees(:, -),
+    deep_predicate_hash(:, -),
+    predicate_dependencies(:, -).
+
+:- multifile
+    hook_predicate_hash/2.              % :Head, -Hash
+
+/** <module> Create signatures for a program
+
+This module is concerned with creating   signatures for a predicate. The
+signature guarantees that neither the predicate   itself, not one of its
+callees has changed. This is used to support persistent result caching.
+*/
+
+%!  goal_signature(:Goal, -Term) is det.
+%!  goal_signature(:Goal, -Term, -Vars) is det.
+%
+%   Replace the module and functor of  Goal   with  a hash. For example,
+%
+%       user:between(1, 5, X),
+%
+%   becomes something like this:
+%
+%       '931be36e3ed89e766d332277a61664ff3c08d56a'(1, 5, X).
+%
+%   The hash is based on the   predicate and predicates reachable though
+%   the call graph for the most generic form.
+%
+%   @arg Vars is a term holding the variables in Goal/Term (these are
+%   the same).
+
+:- dynamic goal_signature_c/3.
+
+goal_signature(M:Goal, Term) :-
+    goal_signature_c(Goal, M, Term0),
+    predicate_dependencies_not_changed(M:Goal),
+    !,
+    Term = Term0.
+goal_signature(M:Goal, Term) :-         % non-predicate calls
+    goal_meta_head(M:Goal, Head),
+    !,
+    retractall(goal_signature_c(Goal, M, _)),
+    setup_call_cleanup(
+        asserta(M:(Head :- Goal), Ref),
+        goal_signature(M:Head, Term0),
+        erase(Ref)),
+    assertz(goal_signature_c(Goal, M, Term0)),
+    Term = Term0.
+goal_signature(Goal0, Term) :-
+    generalise(Goal0, M:Goal),
+    retractall(goal_signature_c(Goal, M, _)),
+    goal_signature_nc(M:Goal, Term0),
+    assertz(goal_signature_c(Goal, M, Term0)),
+    _:Goal = Goal0,
+    Term = Term0.
+
+%!  goal_meta_head(:Goal, -Head) is semidet.
+%
+%   True when Goal is a meta-predicate, and   Head is an artificial head
+%   created from the variables in Goal and the name `'<head>'`.
+
+goal_meta_head(M:Goal, Head) :-
+    predicate_property(M:Goal, meta_predicate(MHead)),
+    arg(_, MHead, Marg),
+    integer(Marg),
+    !,
+    term_variables(Goal, Vars),
+    Head =.. ['<head>'|Vars].
+
+
+goal_signature_nc(M:Goal, Term) :-
+    deep_predicate_hash(M:Goal, Hash),
+    Goal =.. [_|Args],
+    Term =.. [Hash|Args].
+
+goal_signature(Goal, Term, Vars) :-
+    goal_signature(Goal, Term),
+    term_variables(Term, VarList),
+    Vars =.. [v|VarList].
+
+%!  goal_provenance(:Goal, -Provenance) is det.
+%
+%   Establish  the  provenance  information  for   computing  Goal.  The
+%   provenance consists of a list of files and, for each file, a list of
+%   dicts that describe a predicate.
+
+goal_provenance(M:Goal, Provenance) :-
+    goal_meta_head(M:Goal, Head),
+    !,
+    setup_call_cleanup(
+        asserta(M:(Head :- Goal), Ref),
+        goal_provenance(M:Head, Provenance),
+        erase(Ref)).
+goal_provenance(Goal, Provenance) :-
+    predicate_dependencies(Goal, Callees),
+    maplist(predicate_provenance, Callees, ByPredicate),
+    append(ByPredicate, FlatByPredicate),
+    keysort(FlatByPredicate, ByPredicateSorted),
+    group_pairs_by_key(ByPredicateSorted, Provenance).
+
+predicate_provenance(Head, Pairs) :-
+    predicate_hash(Head, Hash),
+    predicate_source(Head, Files),
+    Dep = predicate{head:Head,
+                    hash:Hash},
+    file_pairs(Files, Dep, Pairs).
+
+file_pairs([], _, []).
+file_pairs([H|T0], Dep, [H-Dep|T]) :-
+    file_pairs(T0, Dep, T).
+
+predicate_source(Head, Files) :-
+    predicate_property(Head, multifile),
+    !,
+    findall(File, distinct(File, predicate_file(Head, File)), Files).
+predicate_source(Head, [File]) :-
+    predicate_property(Head, file(File)),
+    !.
+predicate_source(Head, Files) :-
+    predicate_property(Head, dynamic),
+    !,
+    (   Head = _:PHead,
+        functor(PHead, '<head>', _)
+    ->  Files = []
+    ;   Files = ['<dynamic>']
+    ).
+predicate_source(_, ['<unknown>']).
+
+predicate_file(Head, File) :-
+    nth_clause(Head, _, Clause),
+    clause_property(Clause, file(File)).
+
+
+%!  deep_predicate_hash(:Head, -Hash) is det.
+%
+%   Compute the predicate hash of Head and   all its callees and combine
+%   this into a single hash.
+%
+%   @tbd Could be faster by  keeping   track  of  the combined dependent
+%   hashes of predicates per module.
+
+deep_predicate_hash(Head, Hash) :-
+    predicate_dependencies(Head, Callees),
+    maplist(predicate_hash, Callees, Hashes),
+    variant_sha1(Hashes, Hash).
+
+%!  predicate_hash(:Head, -Hash) is det.
+%
+%   Compute the hash for a single   predicate. If the predicates clauses
+%   can be accessed, this is the variant  hash of all clauses, otherwise
+%   it is the variant hash of the head.
+%
+%   This predicate can be hooked using hook_predicate_hash/2.
+
+%!  hook_predicate_hash(:Head, -Hash) is semidet.
+%
+%   Hook that can be used to define   the signature of a predicate. Hash
+%   must be an SHA1 hash key   (see  variant_sha1/2). Defining this hook
+%   has two effects:
+%
+%     1. The predicate is claimed to have no dependencies.  This
+%        in itself can be exploited to prune dependency tracking.
+%     2. The signature is Hash.  A typical use case is a fact base
+%        that is derived from a file.
+
+:- dynamic predicate_hash_c/4.
+
+predicate_hash(Head, Hash) :-
+    hook_predicate_hash(Head, Hash),
+    !.
+predicate_hash(M:Head, Hash) :-
+    predicate_hash_c(Head, M, Gen, Hash0),
+    predicate_generation(M:Head, Gen),
+    !,
+    Hash = Hash0.
+predicate_hash(M:Head, Hash) :-
+    retractall(predicate_hash_c(Head, M, _, _)),
+    predicate_hash_nc(M:Head, Hash0),
+    predicate_generation(M:Head, Gen),
+    assertz(predicate_hash_c(Head, M, Gen, Hash0)),
+    Hash = Hash0.
+
+predicate_hash_nc(Head, Hash) :-
+    implementation(Head, Head1),
+    (   predicate_property(Head1, interpreted)
+    ->  Head1 = _:Head2,
+        findall((Head2:-Body), clause(Head1,Body), Clauses),
+        variant_sha1(Clauses, Hash)
+    ;   variant_sha1(Head1, Hash)
+    ).
+
+implementation(M0:Head, M:Head) :-
+    predicate_property(M0:Head, imported_from(M1)),
+    !,
+    M = M1.
+implementation(Head, Head).
+
+:- dynamic
+    predicate_dependencies_mc/3,
+    predicate_dependencies_c/3.
+
+%!  predicate_dependencies_not_changed(:Head) is semidet.
+%
+%   True when the dependencies of a predicate may have been changed.
+
+predicate_dependencies_not_changed(M:Head) :-
+    predicate_dependencies_mc(Head, M, Modules),
+    maplist(module_not_modified, Modules).
+
+%!  predicate_dependencies(:Head, -Callees:list(callable)) is det.
+%
+%   True when Callees is a set (ordered list) of all predicates that are
+%   directly or indirectly reachable through Head.
+
+predicate_dependencies(Goal, Callees) :-
+    generalise(Goal, M:Head),
+    (   hook_predicate_hash(Head, _Hash)
+    ->  Callees = []
+    ;   predicate_dependencies_mc(Head, M, Modules),
+        predicate_dependencies_c(Head, M, Callees0),
+        (   maplist(module_not_modified, Modules)
+        ->  true
+        ;   maplist(predicate_not_modified, Callees0)
+        ->  callee_modules(Callees0, Modules),
+            retractall(predicate_dependencies_mc(Head, M, _)),
+            assertz(predicate_dependencies_mc(Head, M, Modules))
+        )
+    ->  true
+    ;   retractall(predicate_dependencies_mc(Head, M, _)),
+        retractall(predicate_dependencies_c(Head, M, _)),
+        retractall(goal_signature_c(Head, M, _)),
+        predicate_dependencies_nc(M:Head, Callees0),
+        callee_modules(Callees0, Modules),
+        assertz(predicate_dependencies_c(Head, M, Callees0)),
+        assertz(predicate_dependencies_mc(Head, M, Modules))
+    ),
+    Callees = Callees0.
+
+predicate_not_modified(M:Head) :-
+    predicate_callees_c(Head, M, Gen, _Callees0),
+    predicate_generation(M:Head, Gen).
+
+module_not_modified(M-Gen) :-
+    (   module_property(M, last_modified_generation(Gen0))
+    ->  Gen0 == Gen
+    ;   Gen == 0
+    ).
+
+callee_modules(Callees, Modules) :-
+    maplist(arg(1), Callees, MList0),
+    sort(MList0, MList),
+    maplist(module_gen, MList, Modules).
+
+module_gen(M, M-Gen) :-
+    module_property(M, last_modified_generation(Gen)),
+    !.
+module_gen(M, M-0).
+
+predicate_dependencies_nc(Head0, Callees) :-
+    implementation(Head0, Head),
+    ground(Head, GHead),
+    predicate_dependencies(Head, [GHead], Callees0),
+    maplist(generalise, Callees0, Callees1),
+    order_callees(Callees1, Callees).
+
+%!  order_callees(+Callees1, -Callees) is det.
+%
+%   Order the callees such that the   ordering remains consistent in the
+%   presence of a temporary, anonymous module.   We  first order by Head
+%   and then if there are module conflicts we place the temporary module
+%   last.
+%
+%   @tbd an alternative might be to use the deep hash for ordering, such
+%   that the hash becomes  completely   independent  from  predicate and
+%   module naming.
+
+order_callees(Callees1, Callees) :-
+    sort(2, @>=, Callees1, Callees2),
+    tmp_order(Callees2, Callees).
+
+tmp_order([], []).
+tmp_order([M1:H,M2:H|T0], L) :-
+    tmp_module(M1),
+    !,
+    L = [M2:H|T],
+    tmp_order([M1:H|T0], T).
+tmp_order([H|T0], [H|T]) :-
+    tmp_order(T0, T).
+
+%!  predicate_dependencies(+Head, +Callees0, -Callees)
+%
+%   Compute the transitive  closure  of   predicates  called  from Head.
+%   Predicates are represented as M:C, where C is a numbervars-ed ground
+%   term.
+
+predicate_dependencies(Head, Callees0, Callees) :-
+    predicate_callees(Head, Called),
+    maplist(ground, Called, GCalled),
+    ord_subtract(GCalled, Callees0, New),
+    (   New == []
+    ->  Callees = Callees0
+    ;   ord_union(Callees0, GCalled, Callees1),
+        foldl(predicate_dependencies, New, Callees1, Callees)
+    ).
+
+ground(Term, Ground) :-
+    generalise(Term, Term2),
+    copy_term(Term2, Ground),
+    numbervars(Ground, 0, _).
+
+:- thread_local
+    calls/1.
+
+:- dynamic predicate_callees_c/4.
+
+predicate_callees(M:Head, Callees) :-
+    predicate_callees_c(Head, M, Gen, Callees0),
+    predicate_generation(M:Head, Gen),
+    !,
+    Callees = Callees0.
+predicate_callees(M:Head, Callees) :-
+    retractall(predicate_callees_c(Head, M, _, _)),
+    predicate_callees_nc(M:Head, Callees0),
+    predicate_generation(M:Head, Gen),
+    assertz(predicate_callees_c(Head, M, Gen, Callees0)),
+    Callees = Callees0.
+
+predicate_callees_nc(Head0, Callees) :-
+    generalise(Head0, Head),
+    findall(CRef, nth_clause(Head, _, CRef), CRefs),
+    prolog_walk_code(
+        [ clauses(CRefs),
+          autoload(true),
+          trace_reference(_:_),
+          on_trace(track_ref),
+          source(false)
+        ]),
+    findall(Callee, retract(calls(Callee)), Callees0),
+    sort(Callees0, Callees).
+
+:- public track_ref/3.
+
+track_ref(Callee0, Caller, _Location) :-
+    generalise(Callee0, Callee1),
+    implementation(Callee1, Callee),
+    (   calls(Callee)
+    ->  true
+    ;   \+ Callee \= Caller                     % exclude recursion
+    ->  true
+    ;   Callee = M:_,
+        module_property(M, class(Class)),
+        nodep_module_class(Class)
+    ->  true
+    ;   assertz(calls(Callee))
+    ).
+
+nodep_module_class(system).
+nodep_module_class(library).
+
+
+generalise(M:Head0, M:Head) :-
+    functor(Head0, Name, Arity),
+    functor(Head, Name, Arity).
+
+predicate_generation(Head, Gen) :-
+    predicate_property(Head, last_modified_generation(Gen0)),
+    !,
+    Gen = Gen0.
+predicate_generation(_, 0).
+
+%!  sig_clean_cache is det.
+%!  sig_clean_cache(+M) is det.
+%
+%   Cleanup cached signatures and dependencies. If   a  module is given,
+%   only the depedencies for the matching module are removed.
+
+sig_clean_cache :-
+    sig_clean_cache(_).
+
+sig_clean_cache(M) :-
+    retractall(goal_signature_c(_,M,_)),
+    retractall(predicate_callees_c(_,M,_,_)),
+    retractall(predicate_hash_c(_,M,_,_)),
+    retractall(predicate_dependencies_c(_,M,_)),
+    retractall(predicate_dependencies_mc(_,M,_)).
+
+%!  tmp_module(+M) is semidet.
+%
+%   True if M is a module that may   be switched while the result should
+%   still be the same. These are also   modules that can be removed from
+%   the cache.
+
+tmp_module(M) :-
+    module_property(M, class(temporary)).
+
+
+		 /*******************************
+		 *            SANDBOX		*
+		 *******************************/
+
+:- multifile sandbox:safe_meta_predicate/1.
+
+sandbox:safe_meta_predicate(prolog_signature:goal_signature/2).
+sandbox:safe_meta_predicate(prolog_signature:goal_signature/3).
+sandbox:safe_meta_predicate(prolog_signature:goal_provenance/2).
+sandbox:safe_meta_predicate(prolog_signature:deep_predicate_hash/2).
diff --git a/lib/swish/pack/wordnet/pack.pl b/lib/swish/pack/wordnet/pack.pl
new file mode 100644
index 0000000..abe8bf2
--- /dev/null
+++ b/lib/swish/pack/wordnet/pack.pl
@@ -0,0 +1,7 @@
+name(wordnet).
+version('0.9.1').
+title('Access to WordNet database').
+keywords([wordnet, lexical, nlp]).
+author( 'Jan Wielemaker', 'jan@swi-prolog.org' ).
+home('https://github.com/JanWielemaker/wordnet' ).
+download( 'https://github.com/JanWielemaker/wordnet/releases/*.zip' ).
diff --git a/lib/swish/pack/wordnet/prolog/wn.pl b/lib/swish/pack/wordnet/prolog/wn.pl
new file mode 100644
index 0000000..d3a83ef
--- /dev/null
+++ b/lib/swish/pack/wordnet/prolog/wn.pl
@@ -0,0 +1,431 @@
+/*  Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2017, VU University Amsterdam
+    All rights reserved.
+
+    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.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS 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
+    COPYRIGHT OWNER 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.
+*/
+
+:- module(wordnet,
+	  [ wn_s/6,			% basic Wordnet relations
+	    wn_g/2,
+	    wn_hyp/2,
+	    wn_ins/2,
+	    wn_ent/2,
+	    wn_sim/2,
+	    wn_mm/2,
+	    wn_ms/2,
+	    wn_mp/2,
+	    wn_der/4,
+	    wn_cls/5,
+	    wn_cs/2,
+	    wn_vgp/4,
+	    wn_at/2,
+	    wn_ant/4,
+	    wn_sa/4,
+	    wn_sk/3,
+	    wn_syntax/3,
+	    wn_ppl/4,
+	    wn_per/4,
+	    wn_fr/3,
+
+	    wn_cat/3,			% +SynSet, -SyntacticCategory, -Offset
+	    ss_type/2,			% +Code, -Type
+
+	    load_wordnet/0		% force loading everything
+	  ]).
+
+/** <module> Wordnet lexical and semantic database
+
+This module discloses the Wordnet  Prolog   files  is  a more SWI-Prolog
+friendly manner. It exploits SWI-Prolog   demand-loading  and SWI-Prolog
+Quick Load Files to load `just-in-time' and as quickly as possible.
+
+The system creates Quick Load Files for  each wordnet file needed if the
+.qlf file doesn't exist and  the   wordnet  directory  is writeable. For
+shared installations it is adviced to   run  load_wordnet/0 as user with
+sufficient privileges to create the Quick Load Files.
+
+This library defines a portray/1 rule to explain synset ids.
+
+Some more remarks:
+
+ - SynSet identifiers are large numbers. Such numbers require
+   significant more space on the stacks but not in clauses and
+   therefore it is not considered worthwhile to strip the
+   type info represented in the most significant digit.
+
+ - On wordnet 2.0, the syntactic category deduced from the
+   synset id is consistent with the 4th argument of s/6, though
+   both adjective and adjective_satellite are represented as
+   3XXXXXXXX
+
+@author Originally by Jan Wielemaker.  Partly documented by an
+unknown author.  Current commens copied from prologdb.5WN.html
+file from the sources.
+@see Wordnet is a lexical database for the English language. See
+http://www.cogsci.princeton.edu/~wn/
+*/
+
+
+		 /*******************************
+		 *          FIND WORDNET	*
+		 *******************************/
+
+:- multifile user:file_search_path/2.
+
+user:file_search_path(wndb, WNDB) :-
+    (   getenv('WNDB', WNDB)
+    ->  true
+    ;   current_prolog_flag(windows, true)
+    ->  WNDB = 'C:\\Program Files\\WordNet\\3.0'
+    ;   WNDB = '/usr/local/WordNet-3.0'
+    ).
+
+haswndb :-
+    absolute_file_name(wndb(wn_s), _,
+                       [ file_type(prolog),
+                         access(read),
+                         file_errors(fail)
+                       ]).
+checkwndb :-
+    haswndb,
+    !.
+checkwndb :-
+    print_message(error, wordnet(nodb)).
+
+:- initialization
+    checkwndb.
+
+
+%!  wn_op(PredSpec) is nondet.
+%
+%   Definition of wordnet operator types.
+
+wn_op(ant(synset_id, w_num, synset_id, w_num)).
+wn_op(at(synset_id, synset_id)).
+wn_op(cls(synset_id, w_num, synset_id, wn_num, class_type)).
+wn_op(cs(synset_id, synset_id)).
+wn_op(der(synset_id, w_num, synset_id, wn_num)).
+wn_op(ent(synset_id, synset_id)).
+wn_op(fr(synset_id, w_num, f_num)).
+wn_op(g(synset_id, '(gloss)')).
+wn_op(hyp(synset_id, synset_id)).
+wn_op(ins(synset_id, synset_id)).
+wn_op(mm(synset_id, synset_id)).
+wn_op(mp(synset_id, synset_id)).
+wn_op(ms(synset_id, synset_id)).
+wn_op(per(synset_id, w_num, synset_id, w_num)).
+wn_op(ppl(synset_id, w_num, synset_id, w_num)).
+wn_op(s(synset_id, w_num, 'word', ss_type, sense_number, tag_count)).
+wn_op(sa(synset_id, w_num, synset_id, w_num)).
+wn_op(sim(synset_id, synset_id)).
+wn_op(sk(synset_id, w_num, sense_key)).
+wn_op(syntax(synset_id, w_num, syntax)).
+wn_op(vgp(synset_id, w_num, synset_id, w_num)).
+
+
+		 /*******************************
+		 *    WORDNET BASIC RELATIONS   *
+		 *******************************/
+
+%!  wn_ant(?Antonym1, ?Wnum1, ?Antonym2, ?WNum2) is nondet.
+%
+%   The ant operator specifies antonymous  word   s.  This  is a lexical
+%   relation  that  holds  for  all    syntactic  categories.  For  each
+%   antonymous pair, both relations are listed (ie. each synset_id,w_num
+%   pair is both a source and target word.)
+
+wn_ant(Antonym1, Wnum1, Antonym2, WNum2) :- ant(Antonym1, Wnum1, Antonym2, WNum2).
+
+%!  wn_at(?Noun, ?Adjective) is nondet.
+%
+%   The at operator defines the  attribute   relation  between  noun and
+%   adjective synset pairs in which the  adjective   is  a  value of the
+%   noun. For each pair, both relations   are listed (ie. each synset_id
+%   is both a source and target).
+
+wn_at(Noun, Adjective) :- at(Noun, Adjective).
+
+%!  wn_cls(?SynSet, ?W1, ?Class, ?W2, ?ClassType) is nondet.
+%
+%   The cls operator specifies that the first synset has been classified
+%   as a member of the class represented by the second synset. Either of
+%   the w_num's can be 0, reflecting that the pointer is semantic in the
+%   original WordNet database.
+
+wn_cls(SynSet, W1, Class, W2, ClassType) :-
+    cls(SynSet, W1, Class, W2, ClassType).
+
+%!  wn_cs(?SynSet, ?Causes) is nondet.
+%
+%   First kind of event is caused by second.
+%
+%   The cs operator specifies that the second   synset is a cause of the
+%   first synset. This relation only holds for verbs.
+
+wn_cs(SynSet, Causes) :-
+    cs(SynSet, Causes).
+
+%!  wn_der(?SynSet1, ?W1, ?SynSet2, ?W2) is nondet.
+%
+%   The der operator specifies that  there   exists  a reflexive lexical
+%   morphosemantic relation between the first   and  second synset terms
+%   representing derivational morphology.
+
+wn_der(SynSet1, W1, SynSet2, W2) :-
+    der(SynSet1, W1, SynSet2, W2).
+
+%!  wn_ent(?SynSet, ?Entailment) is nondet.
+%
+%   The ent operator specifies that the   second synset is an entailment
+%   of first synset. This relation only holds for verbs.
+
+wn_ent(SynSet, Entailment) :-
+    ent(SynSet, Entailment).
+
+%!  wn_fr(?Synset, ?Wnum, ?Fnum) is nondet.
+%
+%   fr operator specifies a generic sentence frame  for one or all words
+%   in a synset. The operator is defined only for verbs.
+
+wn_fr(Synset, Wnum, Fnum) :-
+    fr(Synset, Wnum, Fnum).
+
+%!  wn_g(?SynSet, ?Gloss) is nondet.
+%
+%   The g operator specifies the gloss for a synset.
+
+wn_g(SynSet, Gloss) :-
+    g(SynSet, Gloss).
+
+%!  wn_hyp(?Hyponym, ?HyperNym) is nondet.
+%
+%   The hyp operator specifies that the second   synset is a hypernym of
+%   the first synset. This  relation  holds   for  nouns  and verbs. The
+%   reflexive operator, hyponym, implies that  the   first  synset  is a
+%   hyponym of the second synset.
+
+wn_hyp(Hyponym, HyperNym) :-
+    hyp(Hyponym, HyperNym).
+
+%!  wn_ins(?A,?B) is nondet.
+%
+%   The ins operator specifies that the first   synset is an instance of
+%   the second synset. This relation  holds   for  nouns.  The reflexive
+%   operator,  has_instance,  implies  that  the  second  synset  is  an
+%   instance of the first synset.
+
+wn_ins(A,B) :- ins(A,B).
+
+%!  wn_mm(?SynSet, ?MemberMeronym) is nondet.
+%
+%   The mm operator specifies that the second synset is a member meronym
+%   of the first  synset.  This  relation   only  holds  for  nouns. The
+%   reflexive operator, member holonym, can be implied.
+
+wn_mm(SynSet, MemberMeronym) :-
+    mm(SynSet, MemberMeronym).
+
+%!  wn_mp(?SynSet, ?PartMeronym) is nondet.
+%
+%   The mp opeQrator specifies that the second synset is a part meronym
+%   of the first synset. This relation only holds for nouns. The
+%   reflexive operator, part holonym, can be implied.
+
+wn_mp(SynSet, PartMeronym) :-
+    ms(SynSet, PartMeronym).
+
+%!  wn_ms(?SynSet, ?SubstanceMeronym) is nondet.
+%
+%   The ms operator specifies that  the   second  synset  is a substance
+%   meronym of the first synset. This relation only holds for nouns. The
+%   reflexive operator, substance holonym, can be implied.
+
+wn_ms(SynSet, SubstanceMeronym) :-
+    ms(SynSet, SubstanceMeronym).
+
+%!  wn_per(?Synset1, ?WNum1, ?Synset2, ?WNum2) is nondet.
+%
+%   The per operator specifies two  different   relations  based  on the
+%   parts of speech involved. If  the  first   word  is  in an adjective
+%   synset, that word pertains to either   the  noun or adjective second
+%   word. If the first word is in an adverb synset, that word is derived
+%   from the adjective second word.
+
+wn_per(Synset1, WNum1, Synset2, WNum2) :-
+    per(Synset1, WNum1, Synset2, WNum2).
+
+%!  wn_ppl(?Synset1, ?WNum1, ?Synset2, ?WNum2) is nondet.
+%
+%   ppl operator specifies that the adjective first word is a participle
+%   of the verb second word. The reflexive operator can be implied.
+
+wn_ppl(Synset1, WNum1, Synset2, WNum2) :-
+    ppl(Synset1, WNum1, Synset2, WNum2).
+
+%!  wn_s(?SynSet, ?WNum, ?Word, ?SynSetType, ?Sense, ?Tag) is nondet.
+%
+%   A s operator is present for every word sense in WordNet. In wn_s.pl,
+%   w_num specifies the word number for word in the synset.
+
+wn_s(SynSet, WNum, Word, SynSetType, Sense, Tag) :-
+    s(SynSet, WNum, Word, SynSetType, Sense, Tag).
+
+%!  wn_sa(?Synset1, ?WNum1, ?Synset2, ?WNum2) is nondet.
+%
+%   The sa operator specifies  that   additional  information  about the
+%   first word can be obtained by seeing  the second word. This operator
+%   is only defined for verbs  and   adjectives.  There  is no reflexive
+%   relation (ie. it cannot be inferred  that the additional information
+%   about the second word can be obtained from the first word).
+
+wn_sa(Synset1, WNum1, Synset2, WNum2) :-
+    sa(Synset1, WNum1, Synset2, WNum2).
+
+%!  wn_sim(?SynSet, ?Similar) is nondet.
+%
+%   The sim operator specifies that  the   second  synset  is similar in
+%   meaning to the first synset. This means  that the second synset is a
+%   satellite the first synset, which is the cluster head. This relation
+%   only holds for adjective synsets contained in adjective clusters.
+
+wn_sim(SynSet, Similar) :-
+    sim(SynSet, Similar).
+
+%!  wn_sk(?A,?B,?C) is nondet.
+%
+%   A sk operator is present for every word sense in WordNet. This gives
+%   the WordNet sense key for each word sense.
+
+wn_sk(A,B,C) :-
+    sk(A,B,C).
+
+%!  wn_syntax(?A,?B,?C) is nondet.
+%
+%   The syntax operator specifies the syntactic  marker for a given word
+%   sense if one is specified.
+
+wn_syntax(A,B,C) :-
+    syntax(A,B,C).
+
+%!  wn_vgp(?Verb, ?W1, ?Similar, ?W2) is nondet.
+%
+%   vgp operator specifies verb synsets that  are similar in meaning and
+%   should be grouped together when displayed   in response to a grouped
+%   synset search.
+
+wn_vgp(Verb, W1, Similar, W2) :-
+    vgp(Verb, W1, Similar, W2).
+
+
+		 /*******************************
+		 *	   CODE MAPPINGS	*
+		 *******************************/
+
+%!	wn_cat(+SynSet, -SyntacticCategory, -Offset) is det.
+%
+%	Break the synset id into its   syntactic  category and offset as
+%	defined in the manpage prologdb.5
+
+wn_cat(SynSet, Category, Small) :-
+	Small is SynSet mod 100000000,
+	CatNum is SynSet // 100000000,
+	wn_cat(CatNum, Category).
+
+wn_cat(1, noun).
+wn_cat(2, verb).
+wn_cat(3, adjective).
+wn_cat(4, adverb).
+
+%!	ss_type(+Code, -Type) is det.
+%!	ss_type(-Code, -Type) is nondet.
+%
+%	Mapping between readable syntactic category and code.
+
+ss_type(n, noun).
+ss_type(v, verb).
+ss_type(a, adjective).
+ss_type(s, adjective_satellite).
+ss_type(r, adverb).
+
+
+%!	load_wordnet is det.
+%
+%	Load all of wordnet.  This must be used to create all .QLF
+%	files or before creating a stand-alone saved state
+
+load_wordnet :-
+	(   wn_op(O),
+	    functor(O, Name, _),
+	    load_op(Name),
+	    fail
+	;   true
+	).
+
+load_op(Name) :-
+	atom_concat('wn_', Name, File),
+	absolute_file_name(wndb(File),
+			   [ access(read),
+			     file_type(prolog)
+			   ],
+			   PlFile),
+	file_name_extension(Base, _Ext, PlFile),
+	file_name_extension(Base, qlf, QlfFile),
+	(   exists_file(QlfFile),
+	    time_file(QlfFile, QlfTime),
+	    time_file(PlFile, PlTime),
+	    QlfTime >= PlTime
+	->  load_files(QlfFile)
+	;   access_file(QlfFile, write)
+	->  qcompile(PlFile)
+	;   load_files(PlFile)
+	).
+
+
+		 /*******************************
+		 *     JUST IN TIME LOADING	*
+		 *******************************/
+
+:- multifile user:exception/3.
+
+user:exception(undefined_predicate, wordnet:Name/Arity, retry) :-
+	functor(Op, Name, Arity),
+	wn_op(Op),
+	load_op(Name).
+
+
+		 /*******************************
+		 *            MESSAGES		*
+		 *******************************/
+
+:- multifile prolog:message//1.
+
+prolog:message(wordnet(nodb)) -->
+    [ 'Cannot find WordNet data files.  Please set the environment'-[], nl,
+      'variable WNDB to point at the directory holding the WordNet files'-[]
+    ].
diff --git a/lib/swish/pack/wordnet/prolog/wn_portray.pl b/lib/swish/pack/wordnet/prolog/wn_portray.pl
new file mode 100644
index 0000000..24a9d83
--- /dev/null
+++ b/lib/swish/pack/wordnet/prolog/wn_portray.pl
@@ -0,0 +1,54 @@
+/*  Part of SWI-Prolog
+
+    Author:        Jan Wielemaker
+    E-mail:        J.Wielemaker@vu.nl
+    WWW:           http://www.swi-prolog.org
+    Copyright (c)  2017, VU University Amsterdam
+    All rights reserved.
+
+    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.
+
+    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS 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
+    COPYRIGHT OWNER 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.
+*/
+
+:- module(wn_portray, []).
+:- use_module(wn).
+
+/** <module> Portray Wordnet synset numbers
+
+By loading this file, WordNet synset numbers are printed in a more
+readable form.
+
+*/
+
+:- multifile user:portray/1.
+
+user:portray(SynSet) :-
+	integer(SynSet),
+	SynSet > 100000000,
+	SynSet < 500000000,
+	findall(Word, wn_s(SynSet, _, Word, _, _, _), Words),
+	Words \== [], !,
+	atomics_to_string(Words, ', ', SS),
+	format('~w (WN: ~w)', [SynSet, SS]).