Prolog "console"

Admin User, erstellt 26. Mai 2023
         
/**
* Prolog code for the tic-tac-toe game.
* Min-max search via negation.
* Game board via Prolog term.
*
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
% :- use_module(library(standard/lists)).
:- ensure_loaded(library(lists)).
/*************************************************************/
/* Console Play */
/*************************************************************/
% play(+Board)
play :- init(X), show_board(X), prompt_board(X, Y), looser(Y).
% looser(+Board)
looser(X) :- win(X, x), !, write('You win.'), nl.
looser(X) :- tie(X, o), !, write('Nobody won.'), nl.
looser(X) :- best(X, o, Y), !, write('Computer move:'), nl, show_board(Y), winner(Y).
looser(_) :- write('I give up.'), nl.
% winner(+Board)
winner(X) :- win(X, o), !, write('I win.'), nl.
winner(X) :- prompt_board(X, Y), looser(Y).
% prompt_board(+Board, -Board)
prompt_board(X, Y) :-
prompt_position(R, C),
nth0(R, X, A, Z),
nth0(C, A, _, H),
nth0(C, B, 'x', H),
nth0(R, Y, B, Z),
show_board(Y).
% prompt_position(-Integer, -Integer)
prompt_position(R, C) :-
write('Your move: '), flush_output,
read(M), atom_codes(M, [P, Q]),
R is P-0'a, C is Q-0'1.
% show_board(+Board)
show_board([P,Q,R]) :-
write(' 1 2 3'), nl,
write(' +-+-+-+'), nl,
write('a'), show_row(P),
write(' +-+-+-+'), nl,
write('b'), show_row(Q),
write(' +-+-+-+'), nl,
write('c'), show_row(R),
write(' +-+-+-+'), nl.
% show_row(+Row)
show_row([A,B,C]) :-
write('|'), write(A),
write('|'), write(B),
write('|'), write(C),
write('|'), nl.