LoginSignup
0
0

Prologでライフゲーム

Posted at

概要

Prologの練習のためにCUIでライフゲームを作成しました。
以下の書籍のライフゲームをベースとして、ChatGPTで補間しつつなんとか完成させました。

  • 小一時間でゲームをつくる → Amazon

コード

:- use_module(library(process)).
:- use_module(library(apply)).

% -----------------------------------------------------------
% 事実
% -----------------------------------------------------------
field(Field) :- Field = [
  [0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0],
  [0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0]
  ].
field_height(12).
field_width(12).

% -----------------------------------------------------------
% 述語
% -----------------------------------------------------------
% run_command/1
run_command(Command) :- shell(Command, _).
% run_command/2
%   ExitCode (int)  : 終了コード
run_command(Command, ExitCode) :- shell(Command, ExitCode).

% read_input/1
read_input(IsEsc) :-
  get_single_char(Code),
  (
    Code is 27 -> IsEsc = true
    ; IsEsc = false
  ).

main_loop() :-
  field(Field),
  main_loop(Field).

main_loop(Field) :-
  draw_field(Field),
  read_input(IsEsc),
  (
    IsEsc -> ! % Escで終了
  ; calc_living_matrix(Field, LivingCellMatrix),
    step_simulation(Field, LivingCellMatrix, NewField),
    main_loop(NewField)
  ).

neighbor_index_list(1, 1, W, H, EvalList) :-
  % 周囲8セルの座標
  IndexList = [
    [W  , H  ], [1  , H  ], [2  , H  ],
    [W  , 1  ],             [2  , 1  ],
    [W  , 2  ], [1  , 2  ], [2  , 2  ]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(1, Y, W, H, EvalList) :-
  Y < H,
  % 周囲8セルの座標
  IndexList = [
    [W, Y-1], [1  , Y-1], [2  , Y-1],
    [W, Y  ],             [2  , Y  ],
    [W, Y+1], [1  , Y+1], [2  , Y+1]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(X, 1, W, H, EvalList) :-
  X < W,
  % 周囲8セルの座標
  IndexList = [
    [X-1, H  ], [X  , H  ], [X+1, H  ],
    [X-1, 1  ],             [X+1, 1  ],
    [X-1, 2  ], [X  , 2  ], [X+1, 2  ]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(W, 1, W, H, EvalList) :-
  % 周囲8セルの座標
  IndexList = [
    [W-1, H  ], [W  , H  ], [1  , H  ],
    [W-1, 1  ],             [1  , 1  ],
    [W-1, 2  ], [W  , 2  ], [1  , 2  ]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(W, Y, W, H, EvalList) :-
  Y < H,
  % 周囲8セルの座標
  IndexList = [
    [W-1, Y-1], [W  , Y-1], [1  , Y-1],
    [W-1, Y  ],             [1  , Y  ],
    [W-1, Y+1], [W  , Y+1], [1  , Y+1]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(1, H, W, H, EvalList) :-
  % 周囲8セルの座標
  IndexList = [
    [W, H-1], [1  , H-1], [2  , H-1],
    [W, H  ],             [2  , H  ],
    [W, 1  ], [1  , 1  ], [2  , 1  ]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(X, H, W, H, EvalList) :-
  X < W,
  % 周囲8セルの座標
  IndexList = [
    [X-1, H-1], [X  , H-1], [X+1, H-1],
    [X-1, H  ],             [X+1, H  ],
    [X-1, 1  ], [X  , 1  ], [X+1, 1  ]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(X, Y, W, H, EvalList) :-
  X < W, Y < H,
  % 周囲8セルの座標
  IndexList = [
    [X-1, Y-1], [X  , Y-1], [X+1, Y-1],
    [X-1, Y  ],             [X+1, Y  ],
    [X-1, Y+1], [X  , Y+1], [X+1, Y+1]
  ],
  eval_matrix(IndexList, EvalList), !.
neighbor_index_list(W, H, W, H, EvalList) :-
  % 周囲8セルの座標
  IndexList = [
    [W-1, H-1], [W  , H-1], [1  ,H-1],
    [W-1, H  ],             [1  ,H  ],
    [W-1, 1  ], [W  , 1  ], [1  ,1  ]
  ],
  eval_matrix(IndexList, EvalList), !.

eval_list([X], [Value]) :- Value is X.
eval_list([X | Rest], [Value | RestEvalList]) :-
  Value is X,
  eval_list(Rest, RestEvalList).

eval_matrix([Row], [EvalRow]) :- 
  eval_list(Row, EvalRow).
eval_matrix([Row | Rest], [EvalRow | EvalRest]) :-
  eval_list(Row, EvalRow),
  eval_matrix(Rest, EvalRest).

get_at(Matrix, [X, Y], Value) :-
  nth1(Y, Matrix, Row),
  nth1(X, Row, Value).

sum_by_index_list(Field, IndexList, Sum) :-
  maplist(get_at(Field), IndexList, ValueList),
  foldl(plus, ValueList, 0, Sum).

calc_living_matrix(Field, LivingMatrix) :-
  field_width(W), field_height(H),
  calc_living_matrix(1, 1, W, H, Field, LivingMatrix).

calc_living_matrix(X, Y, W, H, Field, LivingMatrix) :-
  Y < H,
  calc_living_matrix_row(X, Y, W, H, Field, LivingRow),
  Next is Y+1,
  calc_living_matrix(X, Next, W, H, Field, LivingRowList),
  LivingMatrix = [LivingRow | LivingRowList], !.

calc_living_matrix(X, H, W, H, Field, LivingMatrix) :-
  calc_living_matrix_row(X, H, W, H, Field, LivingRow),
  LivingMatrix = [LivingRow], !.

calc_living_matrix_row(X, Y, W, H, Field, LivingRow) :-
  X < W,
  neighbor_index_list(X, Y, W, H, IndexList),
  sum_by_index_list(Field, IndexList, Living),
  Next is X+1,
  calc_living_matrix_row(Next, Y, W, H, Field, LivingList),
  LivingRow = [Living | LivingList], !.

calc_living_matrix_row(W, Y, W, H, Field, LivingRow) :-
  neighbor_index_list(W, Y, W, H, IndexList),
  sum_by_index_list(Field, IndexList, Living),
  LivingRow = [Living], !.

step_simulation([Row], [LivingRow], ResultMatrix) :-
  step_simulation_row(Row, LivingRow, NewRow),
  ResultMatrix = [NewRow], !.
step_simulation([Row | RestRows], [LivingRow | LivingRestRows], ResultMatrix) :-
  step_simulation_row(Row, LivingRow, NewRow),
  step_simulation(RestRows, LivingRestRows, NewMatrix),
  ResultMatrix = [NewRow | NewMatrix], !.

step_simulation_row([Cell], [Living], ResultRow) :-
  step_simulation_cell(Cell, Living, NewCell),
  ResultRow = [NewCell], !.

step_simulation_row([Cell | RestCells], [Living | LivingList], ResultRow) :-
  step_simulation_cell(Cell, Living, NewCell),
  step_simulation_row(RestCells, LivingList, NewRow),
  ResultRow = [NewCell | NewRow], !.

step_simulation_cell(Cell, 2, Cell). % 維持
step_simulation_cell(_, 3, 1). % 誕生/生存
step_simulation_cell(_, _, 0). % 死滅

% cell(0, ' ').
cell(0, '□').
cell(1, '■').

% draw_row/1
draw_row([]) :- format('\n'), !.
draw_row([X | Xs]) :-
  cell(X, Cell),
  format('~w', [Cell]),
  draw_row(Xs).

% draw_matrix/1
draw_matrix([]) :- format('\n'), !.
draw_matrix([Row | Rest]) :-
  draw_row(Row),
  draw_matrix(Rest).

% draw_field/1
draw_field(Field) :-
  run_command('clear'), % 画面クリア(Mac/Linux)
  draw_matrix(Field).

% メイン処理 (VSCodeのデバッグ用にstartという名前にしている)
start :-
  main_loop.

% メインを実行
:- initialization(start, main).

使い方

とりあえず起動した後に Enter を押下すると時間が進むようになっています。
終了する場合は Esc キーを押下してください。

簡単な説明

Prologは生成済み配列の要素を変更することができないので、変更する場合は配列を作り直す必要があります。
この制約があるため、ライフゲームの生存判定がややこしくなっています。
特に周囲の8マスを見つける処理は、力技になっています(neighbor_index_listのあたり)。

行列を要素を更新できないので、一旦各セルの周囲8マスの生存数をすべて計算して行列を作成し、その情報を元に次の時刻のデータを計算するという流れになっています。

  1. 各セルの周囲の生存数を計算 : calc_living_matrix/2
  2. 次の時刻のデータを計算 : step_simulation/3
0
0
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
0
0