game_manager.erl 23 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498
  1. -module(game_manager).
  2. -behaviour(gen_server).
  3. -author('Maxim Sokhatsky <maxim@synrc.com>').
  4. -compile(export_all).
  5. -export([init/1, start/0, start_link/0, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3]).
  6. -include_lib("server/include/requests.hrl").
  7. -include_lib("server/include/conf.hrl").
  8. -include_lib("db/include/table.hrl").
  9. -include_lib("db/include/tournaments.hrl").
  10. -include_lib("server/include/log.hrl").
  11. -include_lib("stdlib/include/qlc.hrl").
  12. -include_lib("db/include/scoring.hrl").
  13. -record(state, { game_tavla = 0, game_okey = 0 }).
  14. online() -> [X||X<-qlc:e(gproc:table()),element(1,X)=={p,l,broadcast}].
  15. get_all_games_ids() ->
  16. [GameId || {_, _, #game_table{id = GameId, game_type = game_okey}} <- qlc:e(gproc:table())].
  17. destroy_game(Pid,Sup) -> game_sup:stop_game(Sup,Pid).
  18. gen_game_id() ->
  19. PoolNum = wf:config(nsx_idgen,game_pool,5000000) div 1000000,
  20. PoolNumStr = integer_to_list(PoolNum),
  21. PoolNum*1000000 + 200 + kvs:next_id("game_table", 1).
  22. %% 200 is reserved for lucky games and for already created games
  23. create_game(GameId, GameFSM, Params) ->
  24. {ok, Pid} = create_game_monitor(GameId, GameFSM, Params),
  25. {ok, GameId, Pid}.
  26. %% rank_table(GameId) -> {ok, {LastTourNum, TourResult}} | {error, Reason}
  27. %% TourResult = {UserId, Pos, Points, Status}
  28. rank_table(GameId) ->
  29. case get_relay_mod_pid(GameId) of
  30. {Module, Pid} -> Module:system_request(Pid, last_tour_result);
  31. undefined -> {error, not_found}
  32. end.
  33. get_lucky_pid(Sup) ->
  34. [X]=game_manager:get_lucky_table(Sup),
  35. X#game_table.game_process.
  36. get_relay_pid(GameId) -> case get_tables(GameId) of [] -> undefined;
  37. [#game_table{game_process = P} | _] -> gas:info(?MODULE,"GameRelay: ~p",[P]), P end.
  38. get_relay_mod_pid(GameId) -> case get_tables(GameId) of [] -> undefined;
  39. [#game_table{game_process = P, game_module = M} | _] -> gas:info(?MODULE,"GameRelay: ~p",[{M,P}]), {M,P} end.
  40. get_relay(GameId) -> gen_server:call(?MODULE, {get_relay, GameId}).
  41. game_requirements(GameAtom) -> GameAtom:get_requirements().
  42. game_requirements(game_tavla,paired) -> paired_tavla:get_requirements();
  43. game_requirements(GameAtom,_) -> GameAtom:get_requirements().
  44. counter(Game) -> PL = supervisor:count_children(case Game of game_okey -> okey_sup;
  45. game_tavla -> tavla_sup; _ -> game_sup end),
  46. Res = proplists:get_value(active, PL, 0),
  47. case Game of
  48. game_okey -> Res;
  49. game_tavla -> Res;
  50. _ -> 0 end.
  51. start() -> gen_server:start({local, ?MODULE}, ?MODULE, [], []).
  52. start_link() -> gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
  53. stop(Ref) -> gen_server:cast(Ref, stop).
  54. init([]) -> {ok,#state{}}.
  55. handle_call({get_relay, Topic}, _From, State) -> Res = get_relay_pid(Topic), {reply, Res, State};
  56. handle_call({game_counter, FSM}, _From, State) ->
  57. {reply, case FSM of game_tavla -> State#state.game_tavla; game_okey -> State#state.game_okey; _ -> 0 end, State};
  58. handle_call(Event, From, State) -> {stop, {unknown_call, Event, From}, State}.
  59. handle_cast(stop, State) -> {stop, normal, State};
  60. handle_cast(Event, State) -> {stop, {unknown_cast, Event}, State}.
  61. handle_info({'DOWN', _, process, Pid, Reason}, State) -> {noreply, State};
  62. handle_info(Info, State) -> {stop, {unknown_info, Info}, State}.
  63. terminate(_Reason, _State) -> ok.
  64. code_change(_OldVsn, State, _Extra) -> {ok, State}.
  65. game_sup_domain(Module, Params) ->
  66. case Module of
  67. game_tavla_ng_trn_paired -> tavla_sup;
  68. nsg_trn_standalone ->
  69. case proplists:get_value(game, Params) of
  70. game_okey -> okey_sup;
  71. game_tavla -> tavla_sup;
  72. _ -> game_sup
  73. end;
  74. nsg_trn_elimination ->
  75. case proplists:get_value(game_type, Params) of
  76. game_okey -> okey_sup;
  77. game_tavla -> tavla_sup;
  78. _ -> game_sup
  79. end;
  80. _ -> game_sup
  81. end.
  82. create_game_monitor(Topic, GameFSM, Params) ->
  83. Sup = game_sup_domain(GameFSM, Params),
  84. gas:info(?MODULE,"Create Root Game Process (Game Monitor2): ~p Params: ~p Sup: ~p",[GameFSM, Params,Sup]),
  85. RelayInit = Sup:start_game(GameFSM,[Topic,Params],Topic),
  86. gas:info(?MODULE,"RelayInit ~p",[RelayInit]),
  87. RelayInit.
  88. get_lucky_table(Game) ->
  89. Lucky = true,
  90. Check = fun(undefined, _Value) -> true;
  91. (Param, Value) -> Param == Value
  92. end,
  93. Cursor = fun() ->
  94. qlc:cursor(qlc:q([V || {{_,_,_K},_,V=#game_table{game_type=G,
  95. feel_lucky = L}}
  96. <- gproc:table(props),
  97. Check(Game, G),
  98. Check(Lucky, L)]))
  99. end,
  100. Tables = qlc:next_answers(Cursor(), 1),
  101. Tables.
  102. get_tournament(TrnId) ->
  103. Check = fun(undefined, _Value) -> true;
  104. (Param, Value) -> Param == Value
  105. end,
  106. Cursor = fun() ->
  107. qlc:cursor(qlc:q([V || {{_,_,_K},_, V = #game_table{trn_id=TId}} <- gproc:table(props),
  108. Check(TrnId, TId)]))
  109. end,
  110. Table = case qlc:next_answers(Cursor(), 1) of
  111. [T] -> X = T#game_table.id, X;
  112. _ -> []
  113. end,
  114. % gas:info(?MODULE,"~w:get_tournament Table = ~p", [?MODULE, Table]),
  115. Table.
  116. %% stress_test(NumberOfRooms) ->
  117. %% OkeyPlayers = [begin
  118. %% {ok,GameId,A} = game_manager:create_table(game_okey,[{table_name,"okey maxim and alice + 2 robots"},
  119. %% {speed,normal},
  120. %% {rounds,80},
  121. %% {sets,1},
  122. %% {game_mode,standard},
  123. %% {owner,"kate"}],[<<"maxim">>,<<"alice">>,robot,robot]),
  124. %%
  125. %% Clients = [ proc_lib:spawn_link(fun() ->
  126. %% test_okey:init_with_join_game(self(), '127.0.0.1', ?LISTEN_PORT, GameId, Id, 1, normal)
  127. %% end) || Id <- [<<"maxim">>,<<"alice">>] ],
  128. %%
  129. %% {ok,GameId,A}
  130. %%
  131. %%
  132. %% end ||X<-lists:seq(1,NumberOfRooms)],
  133. %% [{ok,OP1,_}|_] = OkeyPlayers,
  134. %% [{ok,OP2,_}|_] = lists:reverse(OkeyPlayers),
  135. %% gas:info(?MODULE,"Okey bot rooms runned (STRESS): ~p~n",[{OP1,OP2}]).
  136. create_standalone_game(Game, Params, Users) ->
  137. gas:info(?MODULE,"create_standalone_game/3 Params:~p", [Params]),
  138. case Game of
  139. game_okey ->
  140. #pointing_rule{quota = Quota,
  141. kakush_winner = KakushForWinners,
  142. kakush_other = KakushForLoser,
  143. game_points = WinGamePoints
  144. } = proplists:get_value(pointing_rules, Params),
  145. GameId = proplists:get_value(game_id, Params),
  146. TableName = proplists:get_value(table_name, Params),
  147. MulFactor = proplists:get_value(double_points, Params, 1),
  148. SlangAllowed = proplists:get_value(slang, Params, false),
  149. ObserversAllowed = proplists:get_value(observers, Params, false),
  150. Speed = proplists:get_value(speed, Params, normal),
  151. GameMode = proplists:get_value(game_mode, Params),
  152. Rounds = case GameMode of
  153. countdown -> undefined;
  154. _ -> proplists:get_value(rounds, Params, undefined)
  155. end,
  156. GostergeFinishAllowed = proplists:get_value(gosterge_finish, Params, false),
  157. BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
  158. true -> enabled;
  159. false -> disabled
  160. end,
  161. TableParams = [
  162. {table_name, TableName},
  163. {mult_factor, MulFactor},
  164. {slang_allowed, SlangAllowed},
  165. {observers_allowed, ObserversAllowed},
  166. {tournament_type, standalone},
  167. {round_timeout, infinity},
  168. %% {round_timeout, 30 * 1000},
  169. {set_timeout, infinity},
  170. %% {set_timeout, 10 * 60 *1000},
  171. {speed, Speed},
  172. {game_type, GameMode},
  173. {rounds, Rounds},
  174. {reveal_confirmation, true},
  175. {next_series_confirmation, no_exit},
  176. {pause_mode, normal},
  177. {social_actions_enabled, true},
  178. {gosterge_finish_allowed, GostergeFinishAllowed}
  179. ],
  180. create_game(GameId, nsg_trn_standalone,
  181. [{game, Game},
  182. {game_mode, GameMode},
  183. {game_name, TableName},
  184. {seats, 4},
  185. {registrants, Users},
  186. {initial_points, 0},
  187. {quota_per_round, Quota},
  188. {kakush_for_winners, KakushForWinners},
  189. {kakush_for_loser, KakushForLoser},
  190. {win_game_points, WinGamePoints},
  191. {mul_factor, MulFactor},
  192. {table_module, game_okey_table},
  193. {bot_module, game_okey_bot},
  194. {bots_replacement_mode, BotsReplacementMode},
  195. {table_params, TableParams},
  196. {common_params, Params}
  197. ]);
  198. game_tavla ->
  199. #pointing_rule{quota = Quota,
  200. kakush_winner = KakushForWinners,
  201. kakush_other = KakushForLoser,
  202. game_points = WinGamePoints
  203. } = proplists:get_value(pointing_rules, Params),
  204. GameId = proplists:get_value(game_id, Params),
  205. TableName = proplists:get_value(table_name, Params),
  206. MulFactor = proplists:get_value(double_points, Params, 1),
  207. SlangAllowed = proplists:get_value(slang, Params, false),
  208. ObserversAllowed = proplists:get_value(observers, Params, false),
  209. Speed = proplists:get_value(speed, Params, normal),
  210. GameMode = proplists:get_value(game_mode, Params),
  211. Rounds = case GameMode of
  212. _ -> proplists:get_value(rounds, Params, undefined)
  213. end,
  214. BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
  215. true -> enabled;
  216. false -> disabled
  217. end,
  218. TableParams = [
  219. {table_name, TableName},
  220. {mult_factor, MulFactor},
  221. {slang_allowed, SlangAllowed},
  222. {observers_allowed, ObserversAllowed},
  223. {tournament_type, standalone},
  224. {round_timeout, infinity},
  225. %% {round_timeout, 30 * 1000},
  226. {set_timeout, infinity},
  227. %% {set_timeout, 10 * 60 *1000},
  228. {speed, Speed},
  229. {game_mode, GameMode},
  230. {rounds, Rounds},
  231. {next_series_confirmation, no_exit},
  232. {pause_mode, normal},
  233. {social_actions_enabled, true},
  234. {tables_num, 1}
  235. ],
  236. create_game(GameId, nsg_trn_standalone,
  237. [{game, Game},
  238. {game_mode, GameMode},
  239. {game_name, TableName},
  240. {seats, 2},
  241. {registrants, Users},
  242. {initial_points, 0},
  243. {quota_per_round, Quota},
  244. {kakush_for_winners, KakushForWinners},
  245. {kakush_for_loser, KakushForLoser},
  246. {win_game_points, WinGamePoints},
  247. {mul_factor, MulFactor},
  248. {table_module, game_tavla_ng_table},
  249. {bot_module, game_tavla_bot},
  250. {bots_replacement_mode, BotsReplacementMode},
  251. {table_params, TableParams},
  252. {common_params, Params}
  253. ])
  254. end.
  255. create_paired_game(Game, Params, Users) ->
  256. gas:info(?MODULE,"create_paired_game/3 Params:~p", [Params]),
  257. case Game of
  258. game_tavla ->
  259. #pointing_rule{quota = Quota,
  260. kakush_winner = KakushForWinners,
  261. kakush_other = KakushForLoser,
  262. game_points = WinGamePoints
  263. } = proplists:get_value(pointing_rules, Params),
  264. GameId = proplists:get_value(game_id, Params),
  265. TableName = proplists:get_value(table_name, Params),
  266. MulFactor = proplists:get_value(double_points, Params, 1),
  267. SlangAllowed = proplists:get_value(slang, Params, false),
  268. ObserversAllowed = proplists:get_value(observers, Params, false),
  269. Speed = proplists:get_value(speed, Params, normal),
  270. GameMode = proplists:get_value(game_mode, Params),
  271. Rounds = case GameMode of
  272. _ -> proplists:get_value(rounds, Params, undefined)
  273. end,
  274. BotsReplacementMode = case proplists:get_value(robots_replacement_allowed, Params, true) of
  275. true -> enabled;
  276. false -> disabled
  277. end,
  278. TablesNum = length(Users) div 2 + length(Users) rem 2,
  279. TableParams = [
  280. {table_name, TableName},
  281. {mult_factor, MulFactor},
  282. {slang_allowed, SlangAllowed},
  283. {observers_allowed, ObserversAllowed},
  284. {tournament_type, paired},
  285. {round_timeout, infinity},
  286. {set_timeout, infinity},
  287. {speed, Speed},
  288. {game_mode, GameMode},
  289. {rounds, Rounds},
  290. {next_series_confirmation, no_exit},
  291. {pause_mode, disabled},
  292. {social_actions_enabled, true},
  293. {tables_num, TablesNum}
  294. ],
  295. create_game(GameId, game_tavla_ng_trn_paired,
  296. [{game, Game},
  297. {game_mode, GameMode},
  298. {game_name, TableName},
  299. {tables_num, TablesNum},
  300. {registrants, Users},
  301. {quota_per_round, Quota},
  302. {kakush_for_winners, KakushForWinners},
  303. {kakush_for_loser, KakushForLoser},
  304. {win_game_points, WinGamePoints},
  305. {mul_factor, MulFactor},
  306. {table_module, game_tavla_ng_table},
  307. {bot_module, game_tavla_bot},
  308. {bots_replacement_mode, BotsReplacementMode},
  309. {table_params, TableParams},
  310. {common_params, Params}
  311. ])
  312. end.
  313. create_elimination_trn(GameType, Params, Registrants) ->
  314. gas:info(?MODULE,"create_elimination_trn/3 Params:~p", [Params]),
  315. TrnId = proplists:get_value(trn_id, Params),
  316. QuotaPerRound = proplists:get_value(quota_per_round, Params),
  317. PlayersNumber = proplists:get_value(players_number, Params),
  318. Tours = proplists:get_value(tours, Params),
  319. GameMode = proplists:get_value(game_mode, Params),
  320. Speed = proplists:get_value(speed, Params),
  321. Awards = proplists:get_value(awards, Params),
  322. RegistrantsNum = length(Registrants),
  323. if RegistrantsNum =/= PlayersNumber ->
  324. ?ERROR("create_elimination_trn/3 Error: Wrong number of the registrants: ~p (required: ~p). ",
  325. [RegistrantsNum, PlayersNumber]),
  326. exit(wrong_registrants_number);
  327. true -> do_nothing
  328. end,
  329. {ok, Plan} = nsg_matrix_elimination:get_plan(GameType, QuotaPerRound, PlayersNumber, Tours),
  330. case GameType of
  331. game_okey ->
  332. Rounds = 10,
  333. {ok, SetTimeout} = nsm_db:get(config,"games/okey/trn/elim/tour_time_limit/"++integer_to_list(Tours), 35*60*1000),
  334. TableParams = [
  335. {table_name, ""},
  336. {tournament_type, elimination},
  337. {round_timeout, infinity},
  338. {set_timeout, SetTimeout},
  339. {speed, Speed},
  340. {game_type, GameMode},
  341. {rounds, Rounds},
  342. {gosterge_finish_allowed, undefined},
  343. {reveal_confirmation, true},
  344. {next_series_confirmation, no},
  345. {pause_mode, disabled},
  346. {observers_allowed, false},
  347. {slang_allowed, false},
  348. {social_actions_enabled, false},
  349. {mult_factor, 1}
  350. ],
  351. create_game(TrnId, nsg_trn_elimination,
  352. [{game_type, GameType},
  353. {game_mode, GameMode},
  354. {registrants, Registrants},
  355. {plan, Plan},
  356. {quota_per_round, QuotaPerRound},
  357. {rounds_per_tour, Rounds},
  358. {tours, Tours},
  359. {players_per_table, 4},
  360. {speed, Speed},
  361. {awards, Awards},
  362. {trn_id, TrnId},
  363. {table_module, game_okey_table},
  364. {demo_mode, false},
  365. {table_params, TableParams}
  366. ]);
  367. game_tavla ->
  368. Rounds = 3,
  369. {ok, SetTimeout} = nsm_db:get(config,"games/tavla/trn/elim/tour_time_limit/"++integer_to_list(Tours), 35*60*1000),
  370. TableParams = [
  371. {table_name, ""},
  372. {tournament_type, elimination},
  373. {round_timeout, infinity},
  374. {set_timeout, SetTimeout},
  375. {speed, Speed},
  376. {game_mode, GameMode},
  377. {rounds, Rounds},
  378. {next_series_confirmation, no},
  379. {pause_mode, disabled},
  380. {slang_allowed, false},
  381. {observers_allowed, false},
  382. {social_actions_enabled, false},
  383. {mult_factor, 1},
  384. {tables_num, 1}
  385. ],
  386. create_game(TrnId, nsg_trn_elimination,
  387. [{game_type, GameType},
  388. {game_mode, GameMode},
  389. {registrants, Registrants},
  390. {plan, Plan},
  391. {quota_per_round, QuotaPerRound},
  392. {rounds_per_tour, Rounds},
  393. {tours, Tours},
  394. {players_per_table, 2},
  395. {speed, Speed},
  396. {awards, Awards},
  397. {trn_id,TrnId},
  398. {table_module, game_tavla_ng_table},
  399. {demo_mode, false},
  400. {table_params, TableParams}
  401. ])
  402. end.
  403. start_tournament(TrnId,NumberOfTournaments,NumberOfPlayers,_Quota,_Tours,_Speed,GiftIds) ->
  404. gas:info(?MODULE,"START TOURNAMENT: ~p",[{TrnId,NumberOfTournaments,NumberOfPlayers,_Quota,_Tours,_Speed,GiftIds}]),
  405. {ok,Tournament} = nsm_db:get(tournament,TrnId),
  406. RealPlayersUnsorted = nsm_tournaments:joined_users(TrnId),
  407. if NumberOfPlayers - length(RealPlayersUnsorted) > 300 ->
  408. nsm_db:put(Tournament#tournament{status=canceled}),
  409. wf:send([tournament, TrnId, cancel], {TrnId}),
  410. error;
  411. true ->
  412. #tournament{quota = QuotaPerRound,
  413. tours = Tours,
  414. game_type = GameType,
  415. game_mode = GameMode,
  416. speed = Speed} = Tournament,
  417. RealPlayersPR = lists:keysort(#play_record.other, RealPlayersUnsorted),
  418. gas:info(?MODULE,"Head: ~p",[hd(RealPlayersPR)]),
  419. RealPlayers = [list_to_binary(Who)||#play_record{who=Who}<-RealPlayersPR, Who /= undefined],
  420. %% Registrants = case NumberOfPlayers > length(RealPlayers) of
  421. %% true -> nsm_db:put(Tournament#tournament{status=canceled}), RealPlayers;
  422. %% false -> [lists:nth(N,RealPlayers)||N<-lists:seq(1,NumberOfPlayers)] end,
  423. RealPlayersNumber = length(RealPlayers),
  424. Registrants = if NumberOfPlayers == RealPlayersNumber -> RealPlayers;
  425. NumberOfPlayers > RealPlayersNumber ->
  426. RealPlayers ++ [list_to_binary(fake_users:ima_gio(N)) ||
  427. N <- lists:seq(1, NumberOfPlayers-RealPlayersNumber)];
  428. true -> lists:sublist(RealPlayers, NumberOfPlayers)
  429. end,
  430. gas:info(?MODULE,"Registrants: ~p",[Registrants]),
  431. OkeyTournaments =
  432. [begin
  433. Params = [{trn_id, TrnId},
  434. {quota_per_round, QuotaPerRound},
  435. {players_number, NumberOfPlayers},
  436. {tours, Tours},
  437. {game_mode, GameMode},
  438. {speed, Speed},
  439. {awards, GiftIds}],
  440. {ok,GameId,A} = create_elimination_trn(GameType, Params, Registrants),
  441. nsm_db:put(Tournament#tournament{status=activated,start_time=time()}),
  442. wf:send([tournament, TrnId, activate], {TrnId}),
  443. {ok,GameId,A}
  444. end || _ <-lists:seq(1,NumberOfTournaments)],
  445. [{ok,OP1,_}|_] = OkeyTournaments,
  446. [{ok,OP2,_}|_] = lists:reverse(OkeyTournaments),
  447. gas:info(?MODULE,"Okey tournaments runned: ~p~n",[{OP1,OP2}]),
  448. OP1
  449. end.
  450. get_tables(Id) ->
  451. qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{id = _Id}} <- gproc:table(props), Id == _Id ])).
  452. qlc_id(Id) ->
  453. qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{gameid = _GameId, id = _Id,
  454. owner = _Owner, creator = _Creator}} <-
  455. gproc:table(props), Id == _Id])).
  456. qlc_id_creator(Id,Creator,Owner) ->
  457. qlc:e(qlc:q([Val || {{_,_,_Key},_,Val=#game_table{gameid = _GameId, id = _Id,
  458. owner = _Owner, creator = _Creator}} <-
  459. gproc:table(props), Id == _Id, Creator == _Creator, Owner ==_Owner])).