^D not longer working after importing pac

swi prolog version: version 9.3.19-13-gc4848cb0b-DIRTY

normally this works:

$ swipl
reading ~/.swiplrc (FS)
Welcome to SWI-Prolog (threaded, 64 bits, version 9.3.19-13-gc4848cb0b-DIRTY)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

(ins)?- 

% halt

(halt by ^D)

But when I import pac, then I run into problems:


(ins)?- use_module( library( pac)).
true.

(ins)?-  % ^D here
ERROR: Unknown procedure: end_of_file/0 (DWIM could not correct goal)

Thanks in advance

How about to disable pac query expansion by disable_pac_query/0,
which is all what I could propose for now.

% swipl
Welcome to SWI-Prolog (threaded, 64 bits, version 9.3.19-18-gb55bb91c4)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit https://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

102 ?- use_module(library(pac)).
true.

?- disable_pac_query.
true.

?- ^D
% halt
% 

Probably it is related to the following codes about pac query expansion,
which I borrowed without knowing exactly what '$current_typein_module'(C) does.

user: expand_query(X, Y, Z, Z) :- user:chk_pac_query, !,
	'$current_typein_module'(C),
	pac:expand_query(C, X, Y).
user: expand_query(X, X, Z, Z).

Or bypass treating the end_of_file atom. If you hook into
the top-level, it could be that you see an end_of_file atom
during ^D. And something in your pac code causes the problem,

which could be avoided by a different end_of_file atom
treatment. Here is a test:

?- [user].
term_expansion(end_of_file, _) :-
    write('end_of_file hit.'),
    nl, fail.
^D
end_of_file hit.
% user://1 compiled 0.00 sec, 1 clauses
true.
?- 

After your comment, I have inserted a line for ‘end_of_file’ for halt/0.

expand_query(_, [], []).
expand_query(_, 'end_of_file', _) :- halt.
expand_query(M, M:[X|Y], M:[X|Y]).
expand_query(M, X, Y) :-
	once(expand_goal(X, M, Y, Z, [])),
	assert_in_user(Z).

In terminal, ^D works for halt. However, in Ediprolog mode in Emacs, ^D works like Delete one character forward. I think I should give up to control ^D due to my little knowledge. Thanks for letting me to learn that ^D means something like end_of_file.

It depends. On windows terminal you use ^Z to
generate a end of file into the input stream.
The predcate get_code/1 will return -1. The
predicate read_term/2 will return end_of_file.

The top-level uses read_term/2 I guess.
Expanding end_of_file to halt is not a good idea.
Because the interpretation of end_of_file is
context dependent. During [user] it means

that nor more clauses are consulted, just like here:

Disclaimer: I don’t know whether pac supports [user] ?

Wouldn’t this be better?

expand_query(_, end_of_file, end_of_file) :- !.

(I don’t know exactly what your expand_query/3 does; but I presume it’s just a transformation of the input, so you don’t want to execute a halt but instead want to leave end_of_file as-is.)

Thanks. It works for both terminal and emacs.

Agree.
One of purpose of expand_query is to run queries which use my macro like this (zip).

% ?- maplist(pred([X,Y,X-Y]), [a,b],[1,2], Z).
%@ Z = [a-1, b-2].

Sometime it is convenient particularly in ediprolog mode when I’m in a hurry to run queries for testing, though I think one should not invent private macros so freely.

There are more cases where an EOF signal
is interpreted. For example during a debugger break:

?- trace, a=b.
   Call: (13) a=b ? break
% Break level 1
[1]  ?- a=b.
false.

[1]  ?- ^D

% Exit break level 1
   Call: (13) a=b ? 

One would need to check the SWI-Prolog system
and Emacs integration souce code how EOF is
exactly detected. Besides get_code/1 and read_term/2

special values, some Prolog systems have also
stream inquiry built-ins such as at_end_of_stream/1.
But I never implemented it, since it should work the

same as this bootstrapping:

/* Is this bootstrapping supposed to work always? */
at_end_of_stream(S) :- peek_code(S, -1).

Its a little bit a can of worms especially in connection with
teletype terminal streams (tty), since as the example above
shows with the break, we expect that a terminal smoothly

allows to emit multiple ^D each ^D meaning that a section
of text has been completed, not meaning halt/0 in itself.
Inside Emacs ^D probably is never needed since Emacs

has a concept of buffer, and there are other means to
designate sections of text.

Edit 06.02.2025
But since EOF signal is mapped to the special value end_of_file
by read_term/2 , this is very handy. When neither ^D or ^Z
work in the terminal at hand, you can still use the atom:

?- [user].
|: p(a).
|: p(b).
|: end_of_file.

% user://1 compiled 0.02 sec, 2 clauses
true.

?- p(X).
X = a ;
X = b.

The atom end_of_file works also inside a consulted file, across
many Prolog systems actually. But consult behaviour either via
[user] or from a file is not covered by the ISO core standard.