Prolog "sequence"
Admin User, created Mar 21. 2025
/**
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
:- ensure_loaded(library(compat)).
:- ensure_loaded(library(lists)).
:- ensure_loaded(library(util/hash)).
/**
* offset(C, G):
* The predicate succeeds whenever the goal G succeeds, except
* the first C solutions are supressed.
*/
% offset(+Integer, +Goal)
offset(C, Goal) :-
sys_call_nth(Goal, N),
N > C.
/**
* limit(C, G):
* The predicate succeeds whenever the goal G succeeds, but limits
* the number of solutions to C.
*/
% limit(+Integer, +Goal)
limit(C, Goal) :-
C > 0,
sys_call_nth(Goal, N),
(N < C -> true; !).
/**
* call_nth(G, C):
* The predicate succeeds whenever G succeeds and unifies C with
* the numbering of the successes.
*/
% call_nth(+Goal, -Integer)
call_nth(Goal, C) :- var(C), !,
sys_call_nth(Goal, N),
C = N.
call_nth(Goal, C) :-
C > 0,
sys_call_nth(Goal, N),
(C =:= N -> !; fail).
% sys_call_nth(+Goal, -Integer)
sys_call_nth(Goal, N) :-
Holder = v(_),
change_arg(1, Holder, 0),
Goal,
arg(1, Holder, M),
N is M+1,
change_arg(1, Holder, N).
/**
* distinct(G):
* The predicate succeeds eagerly with first solutions of G.
*/
% distinct(+Goal)
distinct(Goal) :-
term_variables(Goal, Key),
hash_new(Hash),
Goal,
sys_distinct(Hash, Key).
/**
* firstof(T, Q):
* The predicate succeeds eagerly with first solutions of T in Q.
*/
firstof(Template, Quant) :-
free_variables(Template^Quant, Key, Goal),
hash_new(Hash),
Goal,
sys_distinct(Hash, Key).
% sys_distinct(+Hash, +Term)
sys_distinct(Hash, Key) :-
numbervars(Key, 0, _),
sys_distinct_not(Hash, Key), !,
fail.
sys_distinct(_, _).
% sys_distinct_not(+Hash, +Term)
sys_distinct_not(Hash, Key) :-
hash_current(Hash, Key, _), !.
sys_distinct_not(Hash, Key) :-
copy_term(Key, Key2),
hash_add(Hash, Key2, true), fail.