-
The following is a minimal example of part of the Advent of Code 2024 Day 2, part 1 exercise: :- use_module(library(reif)).
:- use_module(library(clpz)).
:- use_module(library(lists)).
safe_reports_count(Reports, Count) :-
partition(safe_report, Reports, SafeReports, _),
length(SafeReports, Count).
safe_report(Report) :- safe_report_(Report, _).
safe_report_([_Level], _Direction).
safe_report_([L1, L2 | Rest], increasing) :-
L1 #< L2,
Difference in 1..3,
Difference #= L2 - L1,
safe_report_([L2 | Rest], increasing).
safe_report_([L1, L2 | Rest], decreasing) :-
L1 #> L2,
Difference #= L1 - L2,
Difference in 1..3,
safe_report_([L2 | Rest], decreasing).
%% Elements of 'List' are partitioned into 'Included' when they match 'Pred'
% and into 'Excluded' otherwise.
%
% NOTE: Not nicely relational
% Would be nicer to use `tfilter`
partition(Pred, List, Included, Excluded) :-
partition_(List, Pred, Included, Excluded).
partition_([], _, [], []).
partition_([H|T], Pred, Incl, Excl) :-
( call(Pred, H)
-> Incl = [H|I],
partition_(T, Pred, I, Excl)
; Excl = [H|E],
partition_(T, Pred, Incl, E)
). ?- safe_reports_count([[7,6,4,2,1], [1,2,7,8,9], [9,7,6,2,1], [1,3,2,4,5], [8,6,4,4,1], [1,3,6,7,9]], Count).
Count = 2. This code works and gives the right answer for the posed question, but it is not as relational as I would like. Specifically, I don't like using My question: How do you create a reified version of a predicate like |
Beta Was this translation helpful? Give feedback.
Replies: 2 comments 3 replies
-
It's a bit tricky given the way it's written, but I can help with some low level intuition that perhaps you can extrapolate to the rest. Let's take this one: safe_report_([L1, L2 | Rest], increasing) :-
L1 #< L2,
Difference in 1..3,
Difference #= L2 - L1,
safe_report_([L2 | Rest], increasing). could be written as something like: safe_report_t([_Level], _Direction, true).
safe_report_t([L1, L2 | Rest], increasing, T) :-
Difference in 1..3,
if_((L1 #< L2, Difference #= L2 - L1),
safe_report_t([L2 | Rest], increasing, T),
T=False). This is now a if_(safe_report_t(Stuff, Direction),
This,
That) The trick is that there are a handful of
|
Beta Was this translation helpful? Give feedback.
-
See Section 7:
There are a couple of reasons for that. The first is that it is not clear what kind of reification is intended. In the most extreme interpretation it could mean the same as constructive negation. In that case, every query, really every query that fails in your original program should produce the reified truth value But before looking at your example, let's rewrite it a bit such that the subsequent transformation becomes easier.
Key is
This sanity check helps us to ensure that we have actually implemented a reifying predicate. Note however that under the right circumstances we might even get here answers that do not contain solutions. In that case, an additional
|
Beta Was this translation helpful? Give feedback.
See Section 7:
There are a couple of reasons for that. The first is that it is not clear what kind of reification is intended. In the most extreme interpretation it could mean the same as constructive negation. In that case, every query, really every query that fails in your original program should produce the reified truth value
false
. But in many situations that is not what we expect. As examplesmemberd_t/3
andtreememberd_t/3
is given. See the discussion there.But before looking at your example, let's rewrite it a bit such that the subsequent transformation becomes easier.