1% -*- prolog -*-
    2:- module(rtp_dqs,
    3	[ empty_deque/1,         % creates/tests for the empty deque
    4	  inject_deque/3,        % add to back of deque
    5	  eject_deque/3,         % remove from back of deque
    6	  push_deque/3,          % add to front of deque
    7	  pop_deque/3,           % remove from front of deque
    8	  reverse_deque/2,       % reverse a deque
    9	  poplist_deque/3,       % add/remove a list of 
   10	  pushlist_deque/3,      %   elements from 
   11	  injectlist_deque/3,    %   the front or back
   12	  ejectlist_deque/3      %   of the deque
   13      ]).

Real-time Persistent Deques

Offers a Prolog implementation of double-ended queues (deques) with constant time basic operations and full version reusability. The implementation is based on Bouma (2012), referenced below. Time guarantees and determinism indications apply to the cases in which the predicate signature is respected.

In the signatures, +DQ:deque means that DQ is an input argument and must be sufficiently instantiated, that is, it is a valid deque representing term as produced by a deque outputting predicate. Due to the design of the datastructure, these need not be ground.

author
- Gerlof Bouma, Uni Gothenburg
See also
- Bouma, Gerlof. 2012. Real-time Persistent Queues and Deques with Logic Variables (Declarative Pearl). In Schrijvers and Thiemann (Eds), Functional and Logic Programming, Proceedings of the 11th International Symposium FLOPS 2012, LNCS 7294, pp. 62-72, Heidelberg: Springer.
- http://spraakbanken.gu.se/personal/gerlof/home
bug
- Loading together with rtp_qs.pl somehow doesn't work. */
   39:- use_module(library(type_check)).   40
   41:- type deque(T) ---> dq(integer,list(T),integer,list(T),state(T)).
   42:- type state(T) ---> ready
   43                    %     Lgs     Lgs_revs      Ss_tail
   44                    ; rot(list(T),list(list(T)),list(T))
   45                    %     Ss      Ss_open Ls      Lks      Lgs_revs
   46                    ; rot(list(T),list(T),list(T),list(T), list(list(T))).
   47
   48
   49%% reverse_deque(+DQ:deque,-DQ_rev:deque) is det.
   50%
   51% Reverse a deque. 
   52%
   53:- pred reverse_deque(deque(T),deque(T)).
   54%
   55reverse_deque(dq(Fs_len,Fs,Rs_len,Rs,St),dq(Rs_len,Rs,Fs_len,Fs,St)).
   56
   57
   58%% empty_deque(?DQ:deque) is semidet.
   59% 
   60% Holds of the empty deque.
   61%
   62:- pred empty_deque(deque(_T)).
   63%
   64empty_deque(dq(0,[],0,[],ready)).
   65
   66
   67%% push_deque(?El,+DQ_old:deque,-DQ_new:deque) is det.
   68%
   69% Adds El to the front of DQ_old to give DQ_new.
   70%
   71:- pred push_deque(T, deque(T),deque(T)).
   72%
   73push_deque(F,dq(Fs_len,Fs,Rs_len,Rs,St),DQ_new):-
   74    Fs1_len is Fs_len+1,
   75    make_dq(St,Fs1_len,[F|Fs],Rs_len,Rs,DQ_new).
   76
   77
   78%% inject_deque(?El,+DQ_old:deque,-DQ_new:deque) is det.
   79%
   80% Adds El to the back of DQ_old to give DQ_new.
   81%
   82:- pred inject_deque(T,deque(T),deque(T)).
   83%
   84inject_deque(El,DQ_old,DQ_new):-
   85    reverse_deque(DQ_old,DQ_dlo),
   86    push_deque(El,DQ_dlo,DQ_wen),
   87    reverse_deque(DQ_wen,DQ_new).
   88
   89
   90%% pop_deque(+DQ_old:deque,?El,-DQ_new:deque) is semidet.
   91%
   92% Removes ?El from the front of DQ_old to give DQ_new. 
   93%
   94% May fail if ?El cannot be unified with the front element of DQ_old
   95% or if DQ_old is empty.
   96%
   97:- pred pop_deque(deque(T),T, deque(T)).
   98%
   99pop_deque(dq(Fs_len,Fs,Rs_len,Rs,St),F,DQ_new):-
  100    ( Fs == []
  101      -> Rs = [F],
  102         empty_deque(DQ_new)
  103    ; Fs = [F|Fs1],
  104      Fs1_len is Fs_len-1,
  105      make_dq(St,Fs1_len,Fs1,Rs_len,Rs,DQ_new)
  106    ).
  107
  108
  109%% eject_deque(+DQ_old:deque,?El,-DQ_new:deque) is semidet.
  110%
  111% Removes ?El from the back of DQ_old to give DQ_new. 
  112%
  113% May fail if ?El cannot be unified with the rear element of DQ_old
  114% or if DQ_old is empty.
  115%
  116:- pred eject_deque(deque(T),T, deque(T)).
  117%
  118eject_deque(DQ_old,El,DQ_new):-
  119    reverse_deque(DQ_old,DQ_dlo),
  120    pop_deque(DQ_dlo,El,DQ_wen),
  121    reverse_deque(DQ_wen,DQ_new).
  122
  123
  124%% pushlist_deque(+Els:list,+DQ_old:deque,-DQ_new:deque) is det.
  125%
  126% Pushes elements of Els onto DQ_old to give DQ_new. 
  127%
  128:- pred pushlist_deque(list(T),deque(T),deque(T)).
  129%
  130pushlist_deque([],DQ,DQ).
  131pushlist_deque([El|Els],DQ_old,DQ_new):-
  132	push_deque(El,DQ_old,DQ_mid),
  133	pushlist_deque(Els,DQ_mid,DQ_new).
  134
  135
  136%% injectlist_deque(+Els:list,+DQ_old:deque,-DQ_new:deque) is det.
  137%
  138% Injects elements of Els into DQ_old to give DQ_new. 
  139%
  140:- pred injectlist_deque(list(T),deque(T),deque(T)).
  141injectlist_deque(Els,DQ_old,DQ_new):-
  142	reverse_deque(DQ_old,DQ_dlo),
  143	pushlist_deque(Els,DQ_dlo,DQ_wen),
  144	reverse_deque(DQ_wen,DQ_new).
  145
  146
  147%% poplist_deque(+DQ_old:deque,?Els:list,-DQ_new:deque) is nondet.
  148%
  149% Pops elements from DQ_old onto Els to give DQ_new. See pop_deque/3.
  150%
  151% Gives a.o. quick (and dirty?)
  152% ways of implementing deque-to-list 
  153% ( =|poplist_deque(DQ_old,Els,DQ_new), empty(DQ_new)|= ) and  `take N'
  154% ( =|length(N,Els), poplist(DQ_old,Els,DQ_new)|= ). 
  155%
  156:- pred poplist_deque(deque(T),list(T),deque(T)).
  157%
  158poplist_deque(DQ,[],DQ).
  159poplist_deque(DQ_old,[El|Els],DQ_new):-
  160	pop_deque(DQ_old,El,DQ_mid),
  161	poplist_deque(DQ_mid,Els,DQ_new).
  162
  163
  164%% ejectlist_deque(+DQ_old:deque,?Els:list,-DQ_new:deque) is nondet.
  165%
  166% Ejects elements from DQ_old onto Els to give DQ_new. See
  167% eject_deque/3 and usage hints at poplist_deque/3.
  168%
  169:- pred ejectlist_deque(deque(T),list(T),deque(T)).
  170%
  171ejectlist_deque(DQ_old,Els,DQ_new):-
  172	reverse_deque(DQ_old,DQ_dlo),
  173	poplist_deque(DQ_dlo,Els,DQ_wen),
  174	reverse_deque(DQ_wen,DQ_new).
  175	
  176
  177% Aux predicates. See the paper for explanation. Compared to the
  178% paper, these are longer, `unrolled' versions that do not use the
  179% second-order predicate call/2.
  180%
  181
  182% make_dq/4     +State,  +Fs_len +Fs     +Rs_len +Rs     -DQ_new
  183:- pred make_dq(state(T),integer,list(T),integer,list(T),deque(T)).
  184%
  185make_dq(ready,Fs_len,Fs,Rs_len,Rs,DQ):-
  186	( Rs_len > 3*Fs_len
  187          -> Rs1_len is 2*Fs_len+1,
  188             Fs1_len is Rs_len-Fs_len-1,
  189             four_rot(Fs,Fs1,Rs,Rs1,[[]|_],St1),
  190             DQ = dq(Fs1_len,Fs1,Rs1_len,Rs1,St1)
  191
  192	; Fs_len > 3*Rs_len
  193          -> Fs1_len is 2*Rs_len+1,
  194             Rs1_len is Fs_len-Rs_len-1,
  195	     four_rot(Rs,Rs1,Fs,Fs1,[[]|_],St1),
  196             DQ = dq(Fs1_len,Fs1,Rs1_len,Rs1,St1)
  197
  198	; DQ = dq(Fs_len,Fs,Rs_len,Rs,ready)
  199        ).
  200make_dq(rot(A1,A2,A3),Fs_len,Fs,Rs_len,Rs,dq(Fs_len,Fs,Rs_len,Rs,St1)):-
  201	two_rot(A1,A2,A3,St1).
  202make_dq(rot(A1,A2,A3,A4,A5),Fs_len,Fs,Rs_len,Rs,dq(Fs_len,Fs,Rs_len,Rs,St1)):-
  203	two_rot(A1,A2,A3,A4,A5,St1).
  204
  205
  206% The state update predicates contain now the state update logic as
  207% well as the counting, so that we handle doing two or four repeated
  208% updates without meta-calling. Should really be autogenerated code,
  209% though...
  210
  211% rot/4           +Lgs    ?Lgs_revs     ?Ss_tail -State
  212:- pred  four_rot(list(T),list(list(T)),list(T), state(T)).
  213:- pred three_rot(list(T),list(list(T)),list(T), state(T)).
  214:- pred   two_rot(list(T),list(list(T)),list(T), state(T)).
  215:- pred   one_rot(list(T),list(list(T)),list(T), state(T)).
  216%
  217four_rot([],[Ss_tail],Ss_tail,ready).
  218four_rot([Lg|Lgs],[Lgs_rev|Lgs_revs],Ss_tail,St1):-
  219	Lgs_revs = [[Lg|Lgs_rev]|_],
  220	three_rot(Lgs,Lgs_revs,Ss_tail,St1).
  221three_rot([],[Ss_tail],Ss_tail,ready).
  222three_rot([Lg|Lgs],[Lgs_rev|Lgs_revs],Ss_tail,St1):-
  223	Lgs_revs = [[Lg|Lgs_rev]|_],
  224	two_rot(Lgs,Lgs_revs,Ss_tail,St1).
  225two_rot([],[Ss_tail],Ss_tail,ready).
  226two_rot([Lg|Lgs],[Lgs_rev|Lgs_revs],Ss_tail,St1):-
  227	Lgs_revs = [[Lg|Lgs_rev]|_],
  228	one_rot(Lgs,Lgs_revs,Ss_tail,St1).
  229one_rot([],[Ss_tail],Ss_tail,ready).
  230one_rot([Lg|Lgs],[Lgs_rev|Lgs_revs],Ss_tail,rot(Lgs,Lgs_revs,Ss_tail)):-
  231	Lgs_revs = [[Lg|Lgs_rev]|_].
  232
  233
  234% rot/6           +Ss     ?Ss_open +Ls     ?Lks    ?Lgs_revs     -State
  235:- pred  four_rot(list(T),list(T), list(T),list(T),list(list(T)),state(T)).
  236:- pred three_rot(list(T),list(T), list(T),list(T),list(list(T)),state(T)).
  237:- pred   two_rot(list(T),list(T), list(T),list(T),list(list(T)),state(T)).
  238:- pred   one_rot(list(T),list(T), list(T),list(T),list(list(T)),state(T)).
  239%
  240four_rot([],Ss_tail,[L|Lgs],[L],Lgs_revs,St1):-
  241	three_rot(Lgs,Lgs_revs,Ss_tail,St1).
  242four_rot([S|Ss],[S|Ss_open],[L1,L2|Ls],[L1,L2|Lks],Lgs_revs,St1):-
  243	three_rot(Ss,Ss_open,Ls,Lks,Lgs_revs,St1).
  244three_rot([],Ss_tail,[L|Lgs],[L],Lgs_revs,St1):-
  245	two_rot(Lgs,Lgs_revs,Ss_tail,St1).
  246three_rot([S|Ss],[S|Ss_open],[L1,L2|Ls],[L1,L2|Lks],Lgs_revs,St1):-
  247	two_rot(Ss,Ss_open,Ls,Lks,Lgs_revs,St1).
  248two_rot([],Ss_tail,[L|Lgs],[L],Lgs_revs,St1):-
  249	one_rot(Lgs,Lgs_revs,Ss_tail,St1).
  250two_rot([S|Ss],[S|Ss_open],[L1,L2|Ls],[L1,L2|Lks],Lgs_revs,St1):-
  251	one_rot(Ss,Ss_open,Ls,Lks,Lgs_revs,St1).
  252one_rot([],Ss_tail,[L|Lgs],[L],Lgs_revs,rot(Lgs,Lgs_revs,Ss_tail)).
  253one_rot([S|Ss],[S|Ss_open],[L1,L2|Ls],[L1,L2|Lks],Lgs_revs,rot(Ss,Ss_open,Ls,Lks,Lgs_revs))