The next dish on my menu: the baroque clpfd prolog-coroutining hodgepodge.
:- use_module(library(clpfd)).
samelength_of(N,Xss) :- maplist(length_of__lazy(N),Xss).
length_of__lazy(N,Xs) :-
N #>= 0,
( nonvar(N)
-> length(Xs,N)
; var(Xs)
-> when((nonvar(Xs);nonvar(N)), length_of__lazy(N,Xs))
; Xs = []
-> N = 0
; Xs = [_|Xs0]
-> N0 + 1 #= N,
length_of__lazy(N0,Xs0)
; throw(error(type_error(list,Xs),length_of__lazy/2))
).
my_indomain(N) :-
fd_inf(N,I),
( N #= I
; N #> I, my_indomain(N)
).
Some sample queries:
?- Xss = [As,Bs,Cs], As=[], samelength_of(N,Xss).
N = 0, Xss = [[],[],[]], As = [], Bs = [], Cs = [].
?- Xss = [As,Bs,Cs], samelength_of(N,Xss), As=[].
N = 0, Xss = [[],[],[]], As = [], Bs = [], Cs = [].
Some more? Want to try the flounder?
?- samelength_of(N,[As,Bs,Cs]).
N in 0..sup,
when((nonvar(As);nonvar(N)), length_of__lazy(N,As)),
when((nonvar(Bs);nonvar(N)), length_of__lazy(N,Bs)),
when((nonvar(Cs);nonvar(N)), length_of__lazy(N,Cs)).
Flounder is not your taste? No problemo!
?- samelength_of(N,[As,Bs,Cs]), my_indomain(N).
N = 0, As = [], Bs = [], Cs = [] ;
N = 1, As = [_A1], Bs = [_B1], Cs = [_C1] ;
N = 2, As = [_A1,_A2], Bs = [_B1,_B2], Cs = [_C1,_C2] ;
N = 3, As = [_A1,_A2,_A3], Bs = [_B1,_B2,_B3], Cs = [_C1,_C2,_C3] ...