game.erl 24 KB

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