123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498 |
- -module(game_manager).
- -behaviour(gen_server).
- -author('Maxim Sokhatsky <maxim@synrc.com>').
- -compile(export_all).
- -export([init/1, start/0, start_link/0, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3]).
- -include_lib("server/include/requests.hrl").
- -include_lib("server/include/conf.hrl").
- -include_lib("db/include/table.hrl").
- -include_lib("db/include/tournaments.hrl").
- -include_lib("server/include/log.hrl").
- -include_lib("stdlib/include/qlc.hrl").
- -include_lib("db/include/scoring.hrl").
- -record(state, { game_tavla = 0, game_okey = 0 }).
- online() -> [X||X<-qlc:e(gproc:table()),element(1,X)=={p,l,broadcast}].
- get_all_games_ids() ->
- [GameId || {_, _, #game_table{id = GameId, game_type = game_okey}} <- qlc:e(gproc:table())].
- destroy_game(Pid,Sup) -> game_sup:stop_game(Sup,Pid).
- gen_game_id() ->
- PoolNum = wf:config(nsx_idgen,game_pool,5000000) div 1000000,
- PoolNumStr = integer_to_list(PoolNum),
- PoolNum*1000000 + 200 + kvs:next_id("game_table", 1).
- %% 200 is reserved for lucky games and for already created games
- create_game(GameId, GameFSM, Params) ->
- {ok, Pid} = create_game_monitor(GameId, GameFSM, Params),
- {ok, GameId, Pid}.
- %% rank_table(GameId) -> {ok, {LastTourNum, TourResult}} | {error, Reason}
- %% TourResult = {UserId, Pos, Points, Status}
- rank_table(GameId) ->
- case get_relay_mod_pid(GameId) of
- {Module, Pid} -> Module:system_request(Pid, last_tour_result);
- undefined -> {error, not_found}
- end.
- get_lucky_pid(Sup) ->
- [X]=game_manager:get_lucky_table(Sup),
- X#game_table.game_process.
- get_relay_pid(GameId) -> case get_tables(GameId) of [] -> undefined;
- [#game_table{game_process = P} | _] -> gas:info(?MODULE,"GameRelay: ~p",[P]), P end.
- get_relay_mod_pid(GameId) -> case get_tables(GameId) of [] -> undefined;
- [#game_table{game_process = P, game_module = M} | _] -> gas:info(?MODULE,"GameRelay: ~p",[{M,P}]), {M,P} end.
- get_relay(GameId) -> gen_server:call(?MODULE, {get_relay, GameId}).
- game_requirements(GameAtom) -> GameAtom:get_requirements().
- game_requirements(game_tavla,paired) -> paired_tavla:get_requirements();
- game_requirements(GameAtom,_) -> GameAtom:get_requirements().
- counter(Game) -> PL = supervisor:count_children(case Game of game_okey -> okey_sup;
- game_tavla -> tavla_sup; _ -> game_sup end),
- Res = proplists:get_value(active, PL, 0),
- case Game of
- game_okey -> Res;
- game_tavla -> Res;
- _ -> 0 end.
- start() -> gen_server:start({local, ?MODULE}, ?MODULE, [], []).
- start_link() -> gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
- stop(Ref) -> gen_server:cast(Ref, stop).
- init([]) -> {ok,#state{}}.
- handle_call({get_relay, Topic}, _From, State) -> Res = get_relay_pid(Topic), {reply, Res, State};
- handle_call({game_counter, FSM}, _From, State) ->
- {reply, case FSM of game_tavla -> State#state.game_tavla; game_okey -> State#state.game_okey; _ -> 0 end, State};
- handle_call(Event, From, State) -> {stop, {unknown_call, Event, From}, State}.
- handle_cast(stop, State) -> {stop, normal, State};
- handle_cast(Event, State) -> {stop, {unknown_cast, Event}, State}.
- handle_info({'DOWN', _, process, Pid, Reason}, State) -> {noreply, State};
- handle_info(Info, State) -> {stop, {unknown_info, Info}, State}.
- terminate(_Reason, _State) -> ok.
- code_change(_OldVsn, State, _Extra) -> {ok, State}.
- game_sup_domain(Module, Params) ->
- case Module of
- game_tavla_ng_trn_paired -> tavla_sup;
- nsg_trn_standalone ->
- case proplists:get_value(game, Params) of
- game_okey -> okey_sup;
- game_tavla -> tavla_sup;
- _ -> game_sup
- end;
- nsg_trn_elimination ->
- case proplists:get_value(game_type, Params) of
- game_okey -> okey_sup;
- game_tavla -> tavla_sup;
- _ -> game_sup
- end;
- _ -> game_sup
- end.
- create_game_monitor(Topic, GameFSM, Params) ->
- Sup = game_sup_domain(GameFSM, Params),
- gas:info(?MODULE,"Create Root Game Process (Game Monitor2): ~p Params: ~p Sup: ~p",[GameFSM, Params,Sup]),
- RelayInit = Sup:start_game(GameFSM,[Topic,Params],Topic),
- gas:info(?MODULE,"RelayInit ~p",[RelayInit]),
- RelayInit.
- get_lucky_table(Game) ->
- Lucky = true,
- Check = fun(undefined, _Value) -> true;
- (Param, Value) -> Param == Value
- end,
- Cursor = fun() ->
- qlc:cursor(qlc:q([V || {{_,_,_K},_,V=#game_table{game_type=G,
- feel_lucky = L}}
- <- gproc:table(props),
- Check(Game, G),
- Check(Lucky, L)]))
- end,
- Tables = qlc:next_answers(Cursor(), 1),
- Tables.
- get_tournament(TrnId) ->
- Check = fun(undefined, _Value) -> true;
- (Param, Value) -> Param == Value
- end,
- Cursor = fun() ->
- qlc:cursor(qlc:q([V || {{_,_,_K},_, V = #game_table{trn_id=TId}} <- gproc:table(props),
- Check(TrnId, TId)]))
- end,
- Table = case qlc:next_answers(Cursor(), 1) of
- [T] -> X = T#game_table.id, X;
- _ -> []
- end,
- % gas:info(?MODULE,"~w:get_tournament Table = ~p", [?MODULE, Table]),
- Table.
- %% stress_test(NumberOfRooms) ->
- %% OkeyPlayers = [begin
- %% {ok,GameId,A} = game_manager:create_table(game_okey,[{table_name,"okey maxim and alice + 2 robots"},
- %% {speed,normal},
- %% {rounds,80},
- %% {sets,1},
- %% {game_mode,standard},
- %% {owner,"kate"}],[<<"maxim">>,<<"alice">>,robot,robot]),
- %%
- %% Clients = [ proc_lib:spawn_link(fun() ->
- %% test_okey:init_with_join_game(self(), '127.0.0.1', ?LISTEN_PORT, GameId, Id, 1, normal)
- %% end) || Id <- [<<"maxim">>,<<"alice">>] ],
- %%
- %% {ok,GameId,A}
- %%
- %%
- %% end ||X<-lists:seq(1,NumberOfRooms)],
- %% [{ok,OP1,_}|_] = OkeyPlayers,
- %% [{ok,OP2,_}|_] = lists:reverse(OkeyPlayers),
- %% gas:info(?MODULE,"Okey bot rooms runned (STRESS): ~p~n",[{OP1,OP2}]).
- create_standalone_game(Game, Params, Users) ->
- gas:info(?MODULE,"create_standalone_game/3 Params:~p", [Params]),
- case Game of
- game_okey ->
- #pointing_rule{quota = Quota,
- kakush_winner = KakushForWinners,
- kakush_other = KakushForLoser,
- game_points = WinGamePoints
- } = proplists:get_value(pointing_rules, Params),
- GameId = proplists:get_value(game_id, Params),
- TableName = proplists:get_value(table_name, Params),
- MulFactor = proplists:get_value(double_points, Params, 1),
- SlangAllowed = proplists:get_value(slang, Params, false),
- ObserversAllowed = proplists:get_value(observers, Params, false),
- Speed = proplists:get_value(speed, Params, normal),
- GameMode = proplists:get_value(game_mode, Params),
- Rounds = case GameMode of
- countdown -> undefined;
- _ -> proplists:get_value(rounds, Params, undefined)
- end,
- GostergeFinishAllowed = proplists:get_value(gosterge_finish, Params, false),
- BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
- true -> enabled;
- false -> disabled
- end,
- TableParams = [
- {table_name, TableName},
- {mult_factor, MulFactor},
- {slang_allowed, SlangAllowed},
- {observers_allowed, ObserversAllowed},
- {tournament_type, standalone},
- {round_timeout, infinity},
- %% {round_timeout, 30 * 1000},
- {set_timeout, infinity},
- %% {set_timeout, 10 * 60 *1000},
- {speed, Speed},
- {game_type, GameMode},
- {rounds, Rounds},
- {reveal_confirmation, true},
- {next_series_confirmation, no_exit},
- {pause_mode, normal},
- {social_actions_enabled, true},
- {gosterge_finish_allowed, GostergeFinishAllowed}
- ],
- create_game(GameId, nsg_trn_standalone,
- [{game, Game},
- {game_mode, GameMode},
- {game_name, TableName},
- {seats, 4},
- {registrants, Users},
- {initial_points, 0},
- {quota_per_round, Quota},
- {kakush_for_winners, KakushForWinners},
- {kakush_for_loser, KakushForLoser},
- {win_game_points, WinGamePoints},
- {mul_factor, MulFactor},
- {table_module, game_okey_table},
- {bot_module, game_okey_bot},
- {bots_replacement_mode, BotsReplacementMode},
- {table_params, TableParams},
- {common_params, Params}
- ]);
- game_tavla ->
- #pointing_rule{quota = Quota,
- kakush_winner = KakushForWinners,
- kakush_other = KakushForLoser,
- game_points = WinGamePoints
- } = proplists:get_value(pointing_rules, Params),
- GameId = proplists:get_value(game_id, Params),
- TableName = proplists:get_value(table_name, Params),
- MulFactor = proplists:get_value(double_points, Params, 1),
- SlangAllowed = proplists:get_value(slang, Params, false),
- ObserversAllowed = proplists:get_value(observers, Params, false),
- Speed = proplists:get_value(speed, Params, normal),
- GameMode = proplists:get_value(game_mode, Params),
- Rounds = case GameMode of
- _ -> proplists:get_value(rounds, Params, undefined)
- end,
- BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
- true -> enabled;
- false -> disabled
- end,
- TableParams = [
- {table_name, TableName},
- {mult_factor, MulFactor},
- {slang_allowed, SlangAllowed},
- {observers_allowed, ObserversAllowed},
- {tournament_type, standalone},
- {round_timeout, infinity},
- %% {round_timeout, 30 * 1000},
- {set_timeout, infinity},
- %% {set_timeout, 10 * 60 *1000},
- {speed, Speed},
- {game_mode, GameMode},
- {rounds, Rounds},
- {next_series_confirmation, no_exit},
- {pause_mode, normal},
- {social_actions_enabled, true},
- {tables_num, 1}
- ],
- create_game(GameId, nsg_trn_standalone,
- [{game, Game},
- {game_mode, GameMode},
- {game_name, TableName},
- {seats, 2},
- {registrants, Users},
- {initial_points, 0},
- {quota_per_round, Quota},
- {kakush_for_winners, KakushForWinners},
- {kakush_for_loser, KakushForLoser},
- {win_game_points, WinGamePoints},
- {mul_factor, MulFactor},
- {table_module, game_tavla_ng_table},
- {bot_module, game_tavla_bot},
- {bots_replacement_mode, BotsReplacementMode},
- {table_params, TableParams},
- {common_params, Params}
- ])
- end.
- create_paired_game(Game, Params, Users) ->
- gas:info(?MODULE,"create_paired_game/3 Params:~p", [Params]),
- case Game of
- game_tavla ->
- #pointing_rule{quota = Quota,
- kakush_winner = KakushForWinners,
- kakush_other = KakushForLoser,
- game_points = WinGamePoints
- } = proplists:get_value(pointing_rules, Params),
- GameId = proplists:get_value(game_id, Params),
- TableName = proplists:get_value(table_name, Params),
- MulFactor = proplists:get_value(double_points, Params, 1),
- SlangAllowed = proplists:get_value(slang, Params, false),
- ObserversAllowed = proplists:get_value(observers, Params, false),
- Speed = proplists:get_value(speed, Params, normal),
- GameMode = proplists:get_value(game_mode, Params),
- Rounds = case GameMode of
- _ -> proplists:get_value(rounds, Params, undefined)
- end,
- BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
- true -> enabled;
- false -> disabled
- end,
- TablesNum = length(Users) div 2 + length(Users) rem 2,
- TableParams = [
- {table_name, TableName},
- {mult_factor, MulFactor},
- {slang_allowed, SlangAllowed},
- {observers_allowed, ObserversAllowed},
- {tournament_type, paired},
- {round_timeout, infinity},
- {set_timeout, infinity},
- {speed, Speed},
- {game_mode, GameMode},
- {rounds, Rounds},
- {next_series_confirmation, no_exit},
- {pause_mode, disabled},
- {social_actions_enabled, true},
- {tables_num, TablesNum}
- ],
- create_game(GameId, game_tavla_ng_trn_paired,
- [{game, Game},
- {game_mode, GameMode},
- {game_name, TableName},
- {tables_num, TablesNum},
- {registrants, Users},
- {quota_per_round, Quota},
- {kakush_for_winners, KakushForWinners},
- {kakush_for_loser, KakushForLoser},
- {win_game_points, WinGamePoints},
- {mul_factor, MulFactor},
- {table_module, game_tavla_ng_table},
- {bot_module, game_tavla_bot},
- {bots_replacement_mode, BotsReplacementMode},
- {table_params, TableParams},
- {common_params, Params}
- ])
- end.
- create_elimination_trn(GameType, Params, Registrants) ->
- gas:info(?MODULE,"create_elimination_trn/3 Params:~p", [Params]),
- TrnId = proplists:get_value(trn_id, Params),
- QuotaPerRound = proplists:get_value(quota_per_round, Params),
- PlayersNumber = proplists:get_value(players_number, Params),
- Tours = proplists:get_value(tours, Params),
- GameMode = proplists:get_value(game_mode, Params),
- Speed = proplists:get_value(speed, Params),
- Awards = proplists:get_value(awards, Params),
- RegistrantsNum = length(Registrants),
- if RegistrantsNum =/= PlayersNumber ->
- ?ERROR("create_elimination_trn/3 Error: Wrong number of the registrants: ~p (required: ~p). ",
- [RegistrantsNum, PlayersNumber]),
- exit(wrong_registrants_number);
- true -> do_nothing
- end,
- {ok, Plan} = nsg_matrix_elimination:get_plan(GameType, QuotaPerRound, PlayersNumber, Tours),
- case GameType of
- game_okey ->
- Rounds = 10,
- {ok, SetTimeout} = nsm_db:get(config,"games/okey/trn/elim/tour_time_limit/"++integer_to_list(Tours), 35*60*1000),
- TableParams = [
- {table_name, ""},
- {tournament_type, elimination},
- {round_timeout, infinity},
- {set_timeout, SetTimeout},
- {speed, Speed},
- {game_type, GameMode},
- {rounds, Rounds},
- {gosterge_finish_allowed, undefined},
- {reveal_confirmation, true},
- {next_series_confirmation, no},
- {pause_mode, disabled},
- {observers_allowed, false},
- {slang_allowed, false},
- {social_actions_enabled, false},
- {mult_factor, 1}
- ],
- create_game(TrnId, nsg_trn_elimination,
- [{game_type, GameType},
- {game_mode, GameMode},
- {registrants, Registrants},
- {plan, Plan},
- {quota_per_round, QuotaPerRound},
- {rounds_per_tour, Rounds},
- {tours, Tours},
- {players_per_table, 4},
- {speed, Speed},
- {awards, Awards},
- {trn_id, TrnId},
- {table_module, game_okey_table},
- {demo_mode, false},
- {table_params, TableParams}
- ]);
- game_tavla ->
- Rounds = 3,
- {ok, SetTimeout} = nsm_db:get(config,"games/tavla/trn/elim/tour_time_limit/"++integer_to_list(Tours), 35*60*1000),
- TableParams = [
- {table_name, ""},
- {tournament_type, elimination},
- {round_timeout, infinity},
- {set_timeout, SetTimeout},
- {speed, Speed},
- {game_mode, GameMode},
- {rounds, Rounds},
- {next_series_confirmation, no},
- {pause_mode, disabled},
- {slang_allowed, false},
- {observers_allowed, false},
- {social_actions_enabled, false},
- {mult_factor, 1},
- {tables_num, 1}
- ],
- create_game(TrnId, nsg_trn_elimination,
- [{game_type, GameType},
- {game_mode, GameMode},
- {registrants, Registrants},
- {plan, Plan},
- {quota_per_round, QuotaPerRound},
- {rounds_per_tour, Rounds},
- {tours, Tours},
- {players_per_table, 2},
- {speed, Speed},
- {awards, Awards},
- {trn_id,TrnId},
- {table_module, game_tavla_ng_table},
- {demo_mode, false},
- {table_params, TableParams}
- ])
- end.
- start_tournament(TrnId,NumberOfTournaments,NumberOfPlayers,_Quota,_Tours,_Speed,GiftIds) ->
- gas:info(?MODULE,"START TOURNAMENT: ~p",[{TrnId,NumberOfTournaments,NumberOfPlayers,_Quota,_Tours,_Speed,GiftIds}]),
- {ok,Tournament} = nsm_db:get(tournament,TrnId),
- RealPlayersUnsorted = nsm_tournaments:joined_users(TrnId),
- if NumberOfPlayers - length(RealPlayersUnsorted) > 300 ->
- nsm_db:put(Tournament#tournament{status=canceled}),
- wf:send([tournament, TrnId, cancel], {TrnId}),
- error;
- true ->
- #tournament{quota = QuotaPerRound,
- tours = Tours,
- game_type = GameType,
- game_mode = GameMode,
- speed = Speed} = Tournament,
- RealPlayersPR = lists:keysort(#play_record.other, RealPlayersUnsorted),
- gas:info(?MODULE,"Head: ~p",[hd(RealPlayersPR)]),
- RealPlayers = [list_to_binary(Who)||#play_record{who=Who}<-RealPlayersPR, Who /= undefined],
- %% Registrants = case NumberOfPlayers > length(RealPlayers) of
- %% true -> nsm_db:put(Tournament#tournament{status=canceled}), RealPlayers;
- %% false -> [lists:nth(N,RealPlayers)||N<-lists:seq(1,NumberOfPlayers)] end,
- RealPlayersNumber = length(RealPlayers),
- Registrants = if NumberOfPlayers == RealPlayersNumber -> RealPlayers;
- NumberOfPlayers > RealPlayersNumber ->
- RealPlayers ++ [list_to_binary(fake_users:ima_gio(N)) ||
- N <- lists:seq(1, NumberOfPlayers-RealPlayersNumber)];
- true -> lists:sublist(RealPlayers, NumberOfPlayers)
- end,
- gas:info(?MODULE,"Registrants: ~p",[Registrants]),
- OkeyTournaments =
- [begin
- Params = [{trn_id, TrnId},
- {quota_per_round, QuotaPerRound},
- {players_number, NumberOfPlayers},
- {tours, Tours},
- {game_mode, GameMode},
- {speed, Speed},
- {awards, GiftIds}],
- {ok,GameId,A} = create_elimination_trn(GameType, Params, Registrants),
- nsm_db:put(Tournament#tournament{status=activated,start_time=time()}),
- wf:send([tournament, TrnId, activate], {TrnId}),
- {ok,GameId,A}
- end || _ <-lists:seq(1,NumberOfTournaments)],
- [{ok,OP1,_}|_] = OkeyTournaments,
- [{ok,OP2,_}|_] = lists:reverse(OkeyTournaments),
- gas:info(?MODULE,"Okey tournaments runned: ~p~n",[{OP1,OP2}]),
- OP1
- end.
- get_tables(Id) ->
- qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{id = _Id}} <- gproc:table(props), Id == _Id ])).
- qlc_id(Id) ->
- qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{gameid = _GameId, id = _Id,
- owner = _Owner, creator = _Creator}} <-
- gproc:table(props), Id == _Id])).
- qlc_id_creator(Id,Creator,Owner) ->
- qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{gameid = _GameId, id = _Id,
- owner = _Owner, creator = _Creator}} <-
- gproc:table(props), Id == _Id, Creator == _Creator, Owner ==_Owner])).
|