Segfault via cplint / pita / dt_solve in version swipl: 8.4.1 cplint: 4.5.0

The following code crashes:

:- use_module(library(pita)).

:- pita.

:- begin_lpad.

? :: vars2([0,0,0]).
% ? :: vars2([1,0,0]).
% ? :: vars2([0,1,0]).
% ? :: vars2([1,1,0]).
% ? :: vars2([0,0,1]).
% ? :: vars2([1,0,1]).
% ? :: vars2([0,1,1]).
? :: vars2([1,1,1]).

? :: v1.

vars(L) :- vars2(L), L=[V1,V2,V3], prob( v1, V1).

cnf :- vars(L).

utility( cnf, 1).

:- end_lpad.
(ins)$ swipl -s 00B_v2_probability_vs_sat_crash.pl -g 'dt_solve(A,B)'
reading ~/.swiplrc (FS)
Warning: /home/ox/dev-git/swi-prolog/cplint/003_strategy/00B_v2_probability_vs_sat_crash.pl:19:
Warning:    Singleton variables: [V2,V3]
Warning: /home/ox/dev-git/swi-prolog/cplint/003_strategy/00B_v2_probability_vs_sat_crash.pl:21:
Warning:    Singleton variables: [L]

SWI-Prolog [thread 1 (main) at Fri Apr  1 23:31:45 2022]: received fatal signal 11 (segv)
C-stack trace labeled "crash":
  [0] save_backtrace() at :? [0x7f9ac2ea7175]
  [1] print_c_backtrace() at :? [0x7f9ac2ea728e]
  [2] sigCrashHandler() at :? [0x7f9ac2ea7395]
  [3] killpg() at ??:? [0x7f9ac2b9c840]
  [4] Prob() at /home/mlunife/.local/share/swi-prolog/pack/bddem/bddem.c:1174 [0x7f9ac1ad1368]
  [5] ret_prob() at /home/mlunife/.local/share/swi-prolog/pack/bddem/bddem.c:731 [0x7f9ac1ad31c2]
  [6] PL_next_solution___LD() at :? [0x7f9ac2db9451]
  [7] query_loop() at :? [0x7f9ac2e0381c]
  [8] prologToplevel() at :? [0x7f9ac2e0401b]
  [9] PL_initialise() at ??:? [0x7f9ac2e47084]
  [10] swipl(+0x10a6) [0x563daa3e10a6]
  [11] __libc_start_main() at /build/glibc-vjB4T1/glibc-2.28/csu/../csu/libc-start.c:342 [0x7f9ac2b8909b]
  [12] swipl(+0x10fa) [0x563daa3e10fa]
Prolog stack:
  [40] bddem:ret_prob/3 [PC=1 in supervisor]
  [37] $bags:findall_loop/4 [PC=5 in clause 1]
  [36] system:setup_call_catcher_cleanup/4 [PC=5 in clause 1]
  [32] pita:prob_meta/2 [PC=188 in clause 1]
  [31] vars/3 [PC=48 in clause 1]
  [30] system:call/1 [PC=3 in clause 1]
  [29] system:reset/3 [PC=2 in clause 1]
  [28] $tabling:delim/4 [PC=8 in clause 1]
  [27] $tabling:moded_activate/3 [PC=11 in clause 1]
  [26] $tabling:moded_run_leader/5 [PC=16 in clause 1]
  [25] system:setup_call_catcher_cleanup/4 [PC=5 in clause 1]
  [24] $tabling:start_moded_tabling_2/7 [PC=90 in clause 1]
  [21] cnf/2 [PC=12 in clause 1]
  [20] system:call/1 [PC=3 in clause 1]
  [19] system:reset/3 [PC=2 in clause 1]
  [18] $tabling:delim/4 [PC=8 in clause 1]
  [17] $tabling:moded_activate/3 [PC=11 in clause 1]
  [16] $tabling:moded_run_leader/5 [PC=16 in clause 1]
  [15] system:setup_call_catcher_cleanup/4 [PC=5 in clause 1]
  [14] $tabling:start_moded_tabling_2/7 [PC=90 in clause 1]
  [12] $wrap$cnf/2 [PC=48 in clause 1]
  [11] pita:get_node/3 [PC=65 in clause 2]
  [10] pita:generate_solution/6 [PC=27 in clause 2]
  [9] pita:dt_solve/2 [PC=48 in clause 1]
  [8] system:catch/3 [PC=2 in clause 1]
Running on_halt hooks with status 139
Killing 8243 with default signal handlers
Speicherzugriffsfehler

Thanks in advance

Addendum: I upgraded the last version but the version number did not change. The bug is still remaining.

Thanks for reporting it. I will try to look into it.

1 Like