/* Part of SWI-Prolog Author: Lars Buitinck E-mail: larsmans@gmail.com WWW: http://www.swi-prolog.org Copyright (C): 2010-2015, Lars Buitinck This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this library; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA As a special exception, if you link this library with other files, compiled with a Free Software compiler, to produce an executable, this library does not by itself cause the resulting executable to be covered by the GNU General Public License. This exception does not however invalidate any other reasons why the executable file might be covered by the GNU General Public License. */ :- module(heaps, [ add_to_heap/4, % +Heap0, +Priority, ?Key, -Heap delete_from_heap/4, % +Heap0, -Priority, +Key, -Heap empty_heap/1, % +Heap get_from_heap/4, % ?Heap0, ?Priority, ?Key, -Heap heap_size/2, % +Heap, -Size:int heap_to_list/2, % +Heap, -List:list is_heap/1, % +Term list_to_heap/2, % +List:list, -Heap merge_heaps/3, % +Heap0, +Heap1, -Heap min_of_heap/3, % +Heap, ?Priority, ?Key min_of_heap/5, % +Heap, ?Priority1, ?Key1, % ?Priority2, ?Key2 singleton_heap/3 % ?Heap, ?Priority, ?Key ]). /** heaps/priority queues * * Heaps are data structures that return the entries inserted into them in an * ordered fashion, based on a priority. This makes them the data structure of * choice for implementing priority queues, a central element of algorithms * such as best-first/A* search and Kruskal's minimum-spanning-tree algorithm. * * This module implements min-heaps, meaning that items are retrieved in * ascending order of key/priority. It was designed to be compatible with * the SICStus Prolog library module of the same name. merge_heaps/3 and * singleton_heap/3 are SWI-specific extension. The portray_heap/1 predicate * is not implemented. * * Although the data items can be arbitrary Prolog data, keys/priorities must * be ordered by @= N == 0 ; N > 0, Q = t(_,MinP,Sub), are_pairing_heaps(Sub, MinP) ). % True iff 1st arg is a pairing heap with min key @=< 2nd arg, % where min key of nil is logically @> any term. is_pairing_heap(V, _) :- var(V), !, fail. is_pairing_heap(nil, _). is_pairing_heap(t(_,P,Sub), MinP) :- P @=< MinP, are_pairing_heaps(Sub, P). % True iff 1st arg is a list of pairing heaps, each with min key @=< 2nd arg. are_pairing_heaps(V, _) :- var(V), !, fail. are_pairing_heaps([], _). are_pairing_heaps([Q|Qs], MinP) :- is_pairing_heap(Q, MinP), are_pairing_heaps(Qs, MinP). %% list_to_heap(+List:list, -Heap) is det. % % If List is a list of Priority-Element terms, constructs a heap % out of List. Complexity: linear. list_to_heap(Xs,Q) :- empty_heap(Empty), list_to_heap(Xs,Empty,Q). list_to_heap([],Q,Q). list_to_heap([P-X|Xs],Q0,Q) :- add_to_heap(Q0,P,X,Q1), list_to_heap(Xs,Q1,Q). %% min_of_heap(+Heap, ?Priority, ?Key) is semidet. % % Unifies Key with the minimum-priority element of Heap and % Priority with its priority value. Complexity: constant. min_of_heap(heap(t(X,P,_),_), P, X). %% min_of_heap(+Heap, ?Priority1, ?Key1, ?Priority2, ?Key2) is semidet. % % Gets the two minimum-priority elements from Heap. Complexity: logarithmic % (amortized). % % Do not use this predicate; it exists for compatibility with earlier % implementations of this library and the SICStus counterpart. It performs % a linear amount of work in the worst case that a following get_from_heap % has to re-do. min_of_heap(Q,Px,X,Py,Y) :- get_from_heap(Q,Px,X,Q0), min_of_heap(Q0,Py,Y). %% merge_heaps(+Heap0, +Heap1, -Heap) is det. % % Merge the two heaps Heap0 and Heap1 in Heap. Complexity: constant. merge_heaps(heap(L,K),heap(R,M),heap(Q,N)) :- meld(L,R,Q), N is K+M. % Merge two pairing heaps according to the pairing heap definition. meld(nil,Q,Q) :- !. meld(Q,nil,Q) :- !. meld(L,R,Q) :- L = t(X,Px,SubL), R = t(Y,Py,SubR), ( Px @< Py -> Q = t(X,Px,[R|SubL]) ; Q = t(Y,Py,[L|SubR]) ). % "Pair up" (recursively meld) a list of pairing heaps. pairing([], nil). pairing([Q], Q) :- !. pairing([Q0,Q1|Qs], Q) :- meld(Q0, Q1, Q2), pairing(Qs, Q3), meld(Q2, Q3, Q).