Coroutine to compare two lists using shif/reset continuation

Recently I posted the following codes, which flattens each input terms,
and compare them.

flatten_term_compare(C, A, B):-
	flatten_term(A, X, [], []),
	flatten_term(B, Y, [], []),
	compare(C, X, Y).

Apparently it is preferable to detect early corresponding pair of elements which differs. So I wrote codes below as exercise of continuation using shift/reset. I realized the shift/reset makes it easy to convert existing predicate into that works as coroutine. However, I heard that library(engine) is better than shift/reset in speed efficiency. I am not familiar with library(engine). Comment will be appreciated. Anyway shift/reset is suitable at least for rapid prototyping of complex coroutine, I think, because of its clear behavioral semantics.

% ?- cft_compare(C, [a], [a, b]).
cft_compare(C, X, Y):-
	compare_handler(C, flatten_term_cont(X, _, [], []),
					flatten_term_cont(Y, _, [], [])).
%
compare_handler(D, P, Q):- reset(P, B, C),
   reset(Q, B0, C0),
   (	C = 0, C0 = 0 -> D = (=)
   ;	C = 0  -> D = (<)
   ; 	C0 = 0 -> D = (>)
   ;	compare_token(E, B, B0),
		(	E = (=) ->	compare_handler(D, C, C0)
		;	D = E
		)
   ).
%
flatten_term_cont(A, [U|X], Y, H):- compound(A), !,
	(	cycle_period(A, H, 1, K) ->
		U = ref(K),
		shift(U),
		Y = X
	;	A =.. [F|As],
		length(As, N),
		U = fun(N/F),
		shift(U),
		flatten_term_list_cont(As, X, Y, [A|H])
	).
flatten_term_cont(A, [basic(A)|X], X, _):- shift(basic(A)).

%
flatten_term_list_cont([], [end|X], X, _):- shift(end).
flatten_term_list_cont([A|As], X, Y, H):-
	flatten_term_cont(A, X, Z, H),
	flatten_term_list_cont(As, Z, Y, H).
%
compare_token(=, end, end):-!.
compare_token(<, end, _):-!.
compare_token(>, _, end):-!.
compare_token(C, basic(A), basic(B)):-!, compare(C, A, B).
compare_token(C, fun(U), fun(V)):-!, compare(C, U, V).
compare_token(<, basic(_), fun(_)):-!.
compare_token(>, fun(_), basic(_)):-!.
compare_token(C, fun(U), fun(V)):- compare(C, U, V).

compare_token/3 was incomplete on ref(_). This one is complete, I hope. (fuzzer test passed for 100 seconds.)

compare_token(=, end, end):-!.
compare_token(<, end, _):-!.
compare_token(>, _, end):-!.
compare_token(C, basic(A), basic(B)):-!, compare(C, A, B).
compare_token(C, fun(U), fun(V)):-!, compare(C, U, V).
compare_token(C, ref(X), ref(Y)):-!, compare(C, X, Y).
compare_token(<, basic(_), fun(_)):-!.
compare_token(>, fun(_), basic(_)):-!.
compare_token(<, _, ref(_)):-!.
compare_token(>, ref(_), _).

BTW What is hydra ? Apropos does not hit it.