
% ascSeqs(L, ASeqs)
% -----------------
% given a list of numbers, L, divided it into
%    a set of ascending sublists, ASeqs
% e.g.  ascSeqs([3,4,1,2], R) should give
%    R = [[3,4], [1,2]]
%
ascSeqs([], []).
ascSeqs(L,Aseqs) :- numbers(L), reverse(L,LR),
                    splitIntoSeqs(LR,[],Aseqs).

% numbers(L)
% ----------
% succeeds iff L is a list and all elements of L are numbers
numbers([]).
numbers([H|T]) :- number(H), numbers(T).

% approach: start by reversing the list,
%    then keep pulling off the front element of L, and
%    either add it to the front sequence in the result so far
%        or start a new front sequence in the result so far
% e.g.  [3, 4, 5, 1, 2] =>
%    splitIntoSeqs([2,1,5,4,3], [], R)
%    splitIntoSeqs([1,5,4,3], [[2]], R)
%    splitIntoSeqs([5,4,3], [[1,2]], R)
%    splitIntoSeqs([4,3], [[5],[1,2]], R)
%    splitIntoSeqs([3], [[4,5],[1,2]], R)
%    splitIntoSeqs([], [[3,4,5],[1,2]], R)

% splitIntoSeqs(LRev, SoFar, Final)
% ---------------------------------
% given LRev is the sequence still to be processed, and
%    SoFar is the list of sequences identified so far,
%    unify Final with the end result

% base case, nothing left to process
splitIntoSeqs([], SoFar, SoFar).

% if SoFar is empty, the front element of L is the only element
%    of the only list in the result
splitIntoSeqs([H|T], [], R) :-
   splitIntoSeqs(T, [[H]], R).

% if the next element of L is smaller than the front element
%    of the front list, add it to the front list
splitIntoSeqs([H|T], [[HH|TH]|TS], R) :-
   H < HH, splitIntoSeqs(T, [[H,HH|TH]|TS], R).

% otherwise the next element of L is the first element in a new sequence
splitIntoSeqs([H|T], SoFar, R) :-
   splitIntoSeqs(T, [[H]|SoFar], R).

