1% -*- prolog -*-
    2:- module(rtp_qs,
    3        [ empty_queue/1,         % creates/tests for the empty queue
    4          inject_queue/3,        % add to back of queue
    5          pop_queue/3,           % remove from front of queue
    6          push_queue/3,          % add to front of queue -- it is really
    7	                         %   an output-restricted deque!
    8          poplist_queue/3,       % add a list of elements to
    9          pushlist_queue/3,      %   to front or back or 
   10          injectlist_queue/3     %   remove from the front
   11      ]).   12
   13:- use_module(library(type_check)).   14
   15/** <module> Real-time Persistent Queues
   16
   17Offers a Prolog implementation of queues with constant time basic
   18operations and full version reusability. The implementation is based
   19on Bouma (2012), referenced below. Time guarantees and determinism
   20indications apply to the cases in which the predicate signature is
   21respected.
   22
   23In the signatures, +Q:queue means that Q is an input argument and must
   24be _sufficiently_ instantiated, that is, it is a valid queue
   25representing term as constructed by a queue outputting predicate. Due
   26to the design of the datastructure, these need not be ground.
   27
   28@author Gerlof Bouma, Uni Gothenburg
   29@see Bouma, Gerlof. 2012. Real-time Persistent Queues and Deques with
   30  Logic Variables (Declarative Pearl). In Schrijvers and Thiemann
   31  (Eds), Functional and Logic Programming, Proceedings of the 11th
   32  International Symposium FLOPS 2012, LNCS 7294, pp. 62-72,
   33  Heidelberg: Springer.
   34@see http://spraakbanken.gu.se/personal/gerlof/home
   35@bug Loading together with rtp_dqs.pl somehow doesn't work.
   36*/
   37
   38:- type queue(T) ---> q(list(T),list(T),state(T)).
   39:- type state(T) ---> ready
   40                      % Rs_revs
   41                      ; wait(list(T))
   42		      %      St
   43                      ; delay(state(T))
   44                      %     Fs       Fs_open Rs     Rs_revs
   45                      ; rot(list(T),list(T),list(T),list(list(T))).
   46
   47
   48%% empty_queue(?Q:queue) is semidet.
   49% 
   50% Holds of the empty queue.
   51%
   52:- pred empty_queue(queue(_T)).
   53%
   54empty_queue(q([],[],ready)).
   55
   56
   57%% pop_queue(+Q_old:queue,?El,-Q_new:queue) is semidet.
   58%
   59% Removes ?El from the front of Q_old to give Q_new. 
   60%
   61% May fail if ?El cannot be unified with the front element of Q_old
   62% or if Q_old is empty.
   63%
   64:- pred pop_queue(queue(T),T,  queue(T)).
   65%
   66pop_queue(q([F|Fs],Rs,St),F,Q1):-
   67	make_q(St,Fs,Rs,Q1).
   68
   69
   70%% inject_queue(?El,+Q_old:queue,-Q_new:queue) is det.
   71%
   72% Adds El to the back of Q_old to give Q_new.
   73%
   74:- pred inject_queue(T,  queue(T),queue(T)).
   75%
   76inject_queue(R,q(Fs,Rs,St),Q1):-
   77	make_q(St,Fs,[R|Rs],Q1).
   78
   79
   80%% push_queue(?El,+DQ_old:queue,-DQ_new:queue) is det.
   81%
   82% Adds El to the front of DQ_old to give DQ_new.
   83%
   84% ( This extension of the version presented in the paper makes the
   85% datastructure an output-restricted double-ended queue. )
   86%
   87:- pred push_queue(T,  queue(T),queue(T)).
   88%
   89push_queue(F,q(Fs,Rs,St),q([F|Fs],Rs,delay(St))).
   90
   91
   92%% poplist_queue(+Q_old:queue,?Els:list,-Q_new:queue) is nondet.
   93%
   94% Pops elements from Q_old onto Els to give Q_new. See pop_queue/3.
   95%
   96% Gives a.o. quick (and dirty?)
   97% ways of implementing queue-to-list 
   98% ( =|poplist_queue(Q_old,Els,Q_new), empty(Q_new)|= ) and  `take N'
   99% ( =|length(N,Els), poplist(Q_old,Els,Q_new)|= ). 
  100%
  101:- pred pops_queue(queue(T),list(T),queue(T)).
  102%
  103poplist_queue(Q,[],Q).
  104poplist_queue(Q,[El|Els],Q2):-
  105	pop_queue(Q,El,Q1),
  106	poplist_queue(Q1,Els,Q2).
  107
  108
  109%% injectlist_queue(+Els:list,+Q_old:queue,-Q_new:queue) is det.
  110%
  111% Injects elements of Els into Q_old to give Q_new. 
  112%
  113:- pred injects_queue(list(T),queue(T),queue(T)).
  114%
  115injectlist_queue([],Q,Q).
  116injectlist_queue([El|Els],Q,Q2):-
  117	inject_queue(El,Q,Q1),
  118	injectlist_queue(Els,Q1,Q2).
  119
  120
  121%% pushlist_queue(+Els:list,+Q_old:queue,-Q_new:queue) is det.
  122%
  123% Pushs elements of Els onto Q_old to give Q_new. 
  124%
  125:- pred pushs_queue(list(T),queue(T),queue(T)).
  126%
  127pushlist_queue([],Q,Q).
  128pushlist_queue([El|Els],Q,Q2):-
  129	push_queue(El,Q,Q1),
  130	pushlist_queue(Els,Q1,Q2).
  131
  132
  133% Aux predicates. See the paper for explanation. Compared to the
  134% paper, these are longer, `unrolled' versions that do not use the
  135% second-order predicate call/2.
  136%
  137
  138% make_q/4      +State, +Fs     +Rs     -Q1
  139:- pred make_q(state(T),list(T),list(T),queue(T)).
  140%
  141make_q(ready,Fs,Rs,q(Fs1,[],St1)):-
  142	rot(Fs,Fs1,Rs,[[]|_],St1).
  143make_q(wait(A),Fs,Rs,q(Fs,Rs,St1)):-
  144    wait(A,St1).
  145make_q(delay(St1),Fs,Rs,q(Fs,Rs,St1)).         
  146make_q(rot(A1,A2,A3,A4),Fs,Rs,q(Fs,Rs,St1)):-
  147	rot(A1,A2,A3,A4,St1).
  148
  149
  150% wait/2     +Rs_rev -State
  151:- pred(wait(list(T),state(T))).  152wait([],ready).
  153wait([_|Rs_rev],wait(Rs_rev)).
  154
  155
  156% rot/5     +Fs     ?Fs_tail +Rs     ?Rs_revs      -State
  157:- pred(rot(list(T),list(T), list(T),list(list(T)),state(T))).  158%
  159rot([],[R|Rs_rev],[R],[Rs_rev],wait(Rs_rev)).
  160rot([F|Fs],[F|Fs_tail],[R|Rs],[Rs_rev|Rs_revs],rot(Fs,Fs_tail,Rs,Rs_revs)):-
  161	Rs_revs = [[R|Rs_rev]|_]