Is it idiomatic to assert facts based on input data?

I’m trying to learn Prolog by using it for the Advent of Code challenges (adventofcode.com). These puzzles generally have a bunch of data you load in. Sometimes the puzzle is to just filter the data and count what remains. Other times, the data may describe machines that interact with each other to generate a solution.

I’m trying to parse the inputs and assert facts, then make rules that operate on those facts. This idea comes from the fact that I’ve been using a lot of datalog and rules engines in my day job recently. However, I’m finding it a little cumbersome to work with interactively in emacs because asserted facts are never reset. Also, it kind of feels like mutating global state. I’m wondering if I’m fighting against prolog in my approach.

Is there an idiomatic way to parse and process data in Prolog?
Is it common to assert facts based on input data or is that to be avoided?

Thanks,
Brian

For parsing DCG is my first sword of choice.

Also Regular Expressions can be done with SWI-Prolog.
regex
library(pcre)


Why would it be wrong? If you read

Data stored this way notably does not change on backtracking . Typically it is a bad idea to use any of the predicates in this section for realising global variables that can be assigned to. Typically, first consider representing data processed by your program as terms passed around as predicate arguments

then to quote Pablo Picasso

“Learn the rules like a pro, so you can break them like an artist.”

I use assert with library(persistency) as often as I would use SQL in another language. Then as noted

If you need to reason over multiple solutions to a goal, consider findall/3, aggregate/3 and related predicates.

In the following<=> is just giving an example when using SWI-Prolog versus more traditional programming languages.

Another way to think of it is that you keep the data in a data store (library(persistency) <=> SQL database) then you select the needed data (findall and such <=> SQL) and pass the data around as needed (accumulator <=> collection)


I keep a more extensive list of such here.


HTH

As @EricGT suggests, “it depends”. You can represent data in data structures such as lists, (compound) terms, dicts and derived types such as provided by library(assoc) and several others. You can also assert it into the database and use Prolog more like a relational DB. If you have data that is modified during search that relies on backtracking, the use of data structures is obviously the first choice. There still may be cases where the database is a better choice though. Note that you can have a “backtrackable assert” using

assert(Term, Ref), undo(erase(Ref)).

SWI-Prolog has some more tricks for using the database in a dynamic world. Consider thread-local predicates (thread_local/1). transactions (transaction/1) dynamic and monotonic tabling (should make you feel at home when coming from a Datalog world).

Representing the state of the world in a game in the database is probably fine. If Prolog needs to do planning that involves searching for a set of actions to change the world to some target state you may want some abstraction over the state that allows representing parts of the world state as backtrackable data structures. That is all possible.

2 Likes

I would suggest to keep your prolog pure as far as possible, without relying on DB, because this make easier to correct your logic.
Practically, you can use DCGs for both parse and state handling. About state handling, see for instance this particular solution to zebra puzzle:

solve :- solve(Sol, From), writeln(From), maplist(writeln, Sol).

solve(Sol, From) :-
    phrase( (from(1, norway)
        ,color(red) = from(england)
        ,color(GREEN, green), color(WHITE, white), {GREEN is WHITE-1}
        ,from(denmark) = drink(tea)
        ,smoke(Light, light), animal(Cat, cat), next_to(Light, Cat)
        ,color(Yellow, yellow), smoke(Yellow, cigar)
        ,from(germany) = smoke(waterpipe)
        ,drink(3, milk)
        ,drink(Water, water), next_to(Light, Water)
        ,animal(bird) = smoke(nofilter)
        ,from(sweden) = animal(dog)
        ,from(NORWAY, norway), color(BLUE, blue), next_to(NORWAY, BLUE)
        ,animal(HORSE, horse), next_to(HORSE, GREEN) % next_to(HORSE, Yellow)
        ,drink(beer) = smoke(menthol)
        ,color(green) = drink(coffee)
        ,animal(Fish, fish), from(Fish, From)
    ), [[1,_,_,_,_,_],
        [2,_,_,_,_,_],
        [3,_,_,_,_,_],
        [4,_,_,_,_,_],
        [5,_,_,_,_,_]
    ], Sol).

state(S), [A,B,C,D,E] --> [A,B,C,D,E], {member(S, [A,B,C,D,E])}.

color(A, B)  --> state([A,B,_,_,_,_]).
from(A, B)   --> state([A,_,B,_,_,_]).
animal(A, B) --> state([A,_,_,B,_,_]).
drink(A, B)  --> state([A,_,_,_,B,_]).
smoke(A, B)  --> state([A,_,_,_,_,B]).

X = Y --> {
    X=..[Fx|Ax], Y=..[Fy|Ay],
    Xs=..[Fx,S|Ax], Ys=..[Fy,S|Ay]
}, call(Xs), call(Ys).

next_to(X, Y) --> {1 is abs(X-Y)}.

Beware the correction

..., next_to(HORSE, GREEN) % next_to(HORSE, Yellow)

The code come from here, when debugging because of a missing solution, it’s ‘easy’ to locate the step just commenting out the rule in the phrase… of course, this would be the same using the more traditional member/2 based solution of the puzzle, where the state is explicilty inlined in every goal.

I followed this Markus Triska’ suggestion from ‘The Power of Prolog’, but when your state becomes too much complex, there is pack(edcg) you could check… it has a bit steep learning phase…

HTH

I did the advent of code with Prolog last year (up until I moved and lost momentum); my approach was typically to use DCGs to parse the input & operate on a list of terms (e.g. this or this), but I did assert facts for one or two problems; the way I would make this work well interactively would be to have the “solve” predicates use retractall/1 first to remove the facts from prior runs; see, e.g. here.

Thanks for the thoughts everyone. That gives me a lot of things to explore. I’ve discovered abolish/1 and that’s making using assertz/1 much easier.

@jamesnvc, It looks like that repo might be private, as I’m getting a 404.

What you describe sounds like the general approach I took last year (advent-of-code/2020 at master · bmaddy/advent-of-code · GitHub). I came to the conclusion it was non-idiomatic because the code seemed longer than I was expecting. Perhaps I should consider that approach again. Seeing how an experienced Prolog developer solved the problems last year would probably clear up all of my questions.

Oh oops, made it public, sorry about that

1 Like

If you use the database to keep the state (presumably with assert/1 and retract/1), then you could encounter the “singleton” problem. So, it’s probably a good idea to add something to uniquely identify the state; for example, PlayerID and GameID. (SWI-Prolog’s JITI should be able to handle this nicely)

1 Like

If you are asserting facts then retracting facts to change state as the solution proceeds then it might be a planner you need.

See: Prolog planning using retract and assert

It’s just to get back to a clean slate while I’m experimenting with code. I don’t have mutable state I need to mess with yet (I’m only on the first problem).

abolish/1 is a mistake. It not only removes the clauses, but also the attributes such as dynamic.
In some systems in pre-ISO-standard days it could be used to delete normal static predicates at runtime and replace them with something else. ISO dictates that abolish/1 only works on dynamic predicates. For this we have retractall/1, which preserves other predicate properties.

1 Like