Prolog program of NBA example file (Relational/NBA).

Example taken from relational.fit.cvut.cz


?- induce_lift([f1,f2,f3,f4],P),test_lift(P,[f5],LL,AUCROC,ROC,AUCPR,PR). % learn the structure and the parameters and test the result ?- induce_lift([f1,f2,f3,f4,f5],P). */

   10%%
   11
   12:-use_module(library(liftcover)).   13
   14%:- if(current_predicate(use_rendering/1)).
   15%:- use_rendering(c3).
   16%:- use_rendering(lpad).
   17%:- endif.
   18
   19:-lift.   20
   21:- set_lift(neg_ex,given).   22:- set_lift(megaex_bottom,4).   23:- set_lift(max_iter,20).   24:- set_lift(max_var,100).   25:- set_lift(maxdepth_var,20). %da inserire nel tutorial
   26:- set_lift(verbosity,0).   27
   28
   29fold(f1,[1,2,3,4,5,6]).
   30fold(f2,[7,8,9,10,11,12]).
   31fold(f3,[15,13,14,16,17,18]).
   32fold(f4,[19,20,21,22,23,24]).
   33fold(f5,[27,28,29,30,25,26]).
   34
   35
   36output(game/3).    % game(GameId,Team1Id,Team2Id,ResultOfTeam1,URL,Date).
   37input(actions/21). % actions(GameId,TeamId,PlayerId,...
   38input(player/2).   % player(PlayerId,PlayerName).
   39input(team/2).     % team(TeamId,TeamName).
   40
   41%modeh(1,win1).
   42
   43
   44modeh(1,game(+teamId,+teamId,-#resulteam1)).
   45%modeh(1,game(+teamId,+teamId,-#resulteam1,+url,+date)).
   46
   47%------- nessun istanziato --------%
   48%modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   49
   50%------- una var istanziata --------%
   51
   52modeb(3,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   53/*
   54modeb(1,actions(+teamId,-playerId,-#minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   55
   56modeb(1,actions(+teamId,-playerId,-minutes,-#fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   57
   58modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-#fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   59
   60modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-#threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   61
   62modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-#threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   63
   64modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-#freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   65
   66modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -#freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   67
   68modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-#plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   69
   70modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-#offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   71
   72modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-#defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   73
   74modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-#totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   75
   76modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-#assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   77
   78modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-#personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   79
   80modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-#steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   81
   82modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-#turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   83
   84modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-#blockedShots,-blocksAgainst,-points,-starter)).
   85
   86modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-#blocksAgainst,-points,-starter)).
   87
   88modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-#points,-starter)).
   89
   90modeb(1,actions(+teamId,-playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-#starter)).
   91*/
   92
   93%------- playerID istanziato + una var istanziata --------%
   94/*
   95modeb(1,actions(+teamId,-#playerId,-#minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   96
   97modeb(1,actions(+teamId,-#playerId,-minutes,-#fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
   98
   99modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-#fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  100
  101modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-#threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  102
  103modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-#threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  104
  105modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-#freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  106
  107modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -#freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  108
  109modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-#plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  110
  111modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-#offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  112
  113modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-#defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  114
  115modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-#totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  116
  117modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-#assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  118
  119modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-#personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  120
  121modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-#steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  122
  123modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-#turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  124
  125modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-#blockedShots,-blocksAgainst,-points,-starter)).
  126
  127modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-#blocksAgainst,-points,-starter)).
  128
  129modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-#points,-starter)).
  130
  131modeb(1,actions(+teamId,-#playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-#starter)).
  132*/
  133%------- tutto istanziato --------%
  134
  135%modeb(1,actions(+teamId,-#playerId,-#minutes,-#fieldGoalsMade,-#fieldGoalAttempts,-#threePointsMade,-#threePointAttempts,-#freeThrowsMade, -#freeThrowAttempts,-#plusMinus,-#offensiveRebounds,-#defensiveRebounds,-#totalRebounds,-#assists,-#personalFouls,-#steals,-#turnovers,-#blockedShots,-#blocksAgainst,-#points,-#starter)).
  136
  137
  138%------- playerID input --------%
  139
  140%modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  141
  142%------- playerID input + una var istanziata --------%
  143/*
  144modeb(1,actions(+teamId,+playerId,-#minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  145
  146modeb(1,actions(+teamId,+playerId,-minutes,-#fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  147
  148modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-#fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  149
  150modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-#threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  151
  152modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-#threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  153
  154modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-#freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  155
  156modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -#freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  157
  158modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-#plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  159
  160modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-#offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  161
  162modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-#defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  163
  164modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-#totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  165
  166modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-#assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  167
  168modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-#personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  169
  170modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-#steals,-turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  171
  172modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-#turnovers,-blockedShots,-blocksAgainst,-points,-starter)).
  173
  174modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-#blockedShots,-blocksAgainst,-points,-starter)).
  175
  176modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-#blocksAgainst,-points,-starter)).
  177
  178modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-#points,-starter)).
  179
  180modeb(1,actions(+teamId,+playerId,-minutes,-fieldGoalsMade,-fieldGoalAttempts,-threePointsMade,-threePointAttempts,-freeThrowsMade, -freeThrowAttempts,-plusMinus,-offensiveRebounds,-defensiveRebounds,-totalRebounds,-assists,-personalFouls,-steals,-turnovers,-blockedShots,-blocksAgainst,-points,-#starter)).
  181*/
  182
  183%------- playerID input + tutto istanziato --------%
  184
  185%modeb(1,actions(+teamId,+playerId,-#minutes,-#fieldGoalsMade,-#fieldGoalAttempts,-#threePointsMade,-#threePointAttempts,-#freeThrowsMade, -#freeThrowAttempts,-#plusMinus,-#offensiveRebounds,-#defensiveRebounds,-#totalRebounds,-#assists,-#personalFouls,-#steals,-#turnovers,-#blockedShots,-#blocksAgainst,-#points,-#starter)).
  186
  187
  188modeb(3,player(+playerId,-#pname)).
  189modeb(3,team(+teamId,-#tname)).
  190
  191
  192determination(game/3,actions/21).
  193determination(game/3,player/2).
  194determination(game/3,team/2).
  195
  196
  197
  198
  199
  200% Game information
  201%%
  202% predicate: game_k(GameId,ResultOfTeam1).
  203
  204%game_k(1).
  205%game_k(2).
  206%game_k(3).
  207%game_k(4).
  208%game_k(10).
  209%game_k(11).
  210%game_k(15).
  211%game_k(19).
  212%game_k(20).
  213%game_k(23).
  214%game_k(24).
  215%game_k(27).
  216%game_k(28).
  217%game_k(29).
  218%game_k(30).
  219%
  220%neg(game_k(5)).
  221%neg(game_k(6)).
  222%neg(game_k(7)).
  223%neg(game_k(8)).
  224%neg(game_k(9)).
  225%neg(game_k(12)).
  226%neg(game_k(13)).
  227%neg(game_k(14)).
  228%neg(game_k(16)).
  229%neg(game_k(17)).
  230%neg(game_k(18)).
  231%neg(game_k(21)).
  232%neg(game_k(22)).
  233%neg(game_k(25)).
  234%neg(game_k(26)).
  235
  236
  237%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  238% Game information
  239%%
  240% predicate: game(GameId,Team1Id,Team2Id,ResultOfTeam1,URL,Date).
  241game(M,T1,T2,Res):-
  242  game(M,T1,T2,Res,_,_).
  243
  244neg(game(M,T1,T2,Res)):-
  245    neg(game(M,T1,T2,Res,_,_)).
  246  
  247game(1,7,8,1,"http://www.nba.com/games/20140331/NYKUTA/gameinfo.html","2014-03-31 00:00:00").
  248game(2,9,10,1,"http://www.nba.com/games/20140331/MEMDEN/gameinfo.html","2014-03-31 00:00:00").
  249game(3,11,12,1,"http://www.nba.com/games/20140331/SACNOP/gameinfo.html","2014-03-31 00:00:00").
  250game(4,13,14,1,"http://www.nba.com/games/20140331/LACMIN/gameinfo.html","2014-03-31 00:00:00").
  251neg(game(5,15,16,-1,"http://www.nba.com/games/20140331/BOSCHI/gameinfo.html","2014-03-31 00:00:00")).
  252neg(game(6,17,18,-1,"http://www.nba.com/games/20140331/TORMIA/gameinfo.html","2014-03-31 00:00:00")).
  253neg(game(7,19,20,-1,"http://www.nba.com/games/20140331/MILDET/gameinfo.html","2014-03-31 00:00:00")).
  254neg(game(8,21,22,-1,"http://www.nba.com/games/20140331/PHIATL/gameinfo.html","2014-03-31 00:00:00")).
  255neg(game(9,23,24,-1,"http://www.nba.com/games/20140331/WASCHA/gameinfo.html","2014-03-31 00:00:00")).
  256game(10,1,2,1,"http://www.nba.com/games/20140401/PORLAL/gameinfo.html?ls=slt","2014-04-01 00:00:00").
  257game(11,3,4,1,"http://www.nba.com/games/20140401/GSWDAL/gameinfo.html?ls=slt","2014-04-01 00:00:00").
  258neg(game(12,5,6,-1,"http://www.nba.com/games/20140401/HOUBKN/gameinfo.html?ls=slt","2014-04-01 00:00:00")).
  259neg(game(13,20,25,-1,"http://www.nba.com/games/20140402/DETIND/gameinfo.html","2014-04-02 00:00:00")).
  260neg(game(14,6,7,-1,"http://www.nba.com/games/20140402/BKNNYK/gameinfo.html","2014-04-02 00:00:00")).
  261game(15,26,27,1,"http://www.nba.com/games/20140402/CLEORL/gameinfo.html","2014-04-02 00:00:00").
  262neg(game(16,21,24,-1,"http://www.nba.com/games/20140402/CHAPHI/gameinfo.html","2014-04-02 00:00:00")).
  263neg(game(17,5,17,-1,"http://www.nba.com/games/20140402/HOUTOR/gameinfo.html","2014-04-02 00:00:00")).
  264neg(game(18,15,23,-1,"http://www.nba.com/games/20140402/BOSWAS/gameinfo.html","2014-04-02 00:00:00")).
  265game(19,16,22,1,"http://www.nba.com/games/20140402/CHIATL/gameinfo.html","2014-04-02 00:00:00").
  266game(20,18,19,1,"http://www.nba.com/games/20140402/MILMIA/gameinfo.html","2014-04-02 00:00:00").
  267neg(game(21,9,14,-1,"http://www.nba.com/games/20140402/MEMMIN/gameinfo.html","2014-04-02 00:00:00")).
  268neg(game(22,3,28,-1,"http://www.nba.com/games/20140402/GSWSAS/gameinfo.html","2014-04-02 00:00:00")).
  269game(23,10,12,1,"http://www.nba.com/games/20140402/NOPDEN/gameinfo.html","2014-04-02 00:00:00").
  270game(24,13,29,1,"http://www.nba.com/games/20140402/LACPHX/gameinfo.html","2014-04-02 00:00:00").
  271neg(game(25,2,11,-1,"http://www.nba.com/games/20140402/LALSAC/gameinfo.html","2014-04-02 00:00:00")).
  272neg(game(26,28,30,-1,"http://www.nba.com/games/20140403/SASOKC/gameinfo.html","2014-04-03 00:00:00")).
  273game(27,4,13,1,"http://www.nba.com/games/20140403/DALLAC/gameinfo.html","2014-04-03 00:00:00").
  274game(28,9,10,1,"http://www.nba.com/games/20140404/DENMEM/gameinfo.html","2014-04-04 00:00:00").
  275game(29,24,27,1,"http://www.nba.com/games/20140404/ORLCHA/gameinfo.html","2014-04-04 00:00:00").
  276game(30,17,25,1,"http://www.nba.com/games/20140404/INDTOR/gameinfo.html","2014-04-04 00:00:00").
  277%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  278
  279%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  280% Actions type information
  281%%
  282% predicate: actions(GameId,TeamId,PlayerId,Minutes,FieldGoalsMade,FieldGoalAttempts,3PointsMade,3PointAttempts,FreeThrowsMade,
  283%                    FreeThrowAttempts,PlusMinus,OffensiveRebounds,DefensiveRebounds,TotalRebounds,Assists,PersonalFouls,Steals,
  284%                    Turnovers,BlockedShots,BlocksAgainst,Points,Starter).
  285
  286actions(1,7,78,2605,5,14,3,3,0,0,12,0,3,3,4,2,1,1,0,0,13,1).
  287actions(1,7,79,2359,11,19,3,3,8,8,13,0,8,8,3,2,3,3,1,0,34,1).
  288actions(1,7,80,2104,6,7,3,3,3,8,18,2,7,9,1,3,1,1,2,0,15,1).
  289actions(1,7,81,1392,1,5,3,3,0,0,3,0,2,2,0,4,1,0,0,0,2,1).
  290actions(1,7,82,2124,5,8,3,3,1,2,5,0,3,3,6,1,1,4,0,0,12,1).
  291actions(1,7,83,1880,3,9,3,3,3,4,5,0,2,2,2,3,0,0,0,0,10,0).
  292actions(1,7,84,1009,0,3,3,3,0,0,5,1,3,4,2,0,1,0,0,0,0,0).
  293actions(1,7,85,773,2,4,3,3,2,2,-12,0,6,6,0,3,0,0,3,0,6,0).
  294actions(1,7,86,77,0,1,3,3,0,0,-2,0,0,0,0,0,0,0,0,0,0,0).
  295actions(1,7,87,77,0,0,3,3,0,0,-2,0,1,1,0,0,0,0,0,0,0,0).
  296actions(1,7,88,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  297actions(1,7,89,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  298actions(1,8,90,1680,5,9,3,3,0,0,-5,0,2,2,3,2,0,0,0,0,11,1).
  299actions(1,8,91,1874,2,5,3,3,0,0,-13,2,8,10,2,4,2,0,0,0,5,1).
  300actions(1,8,92,1294,6,14,3,3,1,3,-4,8,5,13,0,4,0,0,0,3,13,1).
  301actions(1,8,93,2362,5,14,3,3,5,8,-7,0,2,2,1,1,1,2,0,0,18,1).
  302actions(1,8,94,1876,2,8,3,3,0,0,-8,1,3,4,3,3,0,3,0,1,5,1).
  303actions(1,8,95,1506,5,11,3,3,2,2,-4,2,4,6,0,3,0,0,0,1,12,0).
  304actions(1,8,96,2052,7,12,3,3,1,2,-4,1,6,7,4,3,1,5,0,0,17,0).
  305actions(1,8,97,1084,0,8,3,3,0,0,-2,0,3,3,1,1,0,0,0,0,0,0).
  306actions(1,8,98,518,0,3,3,3,0,0,-2,0,1,1,1,2,1,1,0,1,0,0).
  307actions(1,8,99,77,1,1,3,3,0,0,2,2,0,2,0,0,0,0,0,0,2,0).
  308actions(1,8,100,77,0,0,3,3,0,0,2,0,0,0,0,0,0,0,0,0,0,0).
  309actions(1,8,101,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  310actions(1,8,102,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  311actions(2,9,103,1742,0,4,3,3,1,2,-6,2,2,4,1,3,0,1,1,0,1,1).
  312actions(2,9,104,2049,8,15,3,3,4,8,1,2,9,11,3,4,1,2,0,2,20,1).
  313actions(2,9,105,1991,6,19,3,3,1,3,-6,4,4,8,2,2,0,2,1,1,13,1).
  314actions(2,9,106,2048,6,12,3,3,4,6,2,2,5,7,3,2,0,0,0,0,19,1).
  315actions(2,9,107,1823,9,15,3,3,0,0,-7,2,0,2,2,1,1,2,0,0,19,1).
  316actions(2,9,108,1057,4,7,3,3,0,0,7,1,1,2,3,2,1,3,0,0,9,0).
  317actions(2,9,109,580,1,1,3,3,1,1,3,0,1,1,1,2,0,0,0,0,3,0).
  318actions(2,9,110,1029,1,2,3,3,0,0,6,0,2,2,0,0,0,1,0,0,2,0).
  319actions(2,9,111,1140,2,7,3,3,2,3,2,4,2,6,0,2,1,0,1,0,6,0).
  320actions(2,9,112,941,1,3,3,3,0,0,-2,0,0,0,2,1,3,0,0,0,2,0).
  321actions(2,9,113,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  322actions(2,9,114,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  323actions(2,9,115,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  324actions(2,10,116,1059,1,2,3,3,0,0,-8,0,3,3,0,1,0,1,0,0,3,1).
  325actions(2,10,117,1908,6,14,3,3,5,9,8,5,3,8,2,2,3,2,1,2,17,1).
  326actions(2,10,118,1895,9,15,3,3,5,7,0,2,8,10,1,5,0,2,1,1,23,1).
  327actions(2,10,119,2414,6,13,3,3,0,0,11,2,7,9,4,2,2,2,0,0,13,1).
  328actions(2,10,120,2371,3,9,3,3,2,4,-1,0,5,5,6,2,0,2,0,0,8,1).
  329actions(2,10,121,973,2,5,3,3,0,0,-8,1,1,2,0,2,0,1,0,0,5,0).
  330actions(2,10,122,1029,2,3,3,3,0,0,-6,0,3,3,1,2,0,1,0,0,5,0).
  331actions(2,10,123,1766,4,8,3,3,0,0,4,0,0,0,6,1,1,2,0,0,10,0).
  332actions(2,10,124,984,3,4,3,3,2,4,0,1,2,3,0,6,1,1,1,0,8,0).
  333actions(2,10,125,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  334actions(2,10,126,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  335actions(2,10,127,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  336actions(2,10,128,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  337actions(3,11,129,2388,7,18,3,3,7,8,13,3,2,5,5,2,0,3,0,1,22,1).
  338actions(3,11,130,1388,1,1,3,3,1,2,13,2,10,12,0,5,1,3,0,0,3,1).
  339actions(3,11,131,2246,13,18,3,3,9,12,23,3,11,14,3,3,1,3,2,3,35,1).
  340actions(3,11,132,2302,5,11,3,3,3,4,15,2,3,5,1,1,0,4,1,0,14,1).
  341actions(3,11,133,2636,9,19,3,3,3,5,12,0,2,2,10,3,2,1,0,2,22,1).
  342actions(3,11,134,1017,1,6,3,3,0,0,-15,0,1,1,1,1,2,0,0,0,2,0).
  343actions(3,11,135,538,1,2,3,3,0,0,-15,0,0,0,0,0,0,1,0,1,2,0).
  344actions(3,11,136,253,1,3,3,3,0,0,-9,1,0,1,0,1,0,0,0,1,2,0).
  345actions(3,11,137,554,0,2,3,3,0,0,-10,0,2,2,0,2,0,2,0,2,0,0).
  346actions(3,11,138,1080,0,0,3,3,0,0,-2,4,1,5,0,1,1,1,0,0,0,0).
  347actions(3,11,139,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  348actions(3,11,140,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  349actions(3,12,141,1149,1,1,3,3,2,2,-14,0,2,2,0,2,3,0,0,0,4,1).
  350actions(3,12,142,2261,5,13,3,3,12,14,-20,2,6,8,4,3,2,1,4,0,22,1).
  351actions(3,12,143,829,1,1,3,3,2,3,-14,0,0,0,0,4,0,0,0,0,4,1).
  352actions(3,12,144,1535,7,15,3,3,1,2,-16,0,2,2,4,3,2,4,0,1,15,1).
  353actions(3,12,145,1313,4,12,3,3,0,0,-15,0,1,1,2,1,0,1,0,1,9,1).
  354actions(3,12,146,1730,3,4,3,3,0,0,12,0,3,3,1,2,1,1,1,0,6,0).
  355actions(3,12,147,500,0,3,3,3,0,0,-7,1,0,1,0,4,0,1,0,0,0,0).
  356actions(3,12,148,1430,2,5,3,3,2,4,9,0,1,1,9,3,0,3,0,1,6,0).
  357actions(3,12,149,1695,9,13,3,3,1,1,14,0,3,3,1,1,2,0,0,0,23,0).
  358actions(3,12,150,1686,4,4,3,3,0,0,19,0,7,7,1,3,1,2,5,0,8,0).
  359actions(3,12,151,272,0,2,3,3,0,0,7,0,2,2,0,0,0,0,0,0,0,0).
  360actions(3,12,152,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  361actions(3,12,153,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  362actions(4,13,154,2056,7,14,3,3,2,2,16,1,5,6,3,3,2,1,0,2,19,1).
  363actions(4,13,155,2129,6,10,3,3,2,2,17,0,4,4,3,4,0,1,0,0,16,1).
  364actions(4,13,156,2408,4,6,3,3,3,8,14,10,14,24,0,2,0,5,4,0,11,1).
  365actions(4,13,157,2602,9,17,3,3,8,8,15,1,2,3,7,1,1,6,0,1,28,1).
  366actions(4,13,158,2281,6,16,3,3,8,8,16,1,6,7,9,4,3,3,0,1,22,1).
  367actions(4,13,159,691,2,5,3,3,0,0,-4,0,2,2,0,0,0,0,0,0,6,0).
  368actions(4,13,160,877,3,9,3,3,0,0,-11,0,0,0,1,3,0,1,0,0,6,0).
  369actions(4,13,161,824,1,5,3,3,0,0,-6,0,2,2,0,1,1,1,0,0,3,0).
  370actions(4,13,162,318,0,0,3,3,1,2,-2,0,1,1,0,0,1,0,0,0,1,0).
  371actions(4,13,163,214,0,0,3,3,2,2,-5,0,0,0,0,0,0,0,0,0,2,0).
  372actions(4,13,164,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  373actions(4,13,165,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  374actions(4,13,166,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  375actions(4,14,167,1246,4,8,3,3,0,0,-22,0,1,1,1,1,1,1,2,0,9,1).
  376actions(4,14,168,1762,8,21,3,3,2,3,-30,5,8,13,4,1,1,4,0,0,20,1).
  377actions(4,14,170,1816,4,14,3,3,2,2,-21,0,2,2,0,2,0,0,0,0,12,1).
  378actions(4,14,171,1659,1,6,3,3,0,0,-32,1,1,2,7,1,1,5,0,0,3,1).
  379actions(4,14,172,1162,4,4,3,3,6,6,-4,3,1,4,3,4,3,1,1,0,14,0).
  380actions(4,14,173,1462,2,10,3,3,0,0,19,0,3,3,8,5,0,2,0,1,4,0).
  381actions(4,14,174,1144,4,8,3,3,0,0,5,3,3,6,2,1,0,2,0,0,8,0).
  382actions(4,14,175,1634,5,8,3,3,1,1,12,0,5,5,1,2,2,1,1,1,12,0).
  383actions(4,14,176,1382,4,8,3,3,0,0,16,0,2,2,3,3,1,1,0,1,11,0).
  384actions(4,14,177,720,5,6,3,3,1,2,12,0,3,3,1,2,0,0,0,0,11,0).
  385actions(4,14,178,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  386actions(4,14,179,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  387actions(4,14,392,413,0,3,3,3,0,0,-5,0,1,1,0,1,0,0,0,1,0,1).
  388actions(5,15,180,2380,4,13,3,3,0,0,-12,0,2,2,1,4,2,4,0,0,9,1).
  389actions(5,15,181,1888,7,10,3,3,4,4,-6,3,6,9,3,1,0,2,4,0,18,1).
  390actions(5,15,182,1523,5,7,3,3,1,2,-29,1,2,3,1,2,1,2,0,1,11,1).
  391actions(5,15,183,824,0,5,3,3,1,1,-6,0,2,2,3,0,0,0,0,1,1,1).
  392actions(5,15,184,1980,6,14,3,3,2,2,-20,0,2,2,5,1,1,1,0,0,18,1).
  393actions(5,15,185,1194,1,6,3,3,0,0,-3,1,5,6,1,2,0,1,0,0,2,0).
  394actions(5,15,186,2105,1,7,3,3,3,4,0,1,1,2,0,1,2,0,0,0,5,0).
  395actions(5,15,187,1132,4,8,3,3,0,2,-2,1,1,2,3,2,4,2,0,0,9,0).
  396actions(5,15,188,1098,3,6,3,3,0,0,10,4,3,7,0,2,0,4,0,1,7,0).
  397actions(5,15,189,276,0,1,3,3,0,0,-2,1,1,2,0,0,0,0,0,0,0,0).
  398actions(5,15,190,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  399actions(5,15,191,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  400actions(5,16,192,2329,7,12,3,3,5,5,11,0,3,3,3,2,0,3,0,0,22,1).
  401actions(5,16,193,1440,7,12,3,3,2,2,4,3,4,7,1,3,0,1,0,0,16,1).
  402actions(5,16,194,2339,9,19,3,3,1,1,26,4,7,11,5,2,2,3,2,3,19,1).
  403actions(5,16,195,2547,8,13,3,3,2,2,9,1,3,4,4,1,1,0,0,1,18,1).
  404actions(5,16,196,1641,0,6,3,3,1,2,11,0,3,3,3,1,4,1,1,0,1,1).
  405actions(5,16,197,1833,1,9,3,3,2,2,11,0,1,1,11,2,0,1,0,0,4,0).
  406actions(5,16,198,1705,6,9,3,3,2,2,5,3,8,11,0,4,1,3,0,0,14,0).
  407actions(5,16,199,276,0,0,3,3,0,0,-7,0,0,0,0,0,0,0,0,0,0,0).
  408actions(5,16,200,290,0,0,3,3,0,0,0,0,0,0,1,1,1,1,0,0,0,0).
  409actions(5,16,201,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  410actions(5,16,202,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  411actions(5,16,203,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  412actions(6,17,204,1443,1,6,3,3,0,0,-12,0,6,6,0,1,0,0,0,0,2,1).
  413actions(6,17,205,1430,2,3,3,3,0,2,-10,1,5,6,1,4,0,1,0,0,4,1).
  414actions(6,17,206,1949,7,9,3,3,0,0,-13,2,8,10,0,4,1,2,0,0,14,1).
  415actions(6,17,207,2357,8,14,3,3,0,1,-8,0,2,2,7,3,2,2,0,0,16,1).
  416actions(6,17,208,1553,4,11,3,3,2,3,-19,1,0,1,4,2,0,5,0,0,11,1).
  417actions(6,17,209,488,1,4,3,3,0,0,-3,1,0,1,0,3,0,0,0,0,2,0).
  418actions(6,17,210,1544,4,6,3,3,1,1,3,0,2,2,0,3,2,0,0,0,13,0).
  419actions(6,17,211,1129,1,3,3,3,0,0,6,0,0,0,3,2,1,0,0,0,2,0).
  420actions(6,17,212,1388,6,11,3,3,2,3,6,0,0,0,1,3,0,4,0,2,17,0).
  421actions(6,17,213,349,0,0,3,3,0,0,3,0,1,1,0,0,0,0,0,0,0,0).
  422actions(6,17,214,633,1,3,3,3,0,0,2,0,1,1,1,0,1,0,1,0,2,0).
  423actions(6,17,215,137,0,0,3,3,0,0,-5,0,0,0,0,0,0,0,0,0,0,0).
  424actions(6,17,216,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  425actions(6,18,217,2333,11,20,3,3,9,11,22,0,7,7,8,2,1,6,0,0,32,1).
  426actions(6,18,218,997,1,3,3,3,0,0,2,1,4,5,1,0,1,0,0,0,2,1).
  427actions(6,18,219,2057,8,16,3,3,2,3,27,1,3,4,2,0,1,1,0,0,18,1).
  428actions(6,18,220,1448,2,4,3,3,0,0,10,0,3,3,0,4,0,1,0,0,5,1).
  429actions(6,18,221,2190,4,8,3,3,1,1,9,0,3,3,4,1,0,0,0,0,12,1).
  430actions(6,18,222,1170,1,4,3,3,0,0,-5,1,2,3,2,2,1,1,0,0,2,0).
  431actions(6,18,223,1211,0,1,3,3,1,2,-6,0,0,0,2,1,1,3,0,0,1,0).
  432actions(6,18,224,1482,2,5,3,3,2,2,-5,0,4,4,0,1,0,2,0,1,8,0).
  433actions(6,18,225,1512,5,5,3,3,3,3,-4,3,4,7,0,3,0,1,2,0,13,0).
  434actions(6,18,226,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  435actions(6,18,227,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  436actions(6,18,228,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  437actions(6,18,229,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  438actions(7,19,230,1906,6,16,3,3,0,0,-15,0,1,1,1,3,2,2,1,0,14,1).
  439actions(7,19,231,1612,7,13,3,3,2,2,-10,4,4,8,1,2,0,1,0,3,16,1).
  440actions(7,19,232,2094,6,13,3,3,0,0,-3,7,6,13,6,2,0,3,3,1,12,1).
  441actions(7,19,233,2620,5,10,3,3,9,11,-6,2,3,5,11,3,1,3,0,0,20,1).
  442actions(7,19,234,2286,7,21,3,3,11,14,-9,3,6,9,7,3,0,0,0,1,25,1).
  443actions(7,19,235,1828,4,6,3,3,4,5,15,0,5,5,2,0,1,1,1,0,14,0).
  444actions(7,19,236,1043,3,8,3,3,1,2,1,1,4,5,0,4,1,2,0,0,7,0).
  445actions(7,19,237,1011,1,1,3,3,1,2,2,1,3,4,0,3,0,1,0,0,3,0).
  446actions(7,19,238,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  447actions(7,19,239,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  448actions(7,19,240,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  449actions(7,19,241,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  450actions(7,19,242,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  451actions(7,20,243,1775,11,19,3,3,2,3,-1,0,1,1,3,4,1,3,1,0,26,1).
  452actions(7,20,244,2370,12,21,3,3,4,6,19,4,10,14,1,1,0,1,2,0,28,1).
  453actions(7,20,245,1692,5,9,3,3,0,0,23,8,8,16,0,4,2,2,0,2,10,1).
  454actions(7,20,246,1704,5,10,3,3,2,2,2,3,2,5,2,3,0,2,1,1,14,1).
  455actions(7,20,247,2306,7,17,3,3,1,3,6,1,2,3,13,5,1,1,0,1,20,1).
  456actions(7,20,248,1215,2,5,3,3,0,1,3,0,0,0,0,1,0,2,0,0,4,0).
  457actions(7,20,249,681,0,4,3,3,0,0,-3,3,4,7,1,3,0,0,0,0,0,0).
  458actions(7,20,250,807,1,4,3,3,0,0,-12,0,1,1,0,1,0,0,0,1,2,0).
  459actions(7,20,251,1397,3,6,3,3,6,6,-1,0,2,2,8,3,1,0,0,0,12,0).
  460actions(7,20,252,452,0,2,3,3,0,0,-11,0,1,1,0,1,0,0,1,0,0,0).
  461actions(7,20,253,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  462actions(7,20,254,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  463actions(7,20,255,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  464actions(8,21,256,1493,2,3,3,3,0,1,-4,0,3,3,2,3,0,1,0,0,5,1).
  465actions(8,21,257,2130,7,10,3,3,4,4,-11,0,3,3,4,5,4,3,3,0,23,1).
  466actions(8,21,258,1617,3,8,3,3,2,3,11,2,3,5,2,3,1,1,0,0,8,1).
  467actions(8,21,259,2074,8,16,3,3,0,0,-3,0,3,3,4,2,0,3,0,0,19,1).
  468actions(8,21,260,2028,7,14,3,3,2,2,1,1,8,9,9,3,3,3,0,0,16,1).
  469actions(8,21,261,1078,3,8,3,3,0,0,-7,0,1,1,3,4,0,5,0,0,6,0).
  470actions(8,21,262,1239,2,3,3,3,1,7,-16,1,8,9,0,1,0,2,3,0,5,0).
  471actions(8,21,263,1148,3,8,3,3,3,3,-5,2,2,4,1,2,1,0,0,0,10,0).
  472actions(8,21,264,852,0,5,3,3,0,0,-9,0,0,0,0,2,1,1,0,0,0,0).
  473actions(8,21,265,742,1,2,3,3,0,0,3,0,3,3,0,2,1,1,0,0,3,0).
  474actions(8,21,266,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  475actions(8,21,267,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  476actions(8,22,268,1727,4,9,3,3,0,0,9,2,3,5,4,2,2,1,0,0,9,1).
  477actions(8,22,269,2156,9,15,3,3,9,13,9,5,12,17,4,1,3,3,0,1,28,1).
  478actions(8,22,270,1270,1,8,3,3,0,0,-10,2,2,4,2,4,0,1,0,2,2,1).
  479actions(8,22,271,1611,3,10,3,3,4,5,-11,0,2,2,2,2,0,3,0,0,11,1).
  480actions(8,22,272,2006,4,11,3,3,3,3,15,1,2,3,5,0,1,4,0,2,12,1).
  481actions(8,22,273,1494,7,12,3,3,6,6,23,1,4,5,5,1,1,1,0,0,22,0).
  482actions(8,22,274,1313,2,5,3,3,0,0,19,1,3,4,1,4,0,0,0,0,4,0).
  483actions(8,22,275,855,2,6,3,3,2,3,4,0,4,4,0,1,1,1,0,1,6,0).
  484actions(8,22,276,874,2,5,3,3,0,0,-7,0,1,1,2,0,2,1,0,0,4,0).
  485actions(8,22,277,265,1,2,3,3,0,0,-3,0,2,2,0,1,0,1,0,0,2,0).
  486actions(8,22,278,828,1,1,3,3,0,0,-8,1,1,2,0,1,0,0,0,0,3,0).
  487actions(8,22,279,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  488actions(9,23,280,1795,4,9,3,3,0,0,-22,0,2,2,1,1,0,1,0,0,11,1).
  489actions(9,23,281,1188,2,5,3,3,0,0,-11,1,1,2,1,1,2,0,1,1,4,1).
  490actions(9,23,282,1616,3,7,3,3,0,0,-21,2,9,11,1,3,0,1,1,1,6,1).
  491actions(9,23,283,2392,8,12,3,3,2,3,0,0,2,2,5,3,0,4,1,0,20,1).
  492actions(9,23,284,1756,4,16,3,3,2,3,-24,0,1,1,6,2,0,5,0,2,10,1).
  493actions(9,23,285,1633,5,12,3,3,2,2,0,4,4,8,2,5,2,0,0,1,12,0).
  494actions(9,23,286,1600,5,7,3,3,2,2,10,0,2,2,1,2,0,1,0,0,14,0).
  495actions(9,23,287,1238,4,5,3,3,1,3,15,0,5,5,0,3,1,1,0,0,11,0).
  496actions(9,23,288,1124,2,5,3,3,0,0,18,1,2,3,9,1,1,1,0,0,4,0).
  497actions(9,23,289,59,1,1,3,3,0,0,5,1,0,1,0,0,0,0,0,0,2,0).
  498actions(9,23,290,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  499actions(9,23,291,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  500actions(9,23,292,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  501actions(9,24,293,1250,0,5,3,3,3,4,2,3,3,6,0,2,1,1,0,1,3,1).
  502actions(9,24,294,1633,1,2,3,3,0,0,-3,3,2,5,1,1,0,0,1,0,2,1).
  503actions(9,24,295,2403,8,19,3,3,3,3,-2,3,8,11,0,3,0,0,2,1,19,1).
  504actions(9,24,296,1625,3,7,3,3,3,4,-1,0,3,3,2,2,1,1,0,0,9,1).
  505actions(9,24,297,2292,6,22,3,3,9,10,16,1,4,5,10,2,1,1,1,1,21,1).
  506actions(9,24,298,1220,4,4,3,3,7,8,9,3,5,8,2,1,1,1,0,0,15,0).
  507actions(9,24,299,477,2,2,3,3,0,0,8,0,0,0,0,0,1,0,1,0,4,0).
  508actions(9,24,300,1255,3,6,3,3,2,2,7,1,5,6,1,2,1,3,0,0,9,0).
  509actions(9,24,301,588,0,2,3,3,0,0,-10,0,1,1,1,1,0,2,0,0,0,0).
  510actions(9,24,302,1657,7,9,3,3,2,3,4,1,2,3,0,1,0,1,0,0,18,0).
  511actions(9,24,303,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  512actions(9,24,304,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  513actions(9,24,305,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  514actions(10,1,1,2134,6,13,3,3,0,0,18,2,3,5,7,2,2,1,0,0,16,1).
  515actions(10,1,2,1952,12,20,3,3,7,8,27,1,14,15,6,2,1,2,2,1,31,1).
  516actions(10,1,3,2043,4,5,3,3,2,2,21,3,7,10,1,2,0,0,2,0,10,1).
  517actions(10,1,4,1952,4,12,3,3,0,0,17,0,4,4,6,1,0,1,1,0,10,1).
  518actions(10,1,5,2130,10,22,3,3,9,9,24,0,2,2,8,3,3,2,0,3,34,1).
  519actions(10,1,6,1077,3,7,3,3,1,2,-13,3,3,6,0,2,3,1,0,3,7,0).
  520actions(10,1,7,1490,3,11,3,3,0,0,2,0,1,1,3,4,1,0,0,1,8,0).
  521actions(10,1,8,676,4,7,3,3,0,0,-13,2,3,5,1,1,0,2,0,1,8,0).
  522actions(10,1,9,559,0,0,3,3,0,0,-5,0,1,1,0,0,0,0,0,0,0,0).
  523actions(10,1,10,129,0,0,3,3,0,0,-6,0,1,1,0,0,0,1,0,0,0,0).
  524actions(10,1,11,129,0,2,3,3,0,0,-6,0,0,0,0,0,0,0,0,1,0,0).
  525actions(10,1,12,92,0,0,3,3,0,0,-4,0,0,0,0,1,0,0,0,0,0,0).
  526actions(10,1,13,37,0,0,3,3,0,0,-2,0,0,0,0,0,0,0,0,0,0,0).
  527actions(10,2,14,1821,6,10,3,3,3,4,-20,0,4,4,1,2,2,1,0,0,17,1).
  528actions(10,2,15,1700,4,9,3,3,1,1,-18,1,3,4,7,4,1,3,2,2,9,1).
  529actions(10,2,16,1744,6,16,3,3,0,0,-19,1,5,6,2,2,1,2,3,0,12,1).
  530actions(10,2,17,1597,2,7,3,3,0,0,-20,0,2,2,2,0,0,1,0,0,4,1).
  531actions(10,2,18,1155,2,4,3,3,2,2,-14,0,6,6,5,3,1,1,0,0,8,1).
  532actions(10,2,19,1308,2,5,3,3,6,6,8,0,4,4,10,1,0,1,1,1,10,0).
  533actions(10,2,20,788,0,4,3,3,0,0,7,0,0,0,0,1,0,0,0,1,0,0).
  534actions(10,2,21,1108,1,3,3,3,1,2,5,1,5,6,1,0,0,0,2,0,3,0).
  535actions(10,2,22,1208,3,8,3,3,2,2,8,4,5,9,2,3,0,1,2,0,9,0).
  536actions(10,2,23,1971,15,26,3,3,4,5,3,2,2,4,1,0,2,1,0,1,40,0).
  537actions(10,2,24,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  538actions(10,2,25,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  539actions(10,2,26,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  540actions(11,3,27,2437,7,9,3,3,0,1,5,2,6,8,7,0,1,0,0,0,16,1).
  541actions(11,3,28,2525,4,9,3,3,0,0,12,1,6,7,6,3,2,2,1,1,9,1).
  542actions(11,3,29,1994,9,12,3,3,2,4,-2,4,4,8,0,1,0,1,1,1,20,1).
  543actions(11,3,30,2830,11,24,3,3,1,1,6,0,5,5,5,3,1,2,0,2,27,1).
  544actions(11,3,31,2587,10,17,3,3,0,0,8,0,5,5,5,3,1,2,0,2,27,1).
  545actions(11,3,32,1026,4,7,3,3,0,0,6,2,7,9,1,3,0,4,0,1,8,0).
  546actions(11,3,33,785,0,0,3,3,0,0,-5,0,0,0,1,1,0,1,1,0,0,0).
  547actions(11,3,34,783,0,3,3,3,0,0,-9,0,0,0,3,1,0,1,0,0,0,0).
  548actions(11,3,35,933,7,10,3,3,0,0,-11,0,4,4,0,2,0,0,0,0,19,0).
  549actions(11,3,36,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  550actions(11,3,37,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  551actions(11,3,38,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  552actions(11,4,39,2154,4,8,3,3,0,0,-8,4,6,10,2,1,0,1,1,0,8,1).
  553actions(11,4,40,2380,13,21,3,3,1,3,-1,1,10,11,3,0,2,0,1,1,33,1).
  554actions(11,4,41,424,1,2,3,3,0,0,-15,2,1,3,0,1,0,0,0,0,2,1).
  555actions(11,4,42,2561,11,23,3,3,3,4,-9,1,1,2,6,0,2,2,1,1,27,1).
  556actions(11,4,43,2198,3,9,3,3,1,1,-8,0,2,2,6,2,0,3,0,0,8,1).
  557actions(11,4,44,1858,4,13,3,3,1,2,9,2,2,4,4,2,2,0,1,0,12,0).
  558actions(11,4,45,1523,5,6,3,3,4,4,-3,4,1,5,0,0,0,1,1,0,14,0).
  559actions(11,4,46,982,3,7,3,3,2,2,6,0,1,1,4,3,0,0,0,1,10,0).
  560actions(11,4,47,1141,0,3,3,3,0,0,15,0,2,2,2,0,0,0,0,0,0,0).
  561actions(11,4,48,679,3,4,3,3,0,0,4,1,2,3,0,3,1,1,0,0,6,0).
  562actions(11,4,49,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  563actions(11,4,50,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  564actions(11,4,51,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  565actions(12,5,52,2477,7,15,3,3,0,2,-9,0,8,8,4,2,1,2,0,2,16,1).
  566actions(12,5,53,506,0,2,3,3,0,0,-6,1,1,2,0,4,0,0,0,0,0,1).
  567actions(12,5,54,2142,5,8,3,3,2,6,-8,6,17,23,0,1,1,3,2,1,12,1).
  568actions(12,5,55,2166,4,10,3,3,16,16,-17,6,17,23,0,1,1,3,2,1,12,1).
  569actions(12,5,56,1975,6,14,3,3,2,2,-14,1,3,4,2,0,1,2,0,1,16,1).
  570actions(12,5,57,1335,3,10,3,3,0,0,-5,1,1,2,0,2,0,0,0,0,7,0).
  571actions(12,5,58,1532,4,9,3,3,0,0,9,0,2,2,3,2,0,0,1,1,10,0).
  572actions(12,5,59,1390,1,8,3,3,0,0,-1,0,1,1,1,1,0,2,0,0,2,0).
  573actions(12,5,60,877,2,8,3,3,2,2,6,0,1,1,3,2,1,2,0,0,7,0).
  574actions(12,5,61,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  575actions(12,5,62,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  576actions(12,5,63,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  577actions(12,5,64,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  578actions(12,6,65,2034,13,21,3,3,2,2,17,0,4,4,3,2,1,1,0,0,32,1).
  579actions(12,6,66,1406,2,4,3,3,0,0,11,0,6,6,1,1,1,2,0,0,4,1).
  580actions(12,6,67,1658,5,6,3,3,1,3,8,3,3,6,4,2,1,2,2,1,11,1).
  581actions(12,6,68,1751,6,12,3,3,5,6,4,0,6,6,2,2,2,1,1,1,17,1).
  582actions(12,6,69,2129,6,14,3,3,0,0,7,0,3,3,6,4,2,1,0,0,12,1).
  583actions(12,6,70,1643,1,3,3,3,2,4,4,0,2,2,2,5,1,1,0,0,4,0).
  584actions(12,6,71,1194,6,12,3,3,1,2,1,2,2,4,2,4,0,4,2,0,13,0).
  585actions(12,6,72,1474,4,7,3,3,0,0,-2,1,6,7,1,2,1,1,0,1,10,0).
  586actions(12,6,73,1039,1,3,3,3,0,0,-3,0,4,4,2,4,0,0,0,0,2,0).
  587actions(12,6,74,44,0,1,3,3,0,0,-2,0,0,0,0,0,0,0,0,0,0,0).
  588actions(12,6,75,28,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  589actions(12,6,76,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  590actions(12,6,77,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  591actions(13,20,243,2240,9,20,3,3,3,7,-11,0,5,5,1,4,2,1,1,1,24,1).
  592actions(13,20,244,1867,6,21,3,3,5,6,6,7,9,16,2,4,3,0,1,2,17,1).
  593actions(13,20,245,1880,5,9,3,3,3,6,-5,6,8,14,0,2,0,1,1,1,13,1).
  594actions(13,20,246,2368,3,11,3,3,3,3,3,3,2,5,3,1,0,1,0,1,10,1).
  595actions(13,20,247,2107,4,11,3,3,2,3,2,0,2,2,9,2,1,1,0,0,12,1).
  596actions(13,20,248,1936,6,12,3,3,3,3,-16,0,1,1,0,0,0,0,1,0,16,0).
  597actions(13,20,249,529,0,1,3,3,0,0,6,1,1,2,0,0,0,0,0,0,0,0).
  598actions(13,20,250,360,0,1,3,3,0,0,-5,0,1,1,1,1,0,0,0,1,0,0).
  599actions(13,20,251,773,1,5,3,3,0,0,-9,0,1,1,0,2,1,1,0,1,2,0).
  600actions(13,20,252,340,0,2,3,3,0,0,-6,0,0,0,0,2,0,0,0,0,0,0).
  601actions(13,20,253,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  602actions(13,20,254,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  603actions(13,20,255,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  604actions(13,25,306,2263,9,19,3,3,5,6,9,1,12,13,7,2,2,2,0,1,27,1).
  605actions(13,25,307,1990,7,10,3,3,1,1,1,2,6,8,3,3,0,0,2,0,15,1).
  606actions(13,25,308,1742,4,10,3,3,3,4,-4,1,2,3,3,5,0,2,2,0,11,1).
  607actions(13,25,309,2040,5,10,3,3,0,0,10,0,5,5,4,2,0,3,0,1,11,1).
  608actions(13,25,310,2323,4,9,3,3,4,5,15,0,1,1,2,3,1,0,0,1,12,1).
  609actions(13,25,311,890,3,7,3,3,3,4,6,4,3,7,2,4,0,2,0,1,9,0).
  610actions(13,25,312,1044,2,5,3,3,0,0,1,0,3,3,1,1,0,0,0,0,4,0).
  611actions(13,25,313,1138,4,5,3,3,2,4,11,2,3,5,1,0,1,0,3,0,10,0).
  612actions(13,25,314,413,1,2,3,3,0,0,-6,0,1,1,0,0,0,0,0,0,2,0).
  613actions(13,25,315,557,0,2,3,3,0,0,-8,0,1,1,1,1,0,1,0,0,0,0).
  614actions(13,25,316,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  615actions(13,25,317,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  616actions(13,25,318,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  617actions(14,6,65,1341,5,13,3,3,4,5,-3,0,1,1,1,1,2,2,0,1,16,1).
  618actions(14,6,66,1604,2,7,3,3,4,4,-7,0,4,4,1,3,1,1,0,2,8,1).
  619actions(14,6,67,1367,1,1,3,3,3,3,-6,2,2,4,2,4,1,1,0,0,5,1).
  620actions(14,6,68,1499,1,4,3,3,2,4,0,1,2,3,3,1,2,1,0,0,4,1).
  621actions(14,6,69,1654,5,11,3,3,0,0,-9,0,1,1,0,1,1,2,0,1,12,1).
  622actions(14,6,70,1539,2,5,3,3,6,8,-25,1,2,3,0,2,1,3,0,0,11,0).
  623actions(14,6,71,1067,1,3,3,3,0,2,-20,1,1,2,1,1,0,2,0,0,3,0).
  624actions(14,6,72,1282,3,8,3,3,0,0,-21,1,0,1,1,0,0,1,0,0,6,0).
  625actions(14,6,73,930,2,3,3,3,2,2,-13,0,0,0,0,1,1,1,0,0,6,0).
  626actions(14,6,74,440,1,2,3,3,0,0,-2,0,0,0,2,0,0,1,0,0,2,0).
  627actions(14,6,75,440,0,0,3,3,0,0,-2,0,1,1,0,0,0,0,0,0,0,0).
  628actions(14,6,76,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  629actions(14,6,77,1237,3,8,3,3,0,0,-32,1,2,3,0,2,0,1,0,1,8,0).
  630actions(14,7,78,2121,9,16,3,3,0,0,17,0,8,8,6,3,1,1,0,0,24,1).
  631actions(14,7,79,2241,8,16,3,3,7,8,21,1,9,10,3,3,2,3,1,0,23,1).
  632actions(14,7,80,1780,2,2,3,3,0,2,13,1,4,5,1,4,1,2,2,0,4,1).
  633actions(14,7,81,1446,4,6,3,3,2,3,29,1,2,3,2,5,5,2,0,0,10,0).
  634actions(14,7,82,1223,2,5,3,3,0,0,4,2,1,3,3,0,0,1,0,0,5,1).
  635actions(14,7,83,1653,7,10,3,3,0,0,33,1,0,1,0,1,0,0,0,0,17,0).
  636actions(14,7,84,1230,2,2,3,3,1,1,17,1,1,2,3,2,0,2,0,0,6,0).
  637actions(14,7,85,363,0,0,3,3,0,0,2,0,0,0,0,1,0,0,0,0,0,0).
  638actions(14,7,86,363,3,5,3,3,0,0,2,1,1,2,0,1,0,0,0,0,6,0).
  639actions(14,7,87,363,0,1,3,3,0,0,2,0,0,0,0,0,2,0,0,0,0,0).
  640actions(14,7,88,363,1,1,3,3,0,0,2,0,1,1,1,1,0,2,0,0,2,0).
  641actions(14,7,89,1254,4,6,3,3,5,6,-2,1,5,6,2,4,0,2,2,0,13,1).
  642actions(15,26,319,1262,4,7,3,3,0,0,28,0,2,2,2,0,0,0,0,1,8,1).
  643actions(15,26,320,1948,6,10,3,3,8,8,18,5,6,11,0,4,2,0,1,2,20,1).
  644actions(15,26,321,2010,7,16,3,3,2,2,17,0,8,8,5,1,0,1,0,1,20,1).
  645actions(15,26,322,2011,10,15,3,3,3,4,10,0,0,0,3,3,1,3,0,0,26,1).
  646actions(15,26,323,1707,7,8,3,3,3,4,20,0,6,6,8,1,1,4,0,0,17,1).
  647actions(15,26,324,1814,5,9,3,3,2,2,-2,0,4,4,4,2,1,3,0,0,13,0).
  648actions(15,26,325,1325,1,5,3,3,0,0,8,0,2,2,5,0,0,0,0,0,3,0).
  649actions(15,26,326,1119,2,3,3,3,0,0,9,1,2,3,0,1,0,1,2,0,4,0).
  650actions(15,26,327,939,1,3,3,3,1,2,-7,0,1,1,0,2,1,0,1,0,3,0).
  651actions(15,26,328,156,2,2,3,3,0,0,2,0,0,0,1,1,0,0,0,0,4,0).
  652actions(15,26,329,109,0,0,3,3,1,2,2,0,0,0,0,0,1,0,0,0,1,0).
  653actions(15,26,330,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  654actions(15,27,331,1271,4,7,3,3,0,0,-12,0,2,2,0,2,1,3,0,0,10,1).
  655actions(15,27,332,1083,3,5,3,3,2,2,-7,1,4,5,2,4,0,2,3,0,8,1).
  656actions(15,27,333,1637,3,11,3,3,1,2,-15,4,3,7,2,1,3,3,0,0,7,1).
  657actions(15,27,334,1725,3,10,3,3,0,0,-18,0,4,4,5,0,0,0,1,0,7,1).
  658actions(15,27,335,1375,3,8,3,3,2,3,-17,0,2,2,4,1,0,1,0,1,9,1).
  659actions(15,27,336,750,2,6,3,3,0,0,-20,0,1,1,1,3,0,0,0,0,4,0).
  660actions(15,27,337,1644,4,10,3,3,6,6,-9,0,0,0,4,4,2,2,0,2,16,0).
  661actions(15,27,338,1155,4,7,3,3,0,0,-3,0,0,0,0,3,0,0,0,0,10,0).
  662actions(15,27,339,1259,5,8,3,3,1,2,7,2,5,7,1,1,0,1,0,1,11,0).
  663actions(15,27,340,1470,3,5,3,3,5,5,-4,0,1,1,1,1,0,4,0,0,14,0).
  664actions(15,27,341,1031,1,2,3,3,0,0,-7,2,3,5,1,1,0,1,0,0,2,0).
  665actions(15,27,342,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  666actions(15,27,343,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  667actions(16,21,256,1578,3,5,3,3,2,2,-22,1,1,2,0,4,0,1,0,0,9,1).
  668actions(16,21,257,2048,4,13,3,3,3,3,-21,0,5,5,4,2,2,4,0,0,11,1).
  669actions(16,21,258,1875,5,13,3,3,5,7,-28,4,2,6,2,2,1,1,0,1,15,1).
  670actions(16,21,259,1507,0,4,3,3,0,0,-16,0,3,3,2,2,0,1,0,0,0,1).
  671actions(16,21,260,1594,10,18,3,3,2,4,-18,2,5,7,3,3,0,1,1,0,22,1).
  672actions(16,21,261,1232,2,8,3,3,4,6,-17,0,0,0,4,2,0,1,0,1,8,0).
  673actions(16,21,262,948,2,5,3,3,0,0,-7,0,1,1,4,5,0,1,1,0,4,0).
  674actions(16,21,263,1241,5,8,3,3,0,0,-5,0,2,2,0,3,0,1,0,2,12,0).
  675actions(16,21,264,430,1,2,3,3,0,0,-1,0,0,0,1,0,0,0,0,0,3,0).
  676actions(16,21,265,889,2,3,3,3,2,2,-4,0,3,3,0,1,0,0,0,0,6,0).
  677actions(16,21,266,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  678actions(16,21,267,1058,1,4,3,3,1,2,-11,0,3,3,1,0,2,0,0,0,3,0).
  679actions(16,24,293,1183,1,2,3,3,5,6,10,1,5,6,2,0,0,0,0,1,7,1).
  680actions(16,24,294,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  681actions(16,24,295,1835,9,17,3,3,7,10,12,1,9,10,0,0,0,1,0,0,25,1).
  682actions(16,24,296,1589,5,8,3,3,3,4,10,0,2,2,4,1,1,0,0,0,14,1).
  683actions(16,24,297,1216,3,6,3,3,2,2,15,0,0,0,5,4,0,0,0,0,8,1).
  684actions(16,24,298,1617,3,5,3,3,3,6,13,1,7,8,3,2,0,3,1,1,9,1).
  685actions(16,24,299,1045,1,3,3,3,0,0,18,4,3,7,0,3,0,1,2,0,2,0).
  686actions(16,24,300,1130,6,10,3,3,2,2,25,0,0,0,3,1,0,0,0,0,15,0).
  687actions(16,24,301,1202,3,8,3,3,0,0,11,0,2,2,1,1,0,1,0,0,8,0).
  688actions(16,24,302,1491,4,6,3,3,3,3,17,0,2,2,4,1,0,2,1,0,14,0).
  689actions(16,24,303,462,2,5,3,3,0,0,4,1,0,1,5,1,0,0,0,0,5,0).
  690actions(16,24,304,1263,5,8,3,3,2,2,17,1,7,8,5,3,0,1,0,0,16,0).
  691actions(16,24,305,367,0,1,3,3,0,0,-2,0,1,1,0,0,0,0,0,0,0,0).
  692actions(17,5,52,2138,8,16,3,3,3,3,-10,1,6,7,3,4,2,4,0,0,20,1).
  693actions(17,5,53,1361,6,11,3,3,1,1,2,3,2,5,1,5,0,3,0,0,13,0).
  694actions(17,5,54,1913,3,5,3,3,3,6,-1,2,13,15,0,3,1,3,0,0,9,1).
  695actions(17,5,55,2377,7,17,3,3,10,12,-14,0,6,6,4,4,2,1,0,0,26,1).
  696actions(17,5,56,2332,6,18,3,3,1,2,15,1,0,1,7,4,2,2,1,1,16,1).
  697actions(17,5,57,1397,2,4,3,3,3,4,8,1,4,5,1,2,0,0,0,0,8,0).
  698actions(17,5,58,1045,2,3,3,3,0,0,-3,0,1,1,2,3,0,0,0,0,4,0).
  699actions(17,5,59,1058,2,8,3,3,1,2,-2,1,3,4,1,2,1,0,0,1,7,0).
  700actions(17,5,60,191,0,1,3,3,0,0,-8,0,0,0,0,1,0,1,0,0,0,0).
  701actions(17,5,61,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  702actions(17,5,62,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  703actions(17,5,63,588,0,4,3,3,0,0,-7,1,2,3,0,2,0,1,0,1,0,1).
  704actions(17,5,64,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  705actions(17,17,204,2079,6,12,3,3,1,2,8,0,9,9,0,3,0,4,0,0,14,1).
  706actions(17,17,205,178,0,0,3,3,0,0,-4,0,2,2,0,0,0,0,0,0,0,1).
  707actions(17,17,206,1799,4,7,3,3,7,9,12,1,5,6,1,3,1,1,1,0,15,1).
  708actions(17,17,207,2407,10,19,3,3,8,10,0,0,6,6,4,5,2,2,0,0,29,1).
  709actions(17,17,209,1540,3,7,3,3,1,3,2,0,2,2,1,1,1,1,1,0,8,0).
  710actions(17,17,210,855,1,4,3,3,0,0,6,0,0,0,0,4,1,1,0,0,3,0).
  711actions(17,17,211,1325,3,8,3,3,4,4,-6,0,3,3,2,0,0,1,0,0,12,0).
  712actions(17,17,212,2394,4,12,3,3,3,4,6,0,4,4,8,4,1,0,0,1,15,1).
  713actions(17,17,213,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  714actions(17,17,214,755,1,4,3,3,2,2,2,1,0,1,2,2,0,1,0,0,4,0).
  715actions(17,17,215,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  716actions(17,17,216,1068,2,2,3,3,3,5,-6,1,2,3,2,3,1,2,1,0,7,0).
  717actions(17,17,344,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  718actions(18,15,180,1948,3,13,3,3,7,7,-22,0,1,1,3,2,1,1,1,0,13,1).
  719actions(18,15,181,905,2,2,3,3,4,4,-23,0,1,1,0,1,0,1,0,0,8,1).
  720actions(18,15,182,644,3,5,3,3,0,0,-10,1,0,1,0,0,0,0,0,0,6,1).
  721actions(18,15,183,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  722actions(18,15,184,1264,1,6,3,3,0,0,-22,0,0,0,1,3,3,0,0,0,2,1).
  723actions(18,15,185,2183,8,15,3,3,8,10,-9,1,3,4,1,5,1,1,0,0,25,0).
  724actions(18,15,186,1971,3,10,3,3,0,0,-6,3,5,8,1,1,1,1,0,2,8,0).
  725actions(18,15,187,1156,0,3,3,3,0,0,-3,0,0,0,6,1,2,0,0,0,0,0).
  726actions(18,15,188,1252,5,10,3,3,4,6,8,3,1,4,1,5,1,2,0,1,14,0).
  727actions(18,15,189,386,0,1,3,3,0,0,1,0,1,1,1,1,0,0,0,0,0,0).
  728actions(18,15,190,776,1,3,3,3,1,2,-18,1,1,2,0,1,1,1,0,1,3,0).
  729actions(18,15,191,1915,6,13,3,3,1,1,-26,1,6,7,6,2,0,7,1,0,13,1).
  730actions(18,23,280,1718,7,13,3,3,1,1,26,1,6,7,0,2,1,0,0,0,18,1).
  731actions(18,23,281,1479,3,5,3,3,4,6,26,1,4,5,1,1,0,1,1,0,10,1).
  732actions(18,23,282,1678,10,13,3,3,2,2,26,1,7,8,4,2,3,1,1,0,22,1).
  733actions(18,23,283,1877,7,8,3,3,4,4,20,0,2,2,2,3,1,3,0,0,19,1).
  734actions(18,23,284,1668,5,10,3,3,3,3,30,0,3,3,10,3,2,4,0,2,13,1).
  735actions(18,23,285,1086,1,5,3,3,0,0,-1,0,2,2,1,3,0,2,1,0,2,0).
  736actions(18,23,286,1687,3,6,3,3,0,0,4,1,1,2,2,1,0,0,0,0,8,0).
  737actions(18,23,287,940,4,6,3,3,2,2,-3,0,2,2,1,5,1,3,0,0,12,0).
  738actions(18,23,288,1188,1,1,3,3,0,0,-7,1,3,4,8,1,0,2,0,0,2,0).
  739actions(18,23,289,355,0,1,3,3,0,0,1,0,4,4,0,2,0,2,1,0,0,0).
  740actions(18,23,290,355,3,3,3,3,2,3,1,1,0,1,0,0,0,1,0,0,9,0).
  741actions(18,23,291,222,0,0,3,3,0,0,3,0,0,0,0,1,0,2,0,0,0,0).
  742actions(18,23,292,147,1,1,3,3,0,0,4,0,1,1,0,0,0,0,0,0,3,0).
  743actions(19,16,192,1835,2,3,3,3,2,2,0,0,2,2,3,3,2,1,0,0,8,1).
  744actions(19,16,193,1440,5,8,3,3,2,3,-2,1,5,6,2,1,0,4,0,0,12,1).
  745actions(19,16,194,2277,5,10,3,3,0,0,5,2,8,10,6,4,2,1,0,1,10,1).
  746actions(19,16,195,2453,6,16,3,3,2,2,11,1,1,2,2,2,3,0,0,1,17,1).
  747actions(19,16,196,1851,7,13,3,3,2,2,0,1,2,3,6,1,2,2,0,0,17,1).
  748actions(19,16,197,1696,8,15,3,3,3,4,18,0,1,1,5,3,2,3,0,0,23,0).
  749actions(19,16,198,1692,4,9,3,3,2,2,22,2,5,7,2,2,2,2,2,1,10,0).
  750actions(19,16,199,351,1,1,3,3,0,0,1,0,3,3,0,1,0,0,1,0,2,0).
  751actions(19,16,200,805,2,3,3,3,0,0,10,0,3,3,1,2,0,0,0,0,6,0).
  752actions(19,16,201,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  753actions(19,16,202,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  754actions(19,16,203,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  755actions(19,22,268,2186,3,8,3,3,2,3,-5,3,3,6,3,2,0,1,0,2,8,1).
  756actions(19,22,269,2239,8,17,3,3,5,7,-4,2,9,11,3,3,2,1,1,1,22,1).
  757actions(19,22,270,611,0,2,3,3,0,0,-2,0,1,1,1,2,0,0,0,0,0,1).
  758actions(19,22,271,2010,4,9,3,3,0,0,-4,0,4,4,1,0,0,4,0,0,12,1).
  759actions(19,22,272,2104,7,14,3,3,4,5,1,1,1,2,8,2,2,4,0,0,21,1).
  760actions(19,22,273,1263,1,4,3,3,4,5,-8,0,2,2,5,1,1,5,0,0,6,0).
  761actions(19,22,274,1552,4,5,3,3,0,0,-5,0,5,5,3,3,2,0,1,0,8,0).
  762actions(19,22,275,641,1,3,3,3,0,0,-9,1,2,3,0,1,0,0,1,0,2,0).
  763actions(19,22,276,776,2,5,3,3,1,2,-14,0,1,1,0,3,0,1,0,0,5,0).
  764actions(19,22,277,717,2,4,3,3,4,4,-6,2,1,3,0,0,0,0,0,0,8,0).
  765actions(19,22,278,301,0,1,3,3,0,0,-9,0,0,0,0,0,0,0,0,0,0,0).
  766actions(19,22,279,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  767actions(20,18,217,1761,7,12,3,3,2,5,18,0,4,4,8,0,1,2,1,0,17,1).
  768actions(20,18,218,1497,3,5,3,3,0,0,12,1,4,5,0,1,1,0,0,0,6,1).
  769actions(20,18,219,1575,7,13,3,3,0,0,13,0,0,0,2,1,1,2,1,0,15,1).
  770actions(20,18,220,1575,3,7,3,3,3,4,13,4,3,7,3,2,2,0,0,1,9,1).
  771actions(20,18,221,1954,6,8,3,3,0,1,8,0,4,4,3,2,2,1,0,0,14,1).
  772actions(20,18,222,974,3,6,3,3,0,0,14,1,2,3,2,3,0,2,0,1,7,0).
  773actions(20,18,223,1518,3,9,3,3,0,0,9,0,2,2,3,1,1,0,1,0,7,0).
  774actions(20,18,224,1501,3,6,3,3,0,0,17,0,2,2,0,1,1,0,0,0,9,0).
  775actions(20,18,225,1052,2,4,3,3,4,4,15,2,5,7,0,1,1,1,2,0,8,0).
  776actions(20,18,226,331,0,0,3,3,0,0,-8,0,1,1,0,0,1,1,0,0,0,0).
  777actions(20,18,227,331,1,5,3,3,0,0,-8,0,0,0,1,0,1,0,0,1,2,0).
  778actions(20,18,228,331,1,2,3,3,0,0,-8,0,0,0,0,0,0,0,0,0,2,0).
  779actions(20,19,230,1955,2,10,3,3,0,0,-15,1,3,4,2,4,1,3,0,1,4,1).
  780actions(20,19,231,2069,7,15,3,3,0,0,-1,1,6,7,2,2,0,2,1,1,14,1).
  781actions(20,19,232,1526,3,5,3,3,2,2,-14,6,10,16,4,2,0,0,0,0,8,1).
  782actions(20,19,233,2724,6,12,3,3,6,6,-13,0,3,3,6,1,1,5,0,0,19,1).
  783actions(20,19,234,2502,4,11,3,3,1,1,-27,1,4,5,2,2,1,5,1,0,11,1).
  784actions(20,19,235,1305,2,5,3,3,0,0,-6,1,1,2,1,1,0,1,1,1,5,0).
  785actions(20,19,236,901,5,9,3,3,0,0,-19,0,1,1,0,3,0,0,0,0,10,0).
  786actions(20,19,237,932,1,3,3,3,0,0,-12,0,2,2,1,1,0,0,0,2,2,0).
  787actions(20,19,238,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  788actions(20,19,239,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  789actions(20,19,240,331,1,1,3,3,0,0,8,1,0,1,0,0,0,1,0,0,2,0).
  790actions(20,19,241,154,1,2,3,3,0,0,4,0,1,1,0,0,0,0,0,0,2,0).
  791actions(20,19,242,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  792actions(20,18,345,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  793actions(21,9,103,822,3,9,3,3,0,0,-10,0,3,3,0,0,0,0,0,0,6,1).
  794actions(21,9,104,1614,1,8,3,3,2,2,-12,2,3,5,3,2,0,2,1,2,4,1).
  795actions(21,9,105,1998,9,18,3,3,0,0,-19,3,4,7,4,2,1,0,0,2,18,1).
  796actions(21,9,106,2057,6,9,3,3,0,0,-19,1,5,6,0,1,1,1,0,0,14,1).
  797actions(21,9,107,1996,3,15,3,3,0,0,-6,0,0,0,8,5,1,3,0,0,7,1).
  798actions(21,9,108,884,3,8,3,3,0,0,-8,0,3,3,3,1,0,2,0,1,6,0).
  799actions(21,9,109,1008,5,8,3,3,0,0,2,3,3,6,0,1,1,1,2,0,10,0).
  800actions(21,9,110,1703,4,8,3,3,0,0,-6,0,4,4,3,0,0,0,0,0,9,0).
  801actions(21,9,111,466,1,3,3,3,0,0,1,1,1,2,0,1,1,0,0,1,2,0).
  802actions(21,9,112,768,0,3,3,3,0,2,-6,1,0,1,1,0,1,2,0,0,0,0).
  803actions(21,9,113,880,3,4,3,3,2,2,9,0,1,1,2,2,0,0,0,0,8,0).
  804actions(21,9,114,204,2,2,3,3,0,0,4,0,0,0,0,0,0,0,0,0,4,0).
  805actions(21,9,115,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  806actions(21,14,167,2027,2,7,3,3,2,2,11,1,1,2,2,1,1,1,1,0,6,1).
  807actions(21,14,168,2167,9,15,3,3,4,5,14,4,12,16,10,2,1,2,1,0,24,1).
  808actions(21,14,170,2024,10,18,3,3,0,0,15,0,2,2,2,2,1,2,0,0,21,1).
  809actions(21,14,171,2006,5,11,3,3,3,4,15,1,2,3,7,3,3,2,0,0,14,1).
  810actions(21,14,172,1532,4,6,3,3,0,0,5,2,7,9,0,2,1,5,1,1,8,1).
  811actions(21,14,173,874,1,6,3,3,0,0,-1,1,0,1,7,1,1,1,0,1,2,0).
  812actions(21,14,174,620,2,3,3,3,1,2,2,0,3,3,1,0,0,0,0,0,5,0).
  813actions(21,14,175,903,1,5,3,3,0,0,1,0,1,1,0,0,0,0,0,1,3,0).
  814actions(21,14,176,93,0,0,3,3,0,0,-2,0,0,0,0,0,0,0,0,0,0,0).
  815actions(21,14,177,853,4,5,3,3,0,0,3,0,2,2,0,0,0,0,0,0,8,0).
  816actions(21,14,178,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  817actions(21,14,179,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  818actions(21,14,346,1301,5,5,3,3,1,3,7,3,4,7,2,2,0,1,3,0,11,0).
  819actions(22,3,27,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  820actions(22,3,28,1925,4,10,3,3,0,0,-19,0,8,8,4,3,0,1,2,2,8,1).
  821actions(22,3,29,264,0,0,3,3,0,0,-2,0,0,0,0,1,0,1,0,0,0,1).
  822actions(22,3,30,1963,5,8,3,3,2,2,-25,0,2,2,2,2,0,0,0,0,15,1).
  823actions(22,3,31,1843,5,15,3,3,0,0,-19,0,0,0,10,2,1,4,0,0,11,1).
  824actions(22,3,32,1793,10,16,3,3,2,2,4,4,5,9,0,4,1,2,0,0,22,0).
  825actions(22,3,33,2138,3,12,3,3,4,4,-13,0,2,2,0,2,1,2,0,0,11,1).
  826actions(22,3,34,1422,0,1,3,3,0,0,-9,0,1,1,3,0,1,1,0,0,0,0).
  827actions(22,3,35,2066,6,18,3,3,1,1,-19,0,2,2,2,3,1,0,0,0,16,0).
  828actions(22,3,36,986,3,5,3,3,1,1,-3,0,2,2,2,3,1,0,0,0,16,0).
  829actions(22,3,37,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  830actions(22,28,347,1765,4,9,3,3,3,3,15,0,4,4,1,0,4,1,0,0,11,1).
  831actions(22,28,348,1221,7,11,3,3,1,2,7,3,5,8,0,2,0,1,0,0,15,1).
  832actions(22,28,349,2008,3,9,3,3,2,2,12,1,2,3,5,0,0,0,0,0,8,1).
  833actions(22,28,350,1610,2,5,3,3,0,0,20,0,4,4,2,2,0,1,1,0,5,1).
  834actions(22,28,351,1695,7,13,3,3,4,4,16,0,3,3,8,1,0,4,0,1,18,1).
  835actions(22,28,352,1148,4,8,3,3,4,4,21,2,4,6,5,2,1,2,1,0,13,0).
  836actions(22,28,353,650,1,2,3,3,2,4,-1,1,6,7,2,2,1,2,0,1,4,0).
  837actions(22,28,354,1185,6,8,3,3,0,0,5,0,3,3,2,1,0,1,0,0,13,0).
  838actions(22,28,355,1665,5,10,3,3,2,2,9,0,1,1,1,0,0,0,0,0,12,0).
  839actions(22,28,356,820,4,5,3,3,1,1,5,1,4,5,2,2,0,1,0,0,9,0).
  840actions(22,28,357,632,1,3,3,3,0,0,-4,0,1,1,1,0,0,0,0,0,3,0).
  841actions(22,28,358,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  842actions(22,28,359,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  843actions(22,3,391,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  844actions(23,10,116,1341,2,6,3,3,0,2,7,1,3,4,0,3,2,0,0,0,6,1).
  845actions(23,10,117,1606,14,19,3,3,6,8,17,2,11,13,2,5,0,1,3,1,34,1).
  846actions(23,10,118,1584,5,11,3,3,4,4,14,1,1,2,0,1,1,1,2,1,15,1).
  847actions(23,10,119,1814,4,9,3,3,0,0,19,1,2,3,7,3,0,1,0,0,9,1).
  848actions(23,10,120,2007,3,7,3,3,8,10,29,0,3,3,12,4,1,3,0,0,14,1).
  849actions(23,10,121,996,3,5,3,3,0,0,18,0,2,2,0,1,0,1,3,1,8,0).
  850actions(23,10,122,1436,5,13,3,3,0,1,13,2,2,4,7,3,0,1,0,2,12,0).
  851actions(23,10,123,1784,9,12,3,3,0,0,18,0,3,3,1,3,2,1,2,1,24,0).
  852actions(23,10,124,1282,5,6,3,3,0,0,16,1,4,5,2,4,2,0,2,1,10,0).
  853actions(23,10,125,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  854actions(23,10,126,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  855actions(23,10,127,551,2,4,3,3,0,0,-1,0,1,1,3,2,0,2,0,0,5,0).
  856actions(23,10,128,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  857actions(23,12,141,1265,0,3,3,3,5,10,-7,2,5,7,1,2,0,1,0,0,5,1).
  858actions(23,12,142,630,3,4,3,3,0,0,-9,0,3,3,1,2,0,0,0,0,6,1).
  859actions(23,12,143,1210,4,9,3,3,1,2,-10,2,4,6,1,3,0,1,1,2,9,1).
  860actions(23,12,144,1962,9,17,3,3,9,9,-18,2,6,8,3,2,0,3,0,4,27,1).
  861actions(23,12,145,1209,3,7,3,3,0,0,-13,0,1,1,6,1,0,2,0,2,6,1).
  862actions(23,12,146,1235,3,5,3,3,3,4,-19,0,2,2,1,1,0,0,1,0,9,0).
  863actions(23,12,147,1182,3,6,3,3,3,4,-21,0,4,4,2,3,2,1,0,1,9,0).
  864actions(23,12,148,1652,1,4,3,3,4,6,-17,0,3,3,2,1,1,4,0,1,6,0).
  865actions(23,12,149,1748,5,12,3,3,5,5,-17,1,1,2,2,5,0,1,1,2,17,0).
  866actions(23,12,150,1795,4,5,3,3,5,5,-13,1,4,5,1,3,1,1,4,0,13,0).
  867actions(23,12,151,511,0,2,3,3,0,0,-6,0,1,1,1,2,1,2,0,0,0,0).
  868actions(23,12,152,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  869actions(23,12,153,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  870actions(24,13,154,2196,7,16,3,3,3,4,0,3,3,6,1,2,1,3,1,1,19,1).
  871actions(24,13,155,1440,2,5,3,3,6,6,19,0,3,3,0,3,1,2,1,0,12,0).
  872actions(24,13,156,1754,2,2,3,3,0,0,-20,1,10,11,0,4,0,0,1,0,4,1).
  873actions(24,13,157,2543,9,16,3,3,3,3,3,0,3,3,5,3,3,2,1,1,23,1).
  874actions(24,13,158,2116,6,17,3,3,4,5,5,0,2,2,9,3,3,2,0,1,20,1).
  875actions(24,13,160,1033,2,4,3,3,0,0,5,0,0,0,0,1,1,0,0,0,5,0).
  876actions(24,13,161,271,0,1,3,3,0,0,-4,0,0,0,0,0,0,0,0,0,0,0).
  877actions(24,13,162,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  878actions(24,13,163,612,1,1,3,3,2,2,10,2,2,4,0,2,0,1,0,0,4,0).
  879actions(24,13,164,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  880actions(24,13,165,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  881actions(24,13,166,2022,7,15,3,3,9,10,-6,4,2,6,3,3,1,3,0,1,23,1).
  882actions(24,13,169,413,1,2,3,3,0,0,8,0,1,1,0,3,0,0,0,0,2,0).
  883actions(24,29,360,2116,4,12,3,3,1,1,-7,6,5,11,1,3,1,1,0,1,10,1).
  884actions(24,29,361,1843,4,9,3,3,2,2,1,1,2,3,1,5,0,1,1,0,14,1).
  885actions(24,29,362,1564,6,7,3,3,1,1,6,3,4,7,1,2,1,1,0,0,13,1).
  886actions(24,29,363,2535,2,11,3,3,11,12,-6,0,1,1,8,3,0,4,0,1,15,1).
  887actions(24,29,364,1772,6,9,3,3,1,1,4,0,1,1,3,4,0,5,0,1,14,1).
  888actions(24,29,365,1376,5,11,3,3,3,4,-2,1,3,4,0,3,0,0,2,1,15,0).
  889actions(24,29,366,1823,3,7,3,3,5,7,-9,2,5,7,2,3,1,1,1,0,11,0).
  890actions(24,29,367,1150,6,12,3,3,4,5,-5,1,3,4,1,2,1,1,0,0,16,0).
  891actions(24,29,368,221,0,0,3,3,0,0,-2,0,0,0,0,1,0,0,0,0,0,0).
  892actions(24,29,369,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  893actions(24,29,370,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  894actions(24,29,371,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  895actions(24,29,372,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  896actions(25,2,14,1852,6,18,3,3,0,0,-4,1,6,7,6,2,2,3,0,0,14,1).
  897actions(25,2,15,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  898actions(25,2,16,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  899actions(25,2,17,2170,8,15,3,3,3,3,0,1,2,3,1,1,0,1,0,0,21,1).
  900actions(25,2,18,1951,3,9,3,3,0,0,1,0,7,7,10,4,2,3,0,1,7,1).
  901actions(25,2,19,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  902actions(25,2,20,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  903actions(25,2,21,1154,3,7,3,3,2,2,-6,1,0,1,3,1,0,0,0,0,8,0).
  904actions(25,2,22,1682,2,6,3,3,2,4,11,1,4,5,2,3,0,0,2,0,6,1).
  905actions(25,2,23,1797,6,17,3,3,1,1,-14,2,0,2,1,3,1,1,0,1,17,0).
  906actions(25,2,24,394,1,3,3,3,0,0,-5,0,0,0,0,0,1,0,0,1,3,0).
  907actions(25,2,25,1726,5,15,3,3,8,10,1,6,9,15,0,6,0,1,4,1,18,1).
  908actions(25,2,26,1674,3,6,3,3,0,0,-9,2,10,12,3,1,1,1,0,0,8,0).
  909actions(25,11,129,2562,12,24,3,3,6,7,-1,0,5,5,4,2,2,2,0,1,31,1).
  910actions(25,11,130,1026,1,3,3,3,1,2,-1,1,1,2,0,2,1,0,0,0,3,1).
  911actions(25,11,131,1287,8,14,3,3,4,5,-7,3,7,10,2,4,1,1,0,1,20,1).
  912actions(25,11,132,2707,5,11,3,3,1,1,7,2,2,4,0,2,1,1,0,2,12,1).
  913actions(25,11,133,2763,12,22,3,3,2,4,3,1,3,4,5,3,0,3,0,2,27,1).
  914actions(25,11,134,1927,3,8,3,3,3,4,9,0,7,7,2,2,0,0,0,0,11,0).
  915actions(25,11,135,603,0,2,3,3,1,2,4,0,3,3,0,0,0,1,1,0,1,0).
  916actions(25,11,136,117,0,0,3,3,0,0,2,0,0,0,0,0,0,0,0,0,0,0).
  917actions(25,11,137,1408,1,2,3,3,0,2,9,1,11,12,3,3,3,0,3,0,2,0).
  918actions(25,11,138,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  919actions(25,11,139,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  920actions(25,11,140,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  921actions(25,11,373,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  922actions(25,11,374,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  923actions(26,28,347,1721,8,15,3,3,0,0,0,0,2,2,3,4,3,2,0,1,17,1).
  924actions(26,28,348,1696,5,15,3,3,7,8,-9,2,6,8,1,2,0,0,2,1,17,1).
  925actions(26,28,349,1498,4,6,3,3,0,0,-16,1,2,3,2,3,0,4,0,0,8,0).
  926actions(26,28,350,2185,4,9,3,3,1,2,-5,1,4,5,2,2,0,1,0,0,11,1).
  927actions(26,28,351,1534,3,10,3,3,0,1,-4,2,2,4,3,2,0,3,0,1,6,1).
  928actions(26,28,352,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  929actions(26,28,353,1160,1,5,3,3,0,0,-2,3,0,3,2,0,1,2,1,2,2,1).
  930actions(26,28,354,1429,8,13,3,3,0,0,-11,2,4,6,1,1,1,2,0,0,21,0).
  931actions(26,28,355,1822,3,10,3,3,1,1,-16,0,6,6,1,1,0,4,0,0,8,0).
  932actions(26,28,356,809,1,2,3,3,0,0,-1,2,1,3,2,2,0,0,0,0,2,0).
  933actions(26,28,357,250,1,2,3,3,0,0,2,0,0,0,1,1,0,0,0,0,2,0).
  934actions(26,28,359,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  935actions(26,28,375,296,0,1,3,3,0,0,2,0,2,2,0,0,0,0,0,0,0,0).
  936actions(26,30,376,2358,11,26,3,3,6,6,13,0,7,7,3,1,0,4,1,1,28,1).
  937actions(26,30,377,2390,5,11,3,3,1,2,4,2,10,12,0,0,1,2,3,1,11,1).
  938actions(26,30,378,719,0,0,3,3,0,0,2,0,1,1,1,3,0,1,1,0,0,1).
  939actions(26,30,379,885,2,2,3,3,0,0,1,2,3,5,0,2,0,1,0,0,5,1).
  940actions(26,30,380,1838,10,20,3,3,6,6,2,0,1,1,6,1,4,2,0,0,27,1).
  941actions(26,30,381,1818,1,5,3,3,1,2,10,0,2,2,2,1,5,0,0,0,4,0).
  942actions(26,30,382,734,2,4,3,3,1,2,6,3,2,5,0,3,1,1,0,0,5,0).
  943actions(26,30,383,803,1,1,3,3,2,2,8,0,0,0,2,2,1,1,0,0,4,0).
  944actions(26,30,384,1823,6,8,3,3,0,0,13,1,3,4,4,0,1,1,0,1,14,0).
  945actions(26,30,385,924,1,3,3,3,3,3,1,0,1,1,0,3,1,0,0,0,6,0).
  946actions(26,30,386,55,1,1,3,3,0,0,0,0,1,1,0,0,0,0,0,0,2,0).
  947actions(26,30,387,52,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  948actions(26,30,388,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  949actions(27,4,39,1851,2,5,3,3,3,4,3,3,6,9,2,0,0,3,3,0,7,1).
  950actions(27,4,40,2088,10,18,3,3,2,2,2,0,11,11,1,4,2,2,1,1,26,1).
  951actions(27,4,41,1715,3,4,3,3,6,6,-7,3,3,6,1,4,0,2,2,0,12,1).
  952actions(27,4,42,2209,4,12,3,3,3,4,-4,0,4,4,9,0,0,2,1,0,12,1).
  953actions(27,4,43,1613,8,13,3,3,0,0,-15,0,2,2,1,4,0,1,0,0,19,1).
  954actions(27,4,44,1522,6,12,3,3,0,0,8,0,2,2,1,3,1,0,0,1,16,0).
  955actions(27,4,45,985,4,7,3,3,0,0,16,0,3,3,1,3,1,0,1,1,8,0).
  956actions(27,4,46,1402,2,6,3,3,0,0,17,0,3,3,7,1,0,0,0,1,6,0).
  957actions(27,4,47,835,2,3,3,3,1,2,13,1,4,5,1,2,0,1,1,0,5,0).
  958actions(27,4,48,180,0,2,3,3,2,2,-3,1,0,1,0,0,0,0,0,0,2,0).
  959actions(27,4,49,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  960actions(27,4,50,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  961actions(27,4,51,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  962actions(27,13,154,2289,2,9,3,3,1,2,-5,1,5,6,2,2,0,2,1,0,6,1).
  963actions(27,13,155,639,0,4,3,3,0,0,1,0,0,0,2,1,0,0,0,1,0,0).
  964actions(27,13,156,2317,9,12,3,3,3,8,1,5,10,15,0,3,2,0,2,1,21,1).
  965actions(27,13,157,2275,7,14,3,3,6,6,5,0,2,2,1,3,3,1,0,0,22,1).
  966actions(27,13,158,2373,7,14,3,3,2,2,-1,2,3,5,9,3,1,1,0,0,17,1).
  967actions(27,13,160,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  968actions(27,13,161,124,0,1,3,3,0,0,-1,0,0,0,0,1,0,0,0,0,0,0).
  969actions(27,13,162,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  970actions(27,13,163,588,2,4,3,3,0,0,-10,0,1,1,0,2,0,1,0,1,4,0).
  971actions(27,13,164,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  972actions(27,13,166,2379,9,23,3,3,7,7,-5,4,6,10,11,5,1,1,1,5,25,1).
  973actions(27,13,169,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  974actions(27,13,389,1416,3,10,3,3,4,4,-15,0,2,2,1,0,0,0,0,1,12,0).
  975actions(28,9,103,842,6,8,3,3,0,0,3,2,0,2,1,0,0,0,0,0,12,1).
  976actions(28,9,104,2499,7,22,3,3,6,6,17,3,12,15,4,4,2,1,3,2,20,1).
  977actions(28,9,105,2145,8,16,3,3,8,10,2,1,4,5,3,6,0,3,1,0,24,1).
  978actions(28,9,106,2324,3,7,3,3,3,3,11,0,1,1,1,1,1,2,0,0,10,1).
  979actions(28,9,107,2120,5,14,3,3,10,11,8,0,5,5,4,4,2,1,0,1,21,1).
  980actions(28,9,108,1040,1,3,3,3,2,2,5,0,1,1,2,3,2,1,0,1,4,0).
  981actions(28,9,109,374,1,4,3,3,0,0,-7,2,0,2,0,2,0,0,0,0,2,0).
  982actions(28,9,110,1056,0,4,3,3,2,2,-3,0,1,1,2,1,0,2,0,0,2,0).
  983actions(28,9,111,686,0,1,3,3,0,0,3,1,4,5,0,1,0,1,0,0,0,0).
  984actions(28,9,112,1224,1,4,3,3,3,4,-3,1,0,1,1,4,2,0,0,0,5,0).
  985actions(28,9,113,90,0,0,3,3,0,0,4,0,0,0,0,0,0,0,0,0,0,0).
  986actions(28,9,114,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  987actions(28,9,115,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  988actions(28,10,116,774,0,2,3,3,0,0,-17,0,1,1,0,1,1,1,0,0,0,1).
  989actions(28,10,117,1410,7,13,3,3,3,4,-7,5,7,12,2,2,1,5,0,0,17,1).
  990actions(28,10,118,1667,4,10,3,3,4,5,-4,1,2,3,2,5,0,1,1,1,13,1).
  991actions(28,10,119,2350,6,13,3,3,5,6,-11,2,7,9,4,5,0,2,1,1,21,1).
  992actions(28,10,120,1926,3,8,3,3,10,12,7,0,1,1,3,2,2,1,0,0,16,0).
  993actions(28,10,121,1430,1,9,3,3,3,3,7,2,5,7,1,5,2,2,2,1,6,0).
  994actions(28,10,122,1185,2,7,3,3,2,2,5,0,2,2,0,2,0,2,0,0,6,0).
  995actions(28,10,123,2421,5,13,3,3,0,0,-8,1,3,4,2,2,0,4,0,0,11,1).
  996actions(28,10,124,1237,1,5,3,3,0,0,-12,3,4,7,2,3,1,2,0,1,2,0).
  997actions(28,10,125,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  998actions(28,10,126,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
  999actions(28,10,127,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1000actions(28,10,128,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1001actions(29,24,293,1006,0,3,3,3,0,0,5,0,2,2,1,0,1,0,0,1,0,1).
 1002actions(29,24,294,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1003actions(29,24,295,2205,13,24,3,3,3,3,7,4,12,16,0,1,0,2,1,3,29,1).
 1004actions(29,24,296,1373,2,7,3,3,3,3,15,0,3,3,2,5,1,3,2,1,7,1).
 1005actions(29,24,297,2089,5,15,3,3,2,2,20,2,8,10,10,2,1,4,0,2,13,1).
 1006actions(29,24,298,1487,2,4,3,3,4,6,11,1,3,4,0,2,0,2,2,0,8,1).
 1007actions(29,24,299,675,1,1,3,3,0,0,4,1,1,2,1,1,0,0,0,0,13,0).
 1008actions(29,24,300,1507,4,10,3,3,3,3,-4,0,3,3,2,1,0,2,0,1,12,0).
 1009actions(29,24,301,791,1,2,3,3,0,0,-9,0,0,0,1,2,1,0,0,0,2,0).
 1010actions(29,24,302,1874,1,5,3,3,3,4,6,0,3,3,3,1,1,1,0,2,5,0).
 1011actions(29,24,303,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1012actions(29,24,304,1393,4,7,3,3,1,2,0,1,1,2,1,1,0,0,0,0,13,0).
 1013actions(29,24,305,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1014actions(29,27,331,1855,1,3,3,3,0,0,-21,0,3,3,1,1,2,1,3,0,2,1).
 1015actions(29,27,332,1778,5,20,3,3,0,0,-6,2,4,6,1,4,3,2,5,1,10,1).
 1016actions(29,27,333,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1017actions(29,27,334,1386,2,10,3,3,4,4,-21,1,2,3,0,1,0,1,0,2,8,1).
 1018actions(29,27,335,1287,5,11,3,3,0,0,-20,1,1,2,7,1,0,1,0,0,11,1).
 1019actions(29,27,336,791,0,1,3,3,0,0,-18,1,2,3,0,4,0,0,0,0,0,1).
 1020actions(29,27,337,1822,8,18,3,3,4,4,7,2,4,6,2,4,2,2,0,1,21,0).
 1021actions(29,27,338,1236,3,7,3,3,0,0,8,0,2,2,2,1,0,2,1,1,6,0).
 1022actions(29,27,339,1888,5,12,3,3,4,5,7,2,6,8,1,3,1,2,1,1,15,0).
 1023actions(29,27,340,1255,0,0,3,3,0,0,14,0,2,2,1,2,0,1,0,0,0,0).
 1024actions(29,27,341,1102,2,5,3,3,3,5,-5,5,3,8,0,4,0,1,0,1,7,0).
 1025actions(29,27,342,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1026actions(29,27,343,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1027actions(30,17,204,1989,8,17,3,3,3,4,-2,2,3,5,1,2,1,0,0,2,24,1).
 1028actions(30,17,206,2022,10,14,3,3,2,3,11,3,6,9,0,3,0,3,1,0,22,1).
 1029actions(30,17,207,2375,8,19,3,3,4,5,9,0,4,4,9,3,0,3,1,1,20,1).
 1030actions(30,17,209,1526,2,5,3,3,0,0,7,1,6,7,2,3,2,0,0,0,5,1).
 1031actions(30,17,210,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1032actions(30,17,211,941,0,1,3,3,0,0,2,0,2,2,1,2,0,1,1,0,0,0).
 1033actions(30,17,212,1963,4,12,3,3,0,0,7,0,5,5,3,3,1,2,0,0,10,1).
 1034actions(30,17,213,1031,3,4,3,3,0,0,1,0,3,3,2,0,0,0,2,0,6,0).
 1035actions(30,17,214,1373,3,8,3,3,2,2,10,0,2,2,5,1,2,2,0,0,10,0).
 1036actions(30,17,215,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1037actions(30,17,216,1180,2,4,3,3,1,2,-5,3,2,5,0,3,0,0,0,0,5,0).
 1038actions(30,25,306,2416,7,17,3,3,9,10,-4,1,5,6,3,3,0,3,0,0,26,1).
 1039actions(30,25,307,2061,9,16,3,3,3,3,-5,1,6,7,4,1,2,0,0,0,21,1).
 1040actions(30,25,308,1911,5,13,3,3,2,3,-2,1,1,2,0,4,1,1,1,1,12,1).
 1041actions(30,25,309,1693,2,5,3,3,1,2,-13,0,3,3,1,4,1,2,0,0,6,1).
 1042actions(30,25,310,2106,2,5,3,3,3,4,-3,0,4,4,5,1,1,1,0,0,8,1).
 1043actions(30,25,311,819,3,7,3,3,0,2,-3,1,4,5,1,1,0,0,0,0,6,0).
 1044actions(30,25,312,1188,1,8,3,3,0,0,3,3,2,5,1,2,1,1,0,4,2,0).
 1045actions(30,25,313,968,1,2,3,3,2,2,-4,1,2,3,0,3,0,2,1,0,4,0).
 1046actions(30,25,314,464,0,1,3,3,0,0,-4,0,3,3,1,0,0,0,1,0,0,0).
 1047actions(30,25,315,774,3,4,3,3,2,2,-5,0,1,1,3,0,0,0,0,0,9,0).
 1048actions(30,25,316,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1049actions(30,25,317,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1050actions(30,25,318,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1051actions(30,17,344,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1052actions(30,17,390,0,0,0,3,3,0,0,0,0,0,0,0,0,0,0,0,0,0,0).
 1053%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1054
 1055:- begin_bg. 1056%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1057% Players information
 1058%%
 1059% predicate: player(PlayerId,PlayerName).
 1060
 1061player(1,"Nicolas Batum").
 1062player(2,"LaMarcus Aldridge").
 1063player(3,"Robin Lopez").
 1064player(4,"Wesley Matthews").
 1065player(5,"Damian Lillard").
 1066player(6,"Thomas Robinson").
 1067player(7,"Maurice Williams").
 1068player(8,"Will Barton").
 1069player(9,"Dorell Wright").
 1070player(10,"Earl Watson").
 1071player(11,"CJ McCollum").
 1072player(12,"Meyers Leonard").
 1073player(13,"Victor Claver").
 1074player(14,"Kent Bazemore").
 1075player(15,"Pau Gasol").
 1076player(16,"Chris Kaman").
 1077player(17,"Jodie Meeks").
 1078player(18,"Kendall Marshall").
 1079player(19,"Steve Nash").
 1080player(20,"Xavier Henry").
 1081player(21,"Robert Sacre").
 1082player(22,"Ryan Kelly").
 1083player(23,"Nick Young").
 1084player(24,"Marshon Brooks").
 1085player(25,"Jordan Hill").
 1086player(26,"Wesley Johnson").
 1087player(27,"Andre Iguodala").
 1088player(28,"Draymond Green").
 1089player(29,"Jermaine O'Neal").
 1090player(30,"Klay Thompson").
 1091player(31,"Stephen Curry").
 1092player(32,"Marreese Speights").
 1093player(33,"Harrison Barnes").
 1094player(34,"Steve Blake").
 1095player(35,"Jordan Crawford").
 1096player(36,"Hilton Armstrong").
 1097player(37,"Andrew Bogut").
 1098player(38,"David Lee").
 1099player(39,"Shawn Marion").
 1100player(40,"Dirk Nowitzki").
 1101player(41,"Samuel Dalembert").
 1102player(42,"Monta Ellis").
 1103player(43,"Jose Calderon").
 1104player(44,"Vince Carter").
 1105player(45,"Brandan Wright").
 1106player(46,"Devin Harris").
 1107player(47,"Jae Crowder").
 1108player(48,"DeJuan Blair").
 1109player(49,"Wayne Ellington").
 1110player(50,"Bernard James").
 1111player(51,"Shane Larkin").
 1112player(52,"Chandler Parsons").
 1113player(53,"Donatas Motiejunas").
 1114player(54,"Omer Asik").
 1115player(55,"James Harden").
 1116player(56,"Jeremy Lin").
 1117player(57,"Omri Casspi").
 1118player(58,"Francisco Garcia").
 1119player(59,"Isaiah Canaan").
 1120player(60,"Jordan Hamilton").
 1121player(61,"Patrick Beverley").
 1122player(62,"Dwight Howard").
 1123player(63,"Terrence Jones").
 1124player(64,"Greg Smith").
 1125player(65,"Joe Johnson").
 1126player(66,"Paul Pierce").
 1127player(67,"Mason Plumlee").
 1128player(68,"Shaun Livingston").
 1129player(69,"Deron Williams").
 1130player(70,"Alan Anderson").
 1131player(71,"Andray Blatche").
 1132player(72,"Mizra Teletovic").
 1133player(73,"Jorge Gutierrez").
 1134player(74,"Marquis Teague").
 1135player(75,"Jason Collins").
 1136player(76,"Andrei Kirilenko").
 1137player(77,"Marcus Thornton").
 1138player(78,"JR Smith").
 1139player(79,"Carmelo Anthony").
 1140player(80,"Tyson Chandler").
 1141player(81,"Iman Shumpert").
 1142player(82,"Raymond Felton").
 1143player(83,"Timothy Hardaway Jr.").
 1144player(84,"Pablo Prigioni").
 1145player(85,"Cole Aldrich").
 1146player(86,"Jeremy Tyler").
 1147player(87,"Shannon Brown").
 1148player(88,"Toure Murry").
 1149player(89,"Amar'e Stoudemire").
 1150player(90,"Richard Jefferson").
 1151player(91,"Marvin Williams").
 1152player(92,"Derrick Favors").
 1153player(93,"Gordon Hayward").
 1154player(94,"Trey Burke").
 1155player(95,"Enes Kanter").
 1156player(96,"Alec Burks").
 1157player(97,"Diante Garrett").
 1158player(98,"Ian Clark").
 1159player(99,"Rudy Gobert").
 1160player(100,"Jeremy Evans").
 1161player(101,"John Lucas III").
 1162player(102,"Brandon Rush").
 1163player(103,"Tayshaun Prince").
 1164player(104,"Zach Randolph").
 1165player(105,"Marc Gasol").
 1166player(106,"Courtney Lee").
 1167player(107,"Mike Conley").
 1168player(108,"Nick Calathes").
 1169player(109,"Ed Davis").
 1170player(110,"Mike Miller").
 1171player(111,"Kosta Koufos").
 1172player(112,"Tony Allen").
 1173player(113,"James Johnson").
 1174player(114,"Jon Leuer").
 1175player(115,"Beno Udrih").
 1176player(116,"Quincy Miller").
 1177player(117,"Kenneth Faried").
 1178player(118,"Timofey Mozgov").
 1179player(119,"Randy Foye").
 1180player(120,"Ty Lawson").
 1181player(121,"Darrell Arthur").
 1182player(122,"Evan Fournier").
 1183player(123,"Aaron Brooks").
 1184player(124,"Jan Vesely").
 1185player(125,"Wilson Chandler").
 1186player(126,"JJ Hickson").
 1187player(127,"Anthony Randolph").
 1188player(128,"Nate Robinson").
 1189player(129,"Rudy Gay").
 1190player(130,"Reggie Evans").
 1191player(131,"DeMarcus Cousins").
 1192player(132,"Ben McLemore").
 1193player(133,"Ray McCallum").
 1194player(134,"Travis Outlaw").
 1195player(135,"Derrick Williams").
 1196player(136,"Jared Cunningham").
 1197player(137,"Jason Thompson").
 1198player(138,"Quincy Acy").
 1199player(139,"Aaron Gray").
 1200player(140,"Isaiah Thomas").
 1201player(141,"Al-Farouq Aminu").
 1202player(142,"Anthony Davis").
 1203player(143,"Greg Stiemsma").
 1204player(144,"Tyreke Evans").
 1205player(145,"Brian Roberts").
 1206player(146,"Darius Miller").
 1207player(147,"Alexis Ajinca").
 1208player(148,"Austin Rivers").
 1209player(149,"Anthony Morrow").
 1210player(150,"Jeff Withey").
 1211player(151,"Luke Babbitt").
 1212player(152,"Eric Gordon").
 1213player(153,"Jason Smith").
 1214player(154,"Matt Barnes").
 1215player(155,"Jared Dudley").
 1216player(156,"DeAndre Jordan").
 1217player(157,"Darren Collison").
 1218player(158,"Chris Paul").
 1219player(159,"Hidayet Turkoglu").
 1220player(160,"Willie Green").
 1221player(161,"Reggie Bullock").
 1222player(162,"Ryan Hollins").
 1223player(163,"Glen Davis").
 1224player(164,"Jamal Crawford").
 1225player(165,"Danny Granger").
 1226player(166,"Blake Griffin").
 1227player(167,"Corey Brewer").
 1228player(168,"Kevin Love").
 1229player(169,"Hidayet Turkoglu").
 1230player(170,"Kevin Martin").
 1231player(171,"Ricky Rubio").
 1232player(172,"Gorgui Dieng").
 1233player(173,"Jose Barea").
 1234player(174,"Dante Cunningham").
 1235player(175,"Chase Budinger").
 1236player(176,"Robbie Hummel").
 1237player(177,"Shabazz Muhammad").
 1238player(178,"Luc Mbah a Moute").
 1239player(179,"Alexey Shved").
 1240player(180,"Jeff Green").
 1241player(181,"Brandon Bass").
 1242player(182,"Kris Humphries").
 1243player(183,"Avery Bradley").
 1244player(184,"Jerryd Bayless").
 1245player(185,"Jared Sullinger").
 1246player(186,"Christapher Johnson").
 1247player(187,"Phil Pressey").
 1248player(188,"Kelly Olynyk").
 1249player(189,"Chris Babb").
 1250player(190,"Joel Anthony").
 1251player(191,"Rajon Rondo").
 1252player(192,"Mike Dunleavy").
 1253player(193,"Carlos Boozer").
 1254player(194,"Joakim Noah").
 1255player(195,"Jimmy Butler").
 1256player(196,"Kirk Hinrich").
 1257player(197,"DJ Augustin").
 1258player(198,"Taj Gibson").
 1259player(199,"Nazr Mohammed").
 1260player(200,"Tony Snell").
 1261player(201,"Jimmer Fredette").
 1262player(202,"Erik Murphy").
 1263player(203,"Tornike Shengelia").
 1264player(204,"Terrence Ross").
 1265player(205,"Amir Johnson").
 1266player(206,"Jonas Valanciunas").
 1267player(207,"Demar DeRozan").
 1268player(208,"Kyle Lowry").
 1269player(209,"Patrick Patterson").
 1270player(210,"Steve Novak").
 1271player(211,"John Salmons").
 1272player(212,"Greivis Vasquez").
 1273player(213,"Chuck Hayes").
 1274player(214,"Nando De Colo").
 1275player(215,"Landry Fields").
 1276player(216,"Tyler Hansbrough").
 1277player(217,"Lebron James").
 1278player(218,"Udonis Haslem").
 1279player(219,"Chris Bosh").
 1280player(220,"Toney Douglas").
 1281player(221,"Mario Chalmers").
 1282player(222,"Rashad Lewis").
 1283player(223,"Norris Cole").
 1284player(224,"James Jones").
 1285player(225,"Chris Andersen").
 1286player(226,"Shane Battier").
 1287player(227,"Michael Beasley").
 1288player(228,"Justin Hamilton").
 1289player(229,"Dwayne Wade").
 1290player(230,"Khris Middleton").
 1291player(231,"Jeff Adrien").
 1292player(232,"Zaza Pachulia").
 1293player(233,"Ramon Sessions").
 1294player(234,"Brandon Knight").
 1295player(235,"Giannis Antetokounmpo").
 1296player(236,"John Henson").
 1297player(237,"Ekpe Udoh").
 1298player(238,"Ersan Ilyasova").
 1299player(239,"OJ Mayo").
 1300player(240,"Miroslav Raduljica").
 1301player(241,"DJ Stephens").
 1302player(242,"Nate Wolters").
 1303player(243,"Josh Smith").
 1304player(244,"Greg Monroe").
 1305player(245,"Andre Drummond").
 1306player(246,"Kyle Singler").
 1307player(247,"Brandon Jennings").
 1308player(248,"Rodney Stuckey").
 1309player(249,"Jonas Jerebko").
 1310player(250,"Kentavious Caldwell-Pope").
 1311player(251,"Will Bynum").
 1312player(252,"Charlie Villanueva").
 1313player(253,"Luigi Datome").
 1314player(254,"Tony Mitchell").
 1315player(255,"Peyton Siva").
 1316player(256,"Hollis Thompson").
 1317player(257,"Thaddeus Young").
 1318player(258,"Henry Sims").
 1319player(259,"James Anderson").
 1320player(260,"Michael Carter-Williams").
 1321player(261,"Tony Wroten").
 1322player(262,"Jarvis Varnado").
 1323player(263,"Elliot Williams").
 1324player(264,"Casper Ware").
 1325player(265,"Brandon Davies").
 1326player(266,"Arnett Moultrie").
 1327player(267,"James Nunnally").
 1328player(268,"DeMarre Carroll").
 1329player(269,"Paul Millsap").
 1330player(270,"Pero Antic").
 1331player(271,"Kyle Korver").
 1332player(272,"Jeff Teague").
 1333player(273,"Louis Williams").
 1334player(274,"Elton Brand").
 1335player(275,"Mike Scott").
 1336player(276,"Dennis Schroder").
 1337player(277,"Mike Muscala").
 1338player(278,"Shelvin Mack").
 1339player(279,"Cartier Martin").
 1340player(280,"Trevor Ariza").
 1341player(281,"Trevor Booker").
 1342player(282,"Marcin Gortat").
 1343player(283,"Bradley Beal").
 1344player(284,"John Wall").
 1345player(285,"Drew Gooden").
 1346player(286,"Martell Webster").
 1347player(287,"Al Harrington").
 1348player(288,"Andre Miller").
 1349player(289,"Kevin Seraphin").
 1350player(290,"Otto Porter").
 1351player(291,"Chris Singleton").
 1352player(292,"Garrett Temple").
 1353player(293,"Michael Kidd-Gilchrist").
 1354player(294,"Josh McRoberts").
 1355player(295,"Al Jefferson").
 1356player(296,"Gerald Henderson").
 1357player(297,"Kemba Walker").
 1358player(298,"Cody Zeller").
 1359player(299,"Bismack Biyombo").
 1360player(300,"Gary Neal").
 1361player(301,"Luke Ridnour").
 1362player(302,"Chris Douglas-Roberts").
 1363player(303,"Jannero Pargo").
 1364player(304,"Anthony Tolliver").
 1365player(305,"DJ White").
 1366player(306,"Paul George").
 1367player(307,"David West").
 1368player(308,"Roy Hibbert").
 1369player(309,"Lance Stephenson").
 1370player(310,"George Hill").
 1371player(311,"Luis Scola").
 1372player(312,"Evan Turner").
 1373player(313,"Ian Mahinmi").
 1374player(314,"Rasual Butler").
 1375player(315,"Donald Sloan").
 1376player(316,"Lavoy Allen").
 1377player(317,"Chris Copeland").
 1378player(318,"Solomon Hill").
 1379player(319,"Luol Deng").
 1380player(320,"Tristan Thompson").
 1381player(321,"Spencer Hawes").
 1382player(322,"Dion Waiters").
 1383player(323,"Kyrie Irving").
 1384player(324,"Jarrett Jack").
 1385player(325,"Matthew Dellavedova").
 1386player(326,"Tyler Zeller").
 1387player(327,"Alonzo Gee").
 1388player(328,"Sergey Karasev").
 1389player(329,"Scotty Hopson").
 1390player(330,"Anderson Varejao").
 1391player(331,"Maurice Harkless").
 1392player(332,"Kyle O'Quinn").
 1393player(333,"Nikola Vucevic").
 1394player(334,"Arron Afflalo").
 1395player(335,"Jameer Nelson").
 1396player(336,"Andrew Nicholson").
 1397player(337,"Victor Oladipo").
 1398player(338,"Etwaun Moore").
 1399player(339,"Tobias Harris").
 1400player(340,"Doron Lamb").
 1401player(341,"Dewayne Dedmon").
 1402player(342,"Jason Maxiell").
 1403player(343,"Ronnie Price").
 1404player(344,"Julyan Stone").
 1405player(345,"Ray Allen").
 1406player(346,"Ronny Turiaf").
 1407player(347,"Kawhi Leonard").
 1408player(348,"Tim Duncan").
 1409player(349,"Boris Diaw").
 1410player(350,"Daniel Green").
 1411player(351,"Tony Parker").
 1412player(352,"Emanuel Ginobli").
 1413player(353,"Tiago Splitter").
 1414player(354,"Patrick Mills").
 1415player(355,"Marco Belinelli").
 1416player(356,"Jeff Ayres").
 1417player(357,"Cory Joseph").
 1418player(358,"Aron Baynes").
 1419player(359,"Austin Daye").
 1420player(360,"PJ Tucker").
 1421player(361,"Channing Frye").
 1422player(362,"Miles Plumlee").
 1423player(363,"Goran Dragic").
 1424player(364,"Eric Bledsoe").
 1425player(365,"Gerald Green").
 1426player(366,"Markieff Morris").
 1427player(367,"Marcus Morris").
 1428player(368,"Ish Smith").
 1429player(369,"Dionte Christmas").
 1430player(370,"Archie Goodwin").
 1431player(371,"Alex Len").
 1432player(372,"Shavlik Randolph").
 1433player(373,"Orlando Johnson").
 1434player(374,"Royce White").
 1435player(375,"Damion James").
 1436player(376,"Kevin Durant").
 1437player(377,"Serge Ibaka").
 1438player(378,"Kendrick Perkins").
 1439player(379,"Andre Roberson").
 1440player(380,"Russell Westbrook").
 1441player(381,"Caron Butler").
 1442player(382,"Steven Adams").
 1443player(383,"Nick Collison").
 1444player(384,"Reggie Jackson").
 1445player(385,"Derek Fisher").
 1446player(386,"Jeremy Lamb").
 1447player(387,"Perry Jones").
 1448player(388,"Hasheem Thabeet").
 1449player(389,"JJ Redick").
 1450player(390,"Dwight Buycks").
 1451player(391,"David Lee").
 1452player(392,"Nikola Pekovic").
 1453%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1454
 1455%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1456% Teams information
 1457%%
 1458% predicate: team(TeamId,TeamName).
 1459
 1460team(1,"Portland Trail Blazers").
 1461team(2,"Los Angeles Lakers").
 1462team(3,"Golden State Warriors").
 1463team(4,"Dallas Mavericks").
 1464team(5,"Houston Rockets").
 1465team(6,"Brooklyn Nets").
 1466team(7,"New York Knicks").
 1467team(8,"Utah Jazz").
 1468team(9,"Memphis Grizzlies").
 1469team(10,"Denver Nuggets").
 1470team(11,"Sacramento Kings").
 1471team(12,"New Orleans Pelicans").
 1472team(13,"Los Angeles Clippers").
 1473team(14,"Minnesota Timberwolves").
 1474team(15,"Boston Celtics").
 1475team(16,"Chicago Bulls").
 1476team(17,"Toronto Raptors").
 1477team(18,"Miami Heat").
 1478team(19,"Milwaukee Bucks").
 1479team(20,"Detroit Pistons").
 1480team(21,"Philadelphia 76ers").
 1481team(22,"Atlanta Hawks").
 1482team(23,"Washington Wizards").
 1483team(24,"Charlotte Bobcats").
 1484team(25,"Indiana Pacers").
 1485team(26,"Cleveland Cavaliers").
 1486team(27,"Orlando Magic").
 1487team(28,"San Antonio Spurs").
 1488team(29,"Phoenix Suns").
 1489team(30,"Oklahoma City Thunder").
 1490%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 1491:- end_bg.