1:- module(
    2       ropes,
    3       [
    4           string_rope/2,
    5           rope_string/2,
    6           rope_codes/2,
    7           rope_split/4,
    8           rope_concat/3,
    9           rope_report/4,
   10           rope_edit/5
   11       ]
   12   ).

Ropes

An implementation of the rope data structure.

Based on Boehm, H.J., Russ Atkinson, and Michael Plass. "Ropes: An alternative to strings." Software: Practice and Experience 25.12 (1995): 1315-1330.

*/

 string_rope(+String:string, -Rope:rope) is det
True when Rope is a rope leaf holding the string String
   26string_rope(S , leaf(L, S)) :- string(S), string_length(S, L).
 rope_string(+Rope:rope, -String:string) is det
True when Rope represents the accumulated string String
   33rope_string(leaf(_, S)         , S ).
   34rope_string(node(_, _, _, A, B), S ) :-
   35    rope_string(A, AS),
   36    rope_string(B, BS),
   37    string_concat(AS, BS, S).
 rope_codes(+Rope:rope, -Codes:codes) is det
True when Rope represents the accumulated list of codes in Codes
   44rope_codes(R, C) :- phrase(rope_codes(R), C).
   45
   46rope_codes(leaf(_, S)         ) --> {   string_codes(S, Cs)   }, Cs.
   47rope_codes(node(_, _, _, A, B)) --> rope_codes(A), rope_codes(B).
 rope_split(+Rope:rope, +At:nonneg, -Left:rope, -Right:rope) is det
True when spliting Rope at underlying offset At yields ropes Left and Right
   54rope_split(leaf(_, String), At, leaf(At, Left), leaf(RLen, Right)) :-
   55    sub_string(String, At, RLen, 0, Right),
   56    !,
   57    sub_string(String, 0 , At  , _, Left).
   58rope_split(node(W, _, _, A, B), At, L, BB) :-
   59    W =< At,
   60    !,
   61    At1 is At - W,
   62    rope_split(B, At1, BA, BB),
   63    rope_concat(A, BA, L).
   64rope_split(node(_, _, _, A, B), At, L, R) :-
   65    rope_split(A, At, L, AB),
   66    rope_concat(AB, B, R).
   67
   68
   69rope_depth(leaf(_, _         ), 0).
   70rope_depth(node(_, _, D, _, _), D).
   71
   72
   73rope_length(leaf(L, _         ), L).
   74rope_length(node(_, L, _, _, _), L).
 rope_concat(+Left:rope, +Right:rope, -Rope:rope) is det
True when Rope is the concatenation of Left and Right
   81rope_concat(A, B, C) :-
   82    rope_concat_(A, B, C0),
   83    (   rope_balanced(C0)
   84    ->  C = C0
   85    ;   rope_balance(C0, C)
   86    ).
   87
   88rope_concat_(A, leaf(0, _), A) :- !.
   89rope_concat_(leaf(0, _), B, B) :- !.
   90rope_concat_(A, B, node(W, L, D, A, B)) :-
   91    rope_length(A, W ), rope_length(B, LB), L is W + LB,
   92    rope_depth( A, DA), rope_depth( B, DB), D is max(DA, DB) + 1.
   93
   94rope_balanced(R) :-
   95    rope_length(R, L),
   96    rope_depth(R, D0),
   97    D is D0 + 2,
   98    fib(D, F),
   99    F =< L.
  100
  101fib(0, 1) :- !.
  102fib(1, 1) :- !.
  103fib(N, F) :-
  104        fib(1,1,1,N,F).
  105
  106fib(_F, F1, N, N, F1) :- !.
  107fib(F0, F1, I, N, F)  :-
  108        F2 is F0+F1,
  109        I2 is I + 1,
  110        fib(F1, F2, I2, N, F).
  111
  112bif(M, N) :- bif(M, 1, 1, 0, N).
  113
  114bif(M, _ , F1, N , N) :- M =< F1, !.
  115bif(M, F0, F1, N0, N) :-
  116    F2 is F0 + F1,
  117    N1 is N0 + 1,
  118    bif(M, F1, F2, N1, N).
  119
  120
  121rope_balance(leaf(L, S), leaf(L, S)).
  122rope_balance(node(_, _, _, A, B), C) :-
  123    rope_balance(A, []    , Slots0),
  124    rope_balance(B, Slots0, Slots),
  125    pairs_values(Slots, Ropes),
  126    foldl(rope_concat_, Ropes, leaf(0, ""), C).
  127
  128rope_balance(leaf(L, S), D0, D) :-
  129    bif(L, I),
  130    partition({I}/[J-R]>>(J=<I), D0, D1, D2),
  131    pairs_values(D1, Rs0),
  132    reverse(Rs0, Rs),
  133    foldl(rope_concat_, Rs, leaf(0, ""), R0),
  134    rope_concat_(R0, leaf(L, S), R),
  135    rope_balance_(R, 0, D2, D).
  136rope_balance(node(_, _, _, A, B), D0, D) :-
  137    rope_balance(A, D0, D1),
  138    rope_balance(B, D1, D).
  139
  140rope_balance_(R0, J0, D0, D) :-
  141    select(J0-O, D0, D1),
  142    !,
  143    rope_concat_(O, R0, R),
  144    J is J0 + 1,
  145    rope_balance_(R, J, D1, D).
  146rope_balance_(R, J, D0, D) :-
  147    rope_length(R, L),
  148    bif(L, I),
  149    (   I =< J
  150    ->  ord_add_element(D0, I-R, D)
  151    ;   J1 is J + 1,
  152        rope_balance_(R, J1, D0, D)
  153    ).
 rope_report(+Rope:rope, +Offset:integer, +Length:integer, -String:string) is det
True when String is unified with the sub string in offset Offset and length Length of the underlying string of rope Rope
  160rope_report(leaf(_, S), O, N, R) :-
  161    sub_string(S, O, N, _, R).
  162rope_report(node(W, _, _, A, _), O, N, R) :-
  163    O + N =< W,
  164    !,
  165    rope_report(A, O, N, R).
  166rope_report(node(W, _, _, A, B), O, N, R) :-
  167    NA is W - O,
  168    0 < NA,
  169    !,
  170    rope_report(A, O, NA, RA),
  171    NB is O + N - W,
  172    rope_report(B, 0, NB, RB),
  173    string_concat(RA, RB, R).
  174rope_report(node(W, _, _, _, B), O, N, R) :-
  175    OB is O - W,
  176    rope_report(B, OB, N, R).
 rope_edit(+RopeIn:rope, +Offset:integer, +Length:integer, +Content:string, -RopeOut:rope) is det
Unify RopeOut with a rope obtained by replacing Content with the portion of RopeIn starting from offset Offset and spanning Length characters.
  184rope_edit(RopeIn, Offset, Length, Content, RopeOut) :-
  185    string_rope(Content, RopeContent),
  186    rope_split(RopeIn, Offset, Lope1, Rope1),
  187    rope_split(Rope1, Length, _, Rope2),
  188    rope_concat(Lope1, RopeContent, Lope2),
  189    rope_concat(Lope2, Rope2, RopeOut).
  190
  191
  192
  193:- begin_tests(ropes).  194
  195test(edit) :-
  196    string_rope("Hello, World!"  , HW),
  197    rope_edit(HW, 7, 5, "dragons", HD),
  198    rope_string(HD, HF),
  199    assertion(HF == "Hello, dragons!").
  200
  201test(report) :-
  202    string_rope("foobarbaz", R),
  203    rope_split(R, 6, FB, BZ),
  204    rope_split(FB, 3, F, BR),
  205    rope_concat(F, BR, FBB),
  206    rope_concat(FBB, BZ, FBZ),
  207    rope_report(FBZ, 2, 5, S),
  208    assertion(S == "obarb").
  209
  210:- end_tests(ropes).