exercism / prolog

Exercism exercises in Prolog.
https://exercism.org/tracks/prolog
MIT License
29 stars 37 forks source link

"Hamming" Exercise allows solutions that produce incorrect results #285

Closed bomber34 closed 8 months ago

bomber34 commented 8 months ago

The following code passes the test cases but is not correct.

hamming_distance_chars([], [], 0).
hamming_distance_chars([C|Cs1], [C|Cs2], Dist) :- 
    hamming_distance_chars(Cs1, Cs2, Dist).
hamming_distance_chars([C1|Cs1], [C2|Cs2], Dist) :- 
    hamming_distance_chars(Cs1, Cs2, SubDist),
    Dist is SubDist + 1.

hamming_distance(Str1, Str2, Dist) :-
    string_length(Str1, Len1),
    string_length(Str2, Len2),
    Len1 == Len2,
    string_chars(Str1, Chars1),
    string_chars(Str2, Chars2),
    hamming_distance_chars(Chars1, Chars2, Dist).

The issue lies in the hamming_distance_chars/3 predicate. The third case does not check if C1 and C2 are different. Therefore for the call ?- hamming_distance("AAA", "AAA", Result). We get the following answers:

Result = 0
Result = 1
Result = 1
Result = 2
Result = 1
Result = 2
Result = 2
Result = 3

However, the only valid answer should be 0. The root cause seems to stem from the attempt of fixing the non-exhaustive test cases as raised in issue #81 since the test cases behave no different than prolog itself test(long_identical_strands, condition(pending)) :- hamming_distance("GGACTGA", "GGACTGA", Result), Result == 0. As long as hamming_distance/3 is able to find a Result which is equal to 0, the test passes.

In my opinion, the better method to write test cases in prolog is to first consider if the exercise expects a deterministic solution (exactly one or zero solutions for bound inputs) or a non-deterministic solution (can have multiple solutions for bound input variables).

Therefore, instead of trying to bind Result and then check if there was a found answer matching our expectation, I suggest using the -Options argument in the test/2 predicate. That should make the intention of the tests clear and avoid the issues in #81

:- begin_tests(hamming).
    % problematic as pointed out in issue #81 and does not invalidate wrong solutions
    test(identical_strands, condition(true)) :-
        hamming_distance("A", "A", 0).

    % accepts only one solution
    test(det_long_identical_strands, true(Result =:= 0)) :-
        hamming_distance("GGACTGA", "GGACTGA", Result).

    % if multiple solutions were considered valid for this exercise for the provided code at the start of this issue
    test(nondet_long_identical_strands, set(Result == [0,1,2,3,4,5,6,7])) :-
        hamming_distance("GGACTGA", "GGACTGA", Result).

:- end_tests(hamming).

While I am sure this is a general problem on this exercism track, I noticed it during a mentoring session for this exercise in particular.

github-actions[bot] commented 8 months ago

Hello. Thanks for opening an issue on Exercism 🙂

At Exercism we use our Community Forum, not GitHub issues, as the primary place for discussion. That allows maintainers and contributors from across Exercism's ecosystem to discuss your problems/ideas/suggestions without them having to subscribe to hundreds of repositories.

This issue will be automatically closed. Please use this link%20:-%0D%0A%20%20%20%20%20%20%20%20hamming_distance(%22GGACTGA%22,%20%22GGACTGA%22,%20Result),%20Result%20==%200.%60%0D%0AAs%20long%20as%20hamming_distance/3%20is%20able%20to%20find%20a%20Result%20which%20is%20equal%20to%200,%20the%20test%20passes.%0D%0A%0D%0AIn%20my%20opinion,%20the%20better%20method%20to%20write%20test%20cases%20in%20prolog%20is%20to%20first%20consider%20if%20the%20exercise%20expects%20a%20deterministic%20solution%20(exactly%20one%20or%20zero%20solutions%20for%20bound%20inputs)%20or%20a%20non-deterministic%20solution%20(can%20have%20multiple%20solutions%20for%20bound%20input%20variables).%0D%0A%0D%0ATherefore,%20instead%20of%20trying%20to%20bind%20Result%20and%20then%20check%20if%20there%20was%20a%20found%20answer%20matching%20our%20expectation,%20I%20suggest%20using%20the%20-Options%20argument%20in%20the%20test/2%20predicate.%20That%20should%20make%20the%20intention%20of%20the%20tests%20clear%20and%20avoid%20the%20issues%20in%20#81%20%0D%0A%0D%0A%60%60%60%0D%0A:-%20begin_tests(hamming).%0D%0A%20%20%20%20%25%20problematic%20as%20pointed%20out%20in%20issue%20#81%20and%20does%20not%20invalidate%20wrong%20solutions%0D%0A%20%20%20%20test(identical_strands,%20condition(true))%20:-%0D%0A%20%20%20%20%20%20%20%20hamming_distance(%22A%22,%20%22A%22,%200).%0D%0A%0D%0A%20%20%20%20%25%20accepts%20only%20one%20solution%0D%0A%20%20%20%20test(det_long_identical_strands,%20true(Result%20=:=%200))%20:-%0D%0A%20%20%20%20%20%20%20%20hamming_distance(%22GGACTGA%22,%20%22GGACTGA%22,%20Result).%0D%0A%0D%0A%20%20%20%20%25%20if%20multiple%20solutions%20were%20considered%20valid%20for%20this%20exercise%20for%20the%20provided%20code%20at%20the%20start%20of%20this%20issue%0D%0A%20%20%20%20test(nondet_long_identical_strands,%20set(Result%20==%20%5B0,1,2,3,4,5,6,7%5D))%20:-%0D%0A%20%20%20%20%20%20%20%20hamming_distance(%22GGACTGA%22,%20%22GGACTGA%22,%20Result).%0D%0A%0D%0A:-%20end_tests(hamming).%0D%0A%60%60%60%0D%0A%0D%0AWhile%20I%20am%20sure%20this%20is%20a%20general%20problem%20on%20this%20exercism%20track,%20I%20noticed%20it%20during%20a%20mentoring%20session%20for%20this%20exercise%20in%20particular.%0D%0A&category=prolog ) to copy your GitHub Issue into a new topic on the forum, where we look forward to chatting with you!

If you're interested in learning more about this auto-responder, please read this blog post.