So basically I am trying to simulate asm code using Prolog.
With the help of #mbratch , I know it is straightforward and easy to use dynamic facts to simulate instructions like
add eax, 1
mov eax, 1
in this way:
:- dynamic(register/2). % Fill in as needed
register(eax, 0).
....
add(Reg, Value) :-
( retract(register(Reg, OldValue))
-> NewValue is OldValue + Value
),
assertz(register(Reg, NewValue)).
But the problem is that how to simulate the stack in a similar way...?
Originally I wrote some quite FP style code like this:
nth_member(1, [M|_], M).
nth_member(N, [_|T], M) :- N>1, N1 is N - 1, nth_member(N1, T, M).
.....
% push ebp
ESP is ESP - 1, nth_member(ESP, STACK, EBP),
....
But the problem is I don't know how to rewrite this code in a dynamic facts style...
Could anyone give me some help..? Thank you!
I'd like to reinforce the point #Boris made: do not use dynamic predicates.
By far the cleanest solution is to use state variables to carry around the current state of the simulated machine. Because of Prolog's single-assignment characteristic, you will always have pairs of these: state before and state after. For registers and memory, the state is best represented as a table which maps register names (or memory addresses) to values. A stack can simply be kept as a list. For example:
main :-
Stack0 = [],
Regs0 = [eax-0, ebx-0, ecx-0, edx-0],
Code = [movi(3,eax), add(eax,7), push(eax), pop(ecx)],
sim_code(Code, Regs0, RegsN, Stack0, StackN),
write(RegsN), nl, write(StackN), nl.
% simulate a sequence of instructions
sim_code([], Regs, Regs, Stack, Stack).
sim_code([Instr|Instrs], Regs0, RegsN, Stack0, StackN) :-
sim_instr(Instr, Regs0, Regs1, Stack0, Stack1),
sim_code(Instrs, Regs1, RegsN, Stack1, StackN).
% simulate one instruction
sim_instr(movi(Value,Reg), Regs0, RegsN, Stack, Stack) :-
update(Regs0, Reg, _Old, Value, RegsN).
sim_instr(add(Reg,Value), Regs0, RegsN, Stack, Stack) :-
update(Regs0, Reg, Old, New, RegsN),
New is Old+Value.
sim_instr(push(Reg), Regs, Regs, Stack, [Val|Stack]) :-
lookup(Regs, Reg, Val).
sim_instr(pop(Reg), Regs0, RegsN, [Val|Stack], Stack) :-
update(Regs0, Reg, _Old, Val, RegsN).
%sim_instr(etc, ...).
% simple key-value table (replace with more efficient library predicates)
lookup([K-V|KVs], Key, Val) :-
( Key==K -> Val=V ; lookup(KVs, Key, Val) ).
update([K-V|KVs], Key, Old, New, KVs1) :-
( Key==K ->
Old = V, KVs1 = [K-New|KVs]
;
KVs1 = [K-V|KVs2],
update(KVs, Key, Old, New, KVs2)
).
In practice, you should replace my simple table implementation (lookup/3, update/5) with an efficient hash or tree-based version. These are not standardised, but you can usually find one among the libraries that come with your Prolog system.
The Prolog canon says, don't use dynamic facts for state unless you have a really good reason. In other words, if you want to model a stack, maintain it as a term that you mutate and pass to the next step of a recursive predicate that takes as arguments the state. For example (very simplified),
step(Current_stack, Final_stack) :-
read_next_instruction(Instruction/*, whatever other arguments you need */),
apply_instruction(Current_stack, Instruction, New_stack),
step(New_stack, Final_stack).
The second argument, Final_stack, is there if you want to have the final stack after getting through all instructions in the code you are simulating. It will probably be a free variable at the beginning of the simulation, or, if you want to validate, the expected final state.
The stack itself would be either a list (if you only need the top of the stack), or a more complex, possibly nested term. You most probably would want to maintain all registers in this way too (as shown in my other answer).
There is another option, using proper mutable global variables. Depending on the Prolog implementation you use, this will involve different built-ins. For SWI-Prolog, look here; for GNU-Prolog, here. Other implementations will probably have predicates along the same lines as well.
The main point here is that using assert and retract for maintaining state that changes frequently makes your program very difficult to understand, and very inefficient. The "pure" Prolog solution is the first suggestion; using global variables can be more efficient in some cases.
PS:
As a full example of how to use a stack, see this answer to a question about a stack-based calculator (shameless self-promotion):
Postfix expression list evaluation
And to expand on the "don't use dynamic predicates", they definitely have their use. A good example of when this is a good solution is if you are implementing a relational database. Then, your tables are implemented as facts, with one clause per column:
name_age('Bob', 20).
name_age('Jane', 23).
% etc
name_occupation('Bob', student).
name_occupation('Jane', teacher).
% etc
Here, you can use asserts to add new rows to your tables, or retracts to remove rows. The main point is that you will probably query your database much more often that you will alter it. You will also profit from Prolog's efficient lookup of facts, plus you can write queries in a more natural way.
Related
This exercise asked me to find the best combination of three products, given the prices and specific combinations to avoid. The textbook employs assertz and retractall to emulate a state variable.
price(a1, 1900).
price(a2, 750).
price(a3, 900).
price(b1, 300).
price(b2, 500).
price(b3, 450).
price(b4, 600).
price(c1, 700).
price(c2, 850).
incompatible(a2, c1).
incompatible(b2, c2).
incompatible(b3, c2).
incompatible(a2, b4).
incompatible(a1, b3).
incompatible(a3, b3).
:- dynamic bound/1.
bound(5000).
solution(A, B, C, P) :-
member(A, [a1, a2, a3]),
price(A, PA),
member(B, [b1, b2, b3, b4]),
\+ incompatible(A, B),
price(B, PB),
P0 is PA + PB,
bound(Bound),
write('Current bound: '), writeln(Bound),
P0 =< Bound,
member(C, [c1, c2]),
\+ incompatible(A, C),
\+ incompatible(B, C),
price(C, PC),
P is PA + PB + PC,
P =< Bound,
retractall(bound(_)),
assertz(bound(P)).
Is it possible to use branch and bound in Prolog without resorting to dynamic predicates?
Is there a consensus on state variables in Prolog?
Is there a way to restrict the scope of a state variable (or whatever the proxy would be) to a single rule?
The biggest problem with this code is that it is not re-entrant. It implicitly assumes that at any point in time there is exactly one instance of searching. But if some part inside wants to use a similar search all by themselves, no warning no error prevents this from happening.
There is not much consensus on how the precise mechanism should look like, existing systems all differ. To understand this, look at the implementation of findall/3 or call_nth/2 where there are specific solutions for SICStus, SWI, and Eclipse. Precisely this mechanism would be needed here too.
But also consider to make this search more generic. Presumably the textbook you are referring to was written prior to the general acceptance of call/N.
Is it possible to use branch and bound in Prolog without resorting to dynamic predicates?
Yes, you just hand the bounds around as additional arguments across recursive calls (as is done in functional programming). IMHO, this is actually a cleaner solutions than asserting into the Prolog database. The trick of changing the database and then performing a redo is confusing, as it's not the same program that is being redone. It's a "neat trick" to put into a textbook though.
Is there a consensus on state variables in Prolog?
Just hand them around as arguments. If need be, you can use Global Variables if supported. See also: Database in SWI-Prolog. To keep argument lists small-ish, you may want to consider using associative arrays (SWI-Prolog dicts, library(assoc)) as "argument bundle". But as usual, this has implications on efficiency.
Is there a way to restrict the scope of a state variable (or whatever the proxy would be) to a single rule?
Evidently, arguments are local, but there is, sadly, nothing beyond. I would like to have "local visibility scopes", especially for predicates so as to unequivocally associate "helper predicates" to their "parent predicate" but "modules" (implemented variously) is the best we have. (This is not made better by a tradition which finds module sizes of enormous size acceptable, something for which I would berate the intern in no uncertain terms, same as writing an object of several thousand lines, but I digress)
Your solution is not always using the proper Bound upon backtracking. The problem is that the variable gets bound too soon and then even if the fact gets updated with assertz/retract the variable will still be bound to the previous value. You can see the effects by letting the toplevel backtrack through all the solutions. There are some solutions intersped that have higher cost than a previous one.
Here goes an iterative solution customized to your problem, though you could probably make it more general by using call/N instead of the fixed calls to price/2 and any_incompatible/2
solution2(Bound, Best):-
branch_and_bound([[a1,a2,a3],[b1,b2,b3,b4],[c1,c2]], Bound, [], Best).
branch_and_bound([[]|_], _, Best, Best).
branch_and_bound([[Item|Layer]|Layers], Bound, CurrentBest, Best):-
price(Item, ItemPrice),
( ItemPrice >= Bound
-> Bound1-CurrentBest1=Bound-CurrentBest
; branch_and_bound(Layers, Bound, Bound1, current(ItemPrice, [Item]), CurrentBest, CurrentBest1)
),
branch_and_bound([Layer|Layers], Bound1, CurrentBest1, Best).
branch_and_bound([], Bound, CurrentPrice, current(CurrentPrice, Items), PreviousBest, [best(CurrentPrice, RItems)|OtherBest]):-
reverse(Items, RItems),
( CurrentPrice==Bound -> OtherBest=PreviousBest ; OtherBest=[] ).
branch_and_bound([[]|_], Bound, Bound, _, Best, Best).
branch_and_bound([[Item|Layer]|Layers], Bound, Bound2, current(CurrentPrice, Items), CurrentBest, Best):-
price(Item, ItemPrice),
NewPrice is CurrentPrice + ItemPrice,
(
( NewPrice > Bound ; any_incompatible(Items, Item) )
-> Bound1-CurrentBest1=Bound-CurrentBest
; branch_and_bound(Layers, Bound, Bound1, current(NewPrice, [Item|Items]), CurrentBest, CurrentBest1)
),
branch_and_bound([Layer|Layers], Bound1, Bound2, current(CurrentPrice, Items), CurrentBest1, Best).
any_incompatible([OneItem|Items], Item):-
incompatible(OneItem, Item) -> true ; any_incompatible(Items, Item).
It will list all the best solutions, trimming the search space with the current Bound defined by the currently found best solution.
Sample run:
?- solution2(5000, Best).
Best = [best(1900, [a3, b1, c1]), best(1900, [a2, b1, c2])].
I am currently writing a solver for a floor planning problem in Prolog and have some issues with the labeling part.
The current problem is my constraints are posted but when I launch the labeling, it takes forever to find a solution. I would like to bring in some heuristics.
My question is, how do I manually label my variables ? I am afraid that after defining a clpfd variable like this :
X in Xinf..Xsup
and constraining it, If I do something like :
fd_sup(X, Xmax),
X = Xmax,
...
in my custom label, I won't be using the backtrack ability of Prolog to test the other values of X's domain. Am I wrong ?
Also, is there a smarter way to label my variables than writing custom labeling procedures ? My idea of heuristics would consist in trying extrema of a variable domain alternatively (like max(X), min(X), max(X-1), min(X-1) etc...)
Hope you can help me :)
It is not difficult to write a custom labeling procedure, and with most real problems you will eventually need one anyway in order to incorporate problem-specific heuristics.
The two main components of a labeling procedure are
variable selection: from all the remaining (i.e. not yet instantiated) problem variables, pick one to consider next.
value selection or branching: explore, via backtracking, two or more alternative sub-problems by reducing the chosen variable's domain in (usually) complementary ways.
Using this scheme, the default labeling procedure can be written as
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
label(Xs1)
;
true % done, no variables left
).
select_variable(X, [X|Xs], Xs). % 'leftmost' strategy
branch(X) :- indomain(X).
You can now redefine select_variable/3 to implement techniques such as "first-fail", and redefine branch/1 to try domain values in different orders. As long as you make sure that branch/1 enumerates all of X's domain values on backtracking, your search remains complete.
Sometimes you want to try just one domain value first (say, one suggested by a heuristics), but, if it is no good, not commit to another value immediately.
Let's say that, as in your example, you want to try the maximum domain value first. You could write this as
branch(X) :-
fd_sup(X, Xmax),
(
X = Xmax % try the maximum
;
X #\= Xmax % otherwise exclude the maximum
).
Because the two cases are complementary and cover all possible values for X, your search is still complete. However, because of the second alternative, branch/1 can now succeed with an uninstantiated X, which means you must make sure in the labeling procedure that you don't lose this variable from your list. One possibility would be:
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
( var(X) -> append(Xs1, [X], Xs2) ; Xs2=Xs1 ),
label(Xs2)
;
true % done, no variables left
).
First, always try built-in heuristics. ff is often a good strategy.
For custom labeling strategies, it is often easiest to first convert the domain to a list, then reorder the list, and then simply use member/2 to assign the values of the domain using the new order.
A good building black is dom_integers/2, relating a finite CLP(FD) domain to a list of integers:
:- use_module(library(clpfd)).
dom_integers(D, Is) :- phrase(dom_integers_(D), Is).
dom_integers_(I) --> { integer(I) }, [I].
dom_integers_(L..U) --> { numlist(L, U, Is) }, Is.
dom_integers_(D1\/D2) --> dom_integers_(D1), dom_integers_(D2).
Your specific strategy is easily expressed on a list of such ordered integers, relating these integers to a second list where the values occur in the order you describe:
outside_in([]) --> [].
outside_in([I]) --> [I].
outside_in([First|Rest0]) --> [First,Last],
{ append(Rest, [Last], Rest0) },
outside_in(Rest).
Sample query and result:
?- phrase(outside_in([1,2,3,4]), Is).
Is = [1, 4, 2, 3] ;
false.
Combining this with fd_dom/2 and dom_integers/2, we get (bindings for variables other than X omitted):
?- X in 10..20,
fd_dom(X, Dom),
dom_integers(Dom, Is0),
phrase(outside_in(Is0), Is),
member(X, Is).
X = 10 ;
X = 20 ;
X = 11 ;
X = 19 ;
X = 12 ;
X = 18 ;
etc.
Nondeterminism is preserved by member/2.
Make sure to distinguish labeling strategies from additional propagation. These two aspects are currently a bit mixed in your question.
In SWI-Prolog, there is a predicate called clpfd:contracting/1. It does what you describe: It tries values from the domain boundaries, and removes values that can be seen as inconsistent, i.e., for which it is known that no solution exists.
Therefore, if you have a list of variables Vs, you can try: clpfd:contracting(Vs), and see if this helps.
Note that this can also significantly slow down the search, though on the other hand, also help significantly to reduce the search space before even trying any labeling!
To complement the other answers (one contrasting labeling and propagation, one showing a dedicated labeling method), I now tackle a further very important aspect of this question:
Very often, when beginners complain about the speed of their code, it turns out that their code in fact doesn't even terminate! More efficiency would not help in that case.
Hence, this answer points you towards first ensuring actual termination of your relation.
The best way to ensure termination of CLP(FD) programs is to separate them into 2 parts:
the first, called the core relation, simply posts all constraints.
the second uses labeling/2 to perform the actual search.
Have you done this in your program? If not, please do. When this is done, make sure that the core relation, say solution/2 (where the arguments are: a term denoting the task instance, and the list of variables to be labeled) terminates universally by querying:
?- solution(Instance, Vs), false.
If this terminates, then the following also terminates:
?- solution(Instance, Vs), label(Vs), false.
Of course, in larger tasks, you have no chance to actually witness the termination of the latter query, but a good chance to witness the termination of the first query, because setting up the constraints is often much faster than actually obtaining even a a single solution.
Therefore, test whether your core relation terminates!
This follows up on this previous answer by #mat.
If you have got some more CPU cycles to burn, try shave_zs/1 as defined in this previous answer.
shave_zs/1 kind of works like the auxiliary library predicate clpfd:contracting/1. Unlike contracting/1, however, all values are "up for grabs"—not just the ones at the boundary. YMMV!
I am trying to write a solution for AdventCode day 6 in Prolog. (http://adventofcode.com/day/6)
Previously I wrote a solution that dynamically created and replaced predicates, to keep track of the lights. Unsurprisingly, it's rather slow, so I decided to try and write it using a more "functional" style; i.e. create a list containing all the lights, then manipulate that list.
I am trying to construct the initial list, which would consist of a million elements, each a term light(X, Y, Status). I figured I'd start with a list [light(0, 0, off)], then prepend new terms to it. To do this, I look at the first element of the list, then determine what the next element should be, then prepend that. Repeat.
I have a predicate next_light/2 which takes a light and determines what the next light (to be prepended) should be. If no more lights need to be added, it returns done:
next_light(light(X, Y, _), NextLight) :-
X < 999,
NextX is X + 1,
NextLight = light(NextX, Y, off).
next_light(light(999, Y, _), NextLight) :-
Y < 999,
NextY is Y + 1,
NextLight = light(0, NextY, off).
next_light(light(999, 999, _), done).
Then I attempt to construct the list with this code:
init_lights(Lights) :-
gen_lights([light(0, 0, off)], Lights).
gen_lights(Lights, AllLights) :-
[Light|_] = Lights,
next_light(Light, NextLight),
add_light(Lights, NextLight, AllLights).
add_light(Lights, done, Lights).
add_light(Lights, NextLight, AllLights) :-
gen_lights([NextLight|Lights], AllLights).
However, when I run init_lights(L) in SWI-Prolog, I get "ERROR: Out of local stack". So there's a stack overflow, but when I look at the code, it looks tail recursive to me. add_light and gen_lights are mutually recursive; not sure if that is a problem.
I tried inspecting the calls with the debugger, but apparently SWI-Prolog turns off tail call optimization when using trace, so that was no help.
(For the record, when I changed the code to use 3 rather than 999 as the maximum coordinate, init_lights(L) seemed to produce the correct list, and didn't hang or cause a stack overflow.)
I'm probably overlooking something, but I am not seeing it. Any tips welcome! ^_^
You are very close to the solution: Your clauses are tail recursive, but tail recursion optimisation only helps if the code is deterministic! In your code, next_light/2 leaves choice-points because the compiler cannot tell which cases are mutually exclusive, so the frames cannot be reclaimed after the tail recursive call.
You can improve the determinism in several ways. The ugliest and most error-prone way is to add !/0 in some strategic places: Be careful with this, because this will destroy many nice declarative properties of your code.
Slightly better, but also almost always declaratively wrong, is to use features like if-then-else.
A safer and more general way is to use features like zcompare/3 with clpfd constraints.
I often end up writing code in Prolog which involves some arithmetic calculation (or state information important throughout the program), by means of first obtaining the value stored in a predicate, then recalculating the value and finally storing the value using retractall and assert because in Prolog we cannot assign values to variable twice using is (thus making almost every variable that needs modification, global). I have come to know that this is not a good practice in Prolog. In this regard I would like to ask:
Why is it a bad practice in Prolog (though i myself don't like to go through the above mentioned steps just to have have a kind of flexible (modifiable) variable)?
What are some general ways to avoid this practice? Small examples will be greatly appreciated.
P.S. I just started learning Prolog. I do have programming experience in languages like C.
Edited for further clarification
A bad example (in win-prolog) of what I want to say is given below:
:- dynamic(value/1).
:- assert(value(0)).
adds :-
value(X),
NewX is X + 4,
retractall(value(_)),
assert(value(NewX)).
mults :-
value(Y),
NewY is Y * 2,
retractall(value(_)),
assert(value(NewY)).
start :-
retractall(value(_)),
assert(value(3)),
adds,
mults,
value(Q),
write(Q).
Then we can query like:
?- start.
Here, it is very trivial, but in real program and application, the above shown method of global variable becomes unavoidable. Sometimes the list given above like assert(value(0))... grows very long with many more assert predicates for defining more variables. This is done to make communication of the values between different functions possible and to store states of variables during the runtime of program.
Finally, I'd like to know one more thing:
When does the practice mentioned above become unavoidable in spite of various solutions suggested by you to avoid it?
The general way to avoid this is to think in terms of relations between states of your computations: You use one argument to hold the state that is relevant to your program before a calculation, and a second argument that describes the state after some calculation. For example, to describe a sequence of arithmetic operations on a value V0, you can use:
state0_state(V0, V) :-
operation1_result(V0, V1),
operation2_result(V1, V2),
operation3_result(V2, V).
Notice how the state (in your case: the arithmetic value) is threaded through the predicates. The naming convention V0 -> V1 -> ... -> V scales easily to any number of operations and helps to keep in mind that V0 is the initial value, and V is the value after the various operations have been applied. Each predicate that needs to access or modify the state will have an argument that allows you to pass it the state.
A huge advantage of threading the state through like this is that you can easily reason about each operation in isolation: You can test it, debug it, analyze it with other tools etc., without having to set up any implicit global state. As another huge benefit, you can then use your programs in more directions provided you are using sufficiently general predicates. For example, you can ask: Which initial values lead to a given outcome?
?- state0_state(V0, given_outcome).
This is of course not readily possible when using the imperative style. You should therefore use constraints instead of is/2, because is/2 only works in one direction. Constraints are much easier to use and a more general modern alternative to low-level arithmetic.
The dynamic database is also slower than threading states through in variables, because it performs indexing etc. on each assertz/1.
1 - it's bad practice because destroys the declarative model that (pure) Prolog programs exhibit.
Then the programmer must think in procedural terms, and the procedural model of Prolog is rather complicate and difficult to follow.
Specifically, we must be able to decide about the validity of asserted knowledge while the programs backtracks, i.e. follow alternative paths to those already tried, that (maybe) caused the assertions.
2 - We need additional variables to keep the state. A practical, maybe not very intuitive way, is using grammar rules (a DCG) instead of plain predicates. Grammar rules are translated adding two list arguments, normally hidden, and we can use those arguments to pass around the state implicitly, and reference/change it only where needed.
A really interesting introduction is here: DCGs in Prolog by Markus Triska. Look for Implicitly passing states around: you'll find this enlighting small example:
num_leaves(nil), [N1] --> [N0], { N1 is N0 + 1 }.
num_leaves(node(_,Left,Right)) -->
num_leaves(Left),
num_leaves(Right).
More generally, and for further practical examples, see Thinking in States, from the same author.
edit: generally, assert/retract are required only if you need to change the database, or keep track of computation result along backtracking. A simple example from my (very) old Prolog interpreter:
findall_p(X,G,_):-
asserta(found('$mark')),
call(G),
asserta(found(X)),
fail.
findall_p(_,_,N) :-
collect_found([],N),
!.
collect_found(S,L) :-
getnext(X),
!,
collect_found([X|S],L).
collect_found(L,L).
getnext(X) :-
retract(found(X)),
!,
X \= '$mark'.
findall/3 can be seen as the basic all solutions predicate. That code should be the very same from Clockins-Mellish textbook - Programming in Prolog. I used it while testing the 'real' findall/3 I implemented. You can see that it's not 'reentrant', because of the '$mark' aliased.
Let's assume, that I have a simple program in Prolog, which is searching through a certain state space:
search(State, State) :-
is_solution(State).
search(State, Solution) :-
generate(State, NewState),
search(NewState, Solution).
And I know that:
generate(State, NewState) is producing at least one NewState for any given State
the whole states space is finite
I want to modify the search predicate to ensure that it always manages to check in a finite time. So I write something like:
search(State, Solution) :-
empty_memory(EmptyMem),
add(State, EmptyMem, Memory),
search(State, Memory, Solution).
search(State, _, State) :-
is_solution(State).
search(State, Memory, Solution) :-
generate(State, NewState),
\+ exist(NewState, Memory),
add(NewState, Memory, NewMemory),
search(NewState, NewMemory, Solution).
which is working, but it's losing computed states during backtracking, so now I have a search tree with maximum height of space size.
Is it any way to propagate a state during the backtracking without losing any computed information? I want to have a whole search tree with O(space_size) nodes. Is it possible?
EDIT:
It seems that I should use assert/[1,2] in order to dynamically create new clauses which will serve as a global memory.
In SICStus Prolog, you can use the blackboard to store information across backtracks: see Blackboard Primitives in the manual. Use bb_put(Key, Value) to store something on the blackboard, and bb_get(Key, Value) to retrieve it. Note that the bloackboard is defined per module.
The most clean solution will likely be to use a Prolog compiler that supports tabling like B-Prolog, Ciao, XSB, or YAP. In this case, you would simply declare the generate/2 predicate as tabled.
Instead of using assert, why not generate all possible states with findall(N, generate(S,N),ALL). This will eliminate the need for backtracking and will explicate the search space tree, which then could be preorder-traversed while passing along the visited-so-far states as additional argument.