This article is about a WebSocket server on Erlang rather than about the game itself. I’ll tell you a small prehistory. When I began playing 2048 I couldn’t stop. It was to the detriment of both my job and family. So I decided that a bot should play instead of me. But the problem was that it’s a user game, there’s no global rating and it’s not comfortable to play without a browser. That’s why I decided to create the server part so that there would be rating and my bot could play without a browser.

It’s my first project in Erlang. Many programmers are afraid of it. They suppose that it’s difficult to use it. But it’s actually not. I’ll try to highlight some things that are not obvious for Erlang beginners.

I’ve hard coded a lot of things for simplicity. But anyway, I’ll be glad to read your comments on the subject.

Here’s a link to erl2048.
It’s a link to erl2048development project.

JavaScript

It may seem strange enough that I’ll begin with JS. I didn’t change the original files so that I would be able to update them from the primary repository when needed. I used the following:


I created main.js file. The logic is simple. The browser sends events to the server and then refreshes the field. It’s good that animframe_polyfill is created in such a way that it accepts the formed grid.

I added the connection initialization:

var websocket = new Websocket(SERVER);
  websocket
  .connect()
  .done(function(){
    var myGame = new MyGame(websocket);    
  });

I also wrote a wrapper for Websocket. It’s too simple to provide its source code here.
A new game start:

self.restart = function(evt){
  websocket.send(JSON.stringify({
    action:'start'
  }));
};

make a move
self.move = function(direction){
  // 0: up, 1: right, 2:down, 3: left
  if(!toMove){
    return false;
  }
  if(direction === 0){
    direction = 'up';
  }else if(direction === 1){
    direction = 'right';
  }else if(direction === 2){
    direction = 'down';
  }else if(direction === 3){
    direction = 'left';
  }
  websocket.send(JSON.stringify({
    action:'move',
    value: direction
  }));
};


It’s the biggest one.
processing the response from a server
self.wsHandler = function(evt){
  var game = JSON.parse(evt.data);

  if(game.grid){

    var grid = {cells: []};
    game.grid.forEach(function (column, y) {
      var row = [];
      column.forEach(function (cell, x) {
        if(cell){
          if(cell.mergedFrom){
            cell.mergedFrom.forEach(function(tile){
              tile['x'] = x;
              tile['y'] = y;
            });
          }
          row.push({
            value:            cell.value,
            x:                x,
            y:                y,
            previousPosition: cell.previousPosition,
            mergedFrom:       cell.mergedFrom
          });
        }
      });
      grid.cells.push(row);
    });

    var scores = game.scores,
      bestScore = 0;
    if(scores && scores.length>0){
      bestScore = scores[0].score;

      while (scoresEl.firstChild) {
        scoresEl.removeChild(scoresEl.firstChild);
      }

      scores.forEach(function(score){
        var div = document.createElement('Div');
        var name = document.createElement('Div');
        var scoreEl = document.createElement('Div');

        div.setAttribute("class", 'score');
        name.setAttribute("class", 'name');
        scoreEl.setAttribute("class", 'score');

        name.appendChild(document.createTextNode(score.name));
        scoreEl.appendChild(document.createTextNode(score.score));

        div.appendChild(name);
        div.appendChild(scoreEl);
        scoresEl.appendChild(div);
      });
    }

    actuator.actuate(grid, {
      score:     game.score,
      bestScore: bestScore,
      score: game.score,
      won: game.won,
      over: game.over,
      keepPlaying: game.keepPlaying
    });
  }

  //playername actuator
  if(game.user){
    if(playername.value !== playername){
      playername.value = game.user.name;
    }
  }
};


As you can see, the game completely depends on the server as all calculations are carried out there. It’s a contrast to my TicToe game, in which the logic is duplicated.

I really didn’t get why X and Y were used in tile in the original version, so the server goes without them. The list of the top 10 players also comes from the server. It’s the innovation of my version. A player can also change his nickname. There’re no signups and guards. It looks like the following:

2048 in Erlang

It’s not good to use the native keyboard_input_manager as now you can enter all symbols in the nickname entry field. You can also enter your nickname from the clipboard.
I haven’t implemented the entire functional. I closed the part that is responsible for “game over”. But it doesn’t affect the game process. There’s also no ability to continue the game after winning. But I haven’t won anyway.

Erlang

This part will be reviewed in more details. First of all, we should setup rebar. Rebar can generate base files but I created them manually.
We can use rebar.config to automatically download and build all the dependencies.

% The next option is required so we can use lager.  
{erl_opts, [{parse_transform, lager_transform}]}.  
{lib_dirs,["deps"]}.  
% Our dependencies.  
{deps, [    
    {'lager', ".*", {  
        git, "git://github.com/basho/lager.git", "master"}  
    },
    {'cowboy', ".*", {  
        git, "git://github.com/extend/cowboy.git", "master"}  
    },
    {'mochiweb', ".*", {
        git, "git://github.com/mochi/mochiweb.git", "master"}
    },
    {'sqlite3', ".*", {
        git, "git://github.com/alexeyr/erlang-sqlite3.git", "master"}
    }
]}.  

# rebar g-d
# rebar co

In order to download and build all the dependencies you may have to install
libsqlite3-dev for sqlite driver.

I use the following command to start the server:
# rebar compile skip_deps=true; erl -pa ebin deps/*/ebin -eval 'starter:start().' -noshell -detached

After that the game will be available at 8080 port. Learning how to start the server was the most difficult task. I created a special “starter” module that starts all dependencies and the application itself

-module(starter).
-export([start/0]).

start() ->
    application:start(ranch),
    application:start(crypto),
    application:start(cowlib),
    application:start(cowboy),
    application:start(inets),
    application:start(mochiweb),
    application:start(erl2048).

Now let’s take a look at the content of src/ directory. The first one is erl2048.app.src file. I don’t really know what it is for, but still added it to my project just in case. It would be great if you could shed some light.

erl2048.app.src
{application, erl2048, [
{description, "2048 game server."},
{vsn, "1"},
{modules, []},
{registered, [erl2048_sup]},
{applications, [
kernel,
stdlib,
cowboy
]},
{mod, {erl2048_app, []}},
{env, []}
]}.


erl2048_sup.erl
%% Feel free to use, reuse and abuse the code in this file.

%% @private
-module(erl2048_sup).
-behaviour(supervisor).

%% API.
-export([start_link/0]).

%% supervisor.
-export([init/1]).

%% API.

-spec start_link() -> {ok, pid()}.
start_link() ->
    supervisor:start_link({local, ?MODULE}, ?MODULE, []).

%% supervisor.

init([]) ->
    Procs = [],
    {ok, {{one_for_one, 10, 10}, Procs}}.


As far as I understand, the supervisor monitors the child processes and restarts them when necessary. I took it from the example and decided to leave it as it was. I'm not exactly sure what one_to_one is, but it works. It makes sense to look through Erlang documentation and find out the definition.
Now let’s review the most important file of the application — erl2048_app.erl.

erl2048_app.erl
%% Feel free to use, reuse and abuse the code in this file.

%% @private
-module(erl2048_app).
-behaviour(application).

%% API.
-export([start/2]).
-export([stop/1]).

%% API.
start(_Type, _Args) ->
    Dispatch = cowboy_router:compile([
        {'_', [
            {"/", cowboy_static, {file, "../client/index.html"}},
            {"/websocket", ws_handler, []},
            {"/static/[...]", cowboy_static, {dir, "../client/static"}}
        ]}
    ]),
    {ok, _} = cowboy:start_http(http, 100, [{port, 8080}],
        [{env, [{dispatch, Dispatch}]}]),
    {ok, _} = db:start_link(),
    erl2048_sup:start_link().

stop(_State) ->
    {ok, _} = db:stop(),
    ok.


That’s where I will explain something. First of all, we compile routes for cowboy. Then start cowboy and attach to the database. We are going to use sqlite database. I also considered Postgresql, mongoDB and Redis, but chose sqlite as it’s very simple. I know that it may create a high load on the application and it will fail. But anyway, I find it the simplest solution. Is there anything simpler? I don't think so. Here is the code of the module:

db.erl
-module(db).

-export([start_link/0,stop/0]).
-export([insert/2, select/0, createUser/1, changeName/2]).

start_link() ->
    {ok, PID} = sqlite3:open(db, [{file, "db.sqlite3"}]),

    Tables = sqlite3:list_tables(db),

    case lists:member("scores", Tables) of false ->
        sqlite3:create_table(db, scores, [{id, integer, [{primary_key, [asc, autoincrement]}]}, {userid, integer}, {score, integer}])
    end,

    case lists:member("users", Tables) of false ->
        sqlite3:create_table(db, users, [{id, integer, [{primary_key, [asc, autoincrement]}]}, {name, text}])
    end,

    {ok, PID}.

stop() ->
    sqlite3:close(db).

select() ->
    Ret = sqlite3:sql_exec(db, "select users.name, scores.score from scores LEFT JOIN users ON (users.id = scores.userid) ORDER BY score desc;"),
    [{columns,_},{rows,Rows}] = Ret,
    formatScores(Rows).

insert(Score, Player) ->
    [{columns,_},{rows,Rows}] = sqlite3:sql_exec(db, "SELECT score FROM scores WHERE userid = ?", [{1,Player}]),
    DBScore = if
        length(Rows) > 0  -> element(1,hd(Rows));
        true -> 0
    end,

    if Score > DBScore ->
        sqlite3:delete(db, scores, {userid, Player}),
        sqlite3:write(db, scores, [{userid, Player}, {score, Score}]),
        sqlite3:sql_exec(db, "DELETE FROM scores WHERE id IN (SELECT id FROM scores ORDER BY score desc LIMIT 1 OFFSET 10)");
        true -> undefined
    end.

formatScores([]) ->
    [];
formatScores([{Name, Score} | Rows]) ->
    [{struct, [{name, Name},{score, Score}]} | formatScores(Rows)].

createUser(UserName) ->
    sqlite3:write(db, users, [{name, UserName}]).

changeName(Id, NewName) ->
    sqlite3:update(db, users, {id, Id}, [{name, NewName}]).


Let’s move on to the module processing WebSocket connections.

ws_handler.erl
-module(ws_handler).
-behaviour(cowboy_websocket_handler).

-export([init/3]).
-export([websocket_init/3]).
-export([websocket_handle/3]).
-export([websocket_info/3]).
-export([websocket_terminate/3]).

init({tcp, http}, _Req, _Opts) ->
    {upgrade, protocol, cowboy_websocket}.

websocket_init(_TransportName, Req, _Opts) ->
    State = {struct, [ 
        { user, { struct, [{id, null},{name, <<"Player">>}] } } 
    ]},
    {ok, Req, State}.

websocket_handle({text, Msg}, Req, State) ->
    Message = mochijson2:decode(Msg, [{format, proplist}]),
    Action =  binary_to_list(proplists:get_value(<<"action">>, Message)),
    {NewState, Response} = case Action of
        "start" ->
            TmpState = game:init(State),
            {TmpState, TmpState};
        "move"  ->
            TmpState = game:move(list_to_atom(binary_to_list(proplists:get_value(<<"value">>, Message))), State),
            {TmpState, TmpState};
        "newName" ->
            NewName = proplists:get_value(<<"value">>, Message),
            JsonData = element(2, State),

            User = proplists:get_value(user, JsonData),
            {struct,UserJsonData} = User,

            Id = proplists:get_value(id, UserJsonData),

            db:changeName(Id, NewName),

            TmpState = {struct, [
                    { user, { struct, [ { name, NewName },{ id, Id } ] } }
                    | proplists:delete(user, JsonData)
                ]},
            {
                TmpState,
                {struct, [{ user, { struct, [ { name, NewName },{ id, Id } ] } }]}
            };
        _Else -> State
    end,
    {reply, {text, mochijson2:encode(Response)}, Req, NewState};

websocket_handle(_Data, Req, State) ->
    {ok, Req, State}.

websocket_info({send, Msg}, Req, State) ->
    {reply, {text, Msg}, Req, State};
websocket_info(_Info, Req, State) ->
    {ok, Req, State}.

websocket_terminate(_Reason, _Req, _State) ->
    ok.


At first I didn’t get the way it’s built. But it turned out to be very simple. There’s a state we define when establishing connection. We send it to each request handler, individually for every user. The main method here is websocket_handle. It accepts a message and state. Returns a response and state.
We use JSON format for communication. In Erlang it’s represented by a structure like the following:

{struct, [
  {key1, Value1},
  {key2, Value2},
  ....
]}

Now let’s review the game files. The simplest one is tile.erl.

tile.erl
-module(tile).

-export([init/1, init/0, prepare/2]).

prepare(null, _) ->
    null;
prepare(Tile, { X, Y }) ->
    {
        struct,
        [
            {value, proplists:get_value(value, element(2, Tile))},
            {mergedFrom, null},
            {previousPosition, {struct, [{ x, X - 1},{ y, Y - 1 }]}}
        ]
    }.
init(Value) ->
    {
        struct,
        [
            {value, Value},
            {mergedFrom, null},
            {previousPosition, null}
        ]
    }.
init() ->
    init(2).


It can only create a new tile and save the previous position. grid.erl is a bit more complex.

grid.erl
-module(grid).

-export([
    build/0,
    cellsAvailable/1,
    randomAvailableCell/1,
    insertTile/3,
    availableCells/1,
    cellContent/2,
    removeTile/2,
    moveTile/3,
    size/0,
    withinBounds/1,
    cellAvailable/2
]).

-define(SIZE, 4).

size() ->
    ?SIZE.

build() ->
    [[null || _ <- lists:seq(1, )] || _ <- lists:seq(1, )].

availableCells(Grid) ->
    lists:append(
        setY(
            availableCells(Grid, 1)
        )
    ).

availableCells([Grid | Tail ], N) when is_list(Grid) ->
    [{availableCells(Grid, 1), N} | availableCells(Tail, N +1)];
availableCells([Grid | Tail ], N) ->
    case Grid =:= null of
        true -> [ N | availableCells(Tail, N +1)];
        false ->  availableCells(Tail, N +1)
    end;
availableCells([], _) ->
    [].

setY([{Cell, Y}|Tail]) -> 
    [ setY(Cell, Y) | setY(Tail)];
setY([]) -> 
    [].
setY([Head | Tail], Y) ->
    [ {Head, Y} | setY(Tail, Y)];
setY([], _) ->
    [].

cellsAvailable(Grid) ->
    length(availableCells(Grid)) > 0.

randomAvailableCell(Grid) ->
    Cells = availableCells(Grid),
    lists:nth(random:uniform(length(Cells)) ,Cells).

insertTile({X, Y}, Tile, Grid) ->
    Row = lists:nth(Y,Grid),
    lists:sublist(Grid,Y - 1) ++ [ lists:sublist(Row,X - 1) ++ [Tile] ++ lists:nthtail(X,Row)] ++ lists:nthtail(Y,Grid).

cellContent({ X, Y }, Grid) ->
    case withinBounds({ X, Y }) of
        true -> lists:nth(X,lists:nth(Y,Grid));
        false -> null
    end.

removeTile({ X, Y }, Grid) ->
    insertTile({X, Y}, null, Grid).

moveTile(Cell, Cell, Grid) ->
    Grid;
moveTile(Cell, Next, Grid) ->
    insertTile(Next, grid:cellContent(Cell, Grid), removeTile(Cell, Grid)).

withinBounds({X, Y}) when
    (X > 0), (X =< ), 
    (Y > 0), (Y =< ) ->
    true;
withinBounds(_) ->
    false.

cellAvailable(Cell, Grid) ->
    case grid:withinBounds(Cell) of
        true -> cellContent(Cell, Grid) =:= null;
        false -> false
    end.


Pay attention to availableCells. In Erlang we should use recursion as much as possible. I was too clever by half here. At first I generated a list (containing lists with the one coordinate) and the second coordinate. Then I added the second to the first one. I decided not to do so anymore. I guess, other functions are obvious.
The main game file is game.erl.

game.erl
-module(game).

-export([init/1, move/2]).

init(State) ->

    StateUser = proplists:get_value(user, element(2, State)),
    StateUserJsonData = element(2, StateUser),

    User = case proplists:get_value(id, StateUserJsonData) of
        null ->
            Name = proplists:get_value(name, StateUserJsonData),
            {rowid, Id} = db:createUser(Name),
            { struct, [{name, Name},{id, Id}]};
        _Else ->
            StateUser
    end,

    {
        struct,
        [
            {grid ,addStartTiles(grid:build())},
            {user , User},
            {score,0},
            {scores, db:select()},
            {won, false},
            {over, false},
            {keepPlaying, false}
        ]
    }.

addStartTiles(Grid, 0) -> 
    Grid;
addStartTiles(Grid, N) -> 
    NewGrid = addRandomTile(Grid),
    addStartTiles(NewGrid, N - 1).
addStartTiles(Grid) ->
    addStartTiles(Grid, 2).

addRandomTile(Grid) ->
    random:seed(now()),
    case grid:cellsAvailable(Grid) of
        true -> 
            case random:uniform(10) < 9 of
                true -> Tile = tile:init();
                false -> Tile = tile:init(grid:size())
            end,
            grid:insertTile(grid:randomAvailableCell(Grid), Tile, Grid);
        false -> Grid
    end.

getVector(left) ->
    { -1, 0 };
getVector(up) ->
    { 0,  -1 };
getVector(right) ->
    { 1,  0 };
getVector(down) ->
    { 0,  1 }.

buildTraversals() ->
    Traver = lists:seq(1, grid:size()),
    { Traver, Traver }.
buildTraversals({ 1 , _ }) ->
    { T1, T2} = buildTraversals(),
    { lists:reverse(T1), T2 };
buildTraversals({ _ , 1 }) ->
    { T1, T2} = buildTraversals(),
    { T1, lists:reverse(T2) };
buildTraversals({ _ , _ }) ->
    buildTraversals().

prepareTiles( [{_Key, _Value} | _Tail ] ) ->
    JsonData = [{_Key, _Value} | _Tail ],
    [{ grid, prepareTiles(proplists:get_value(grid, JsonData)) } | proplists:delete(grid, JsonData) ];
prepareTiles( Grid ) ->
    prepareTiles( Grid, 1).
prepareTiles([], _) ->
    [];
prepareTiles([Row | Tail], Y) ->
    [ prepareTileY(Row, 1, Y) | prepareTiles(Tail, Y + 1)].
prepareTileY([], _, _) ->
    [];
prepareTileY([Cell | Tail], X, Y) ->
    [prepareTileX(Cell, X, Y) | prepareTileY(Tail, X + 1, Y) ].
prepareTileX(Tile, X, Y) ->
    tile:prepare(Tile, {X, Y}).

process_travesals_y([], _, _, JsonData) ->
    JsonData;
process_travesals_y(_, [], _, JsonData) ->
    JsonData;
process_travesals_y([ Y | Tail ], TraversalsX, Vector, JsonData) ->
    process_travesals_y(
        Tail,
        TraversalsX,
        Vector,
        process_travesals_y( Y, TraversalsX, Vector, JsonData)
    );
process_travesals_y(Y, [ X | Tail ], Vector, JsonData) ->
    process_travesals_y(Y, Tail, Vector, process_travesals_y( Y, X, Vector, JsonData ));
process_travesals_y( Y, X, Vector, JsonData ) ->
    moveTile({ X, Y }, Vector, JsonData).

findFarthestPosition({X, Y}, {VecX, VecY}, Grid) ->

    Next = { X + VecX, Y + VecY },

    case grid:cellAvailable(Next, Grid) of
        true -> 
            findFarthestPosition(Next, {VecX, VecY}, Grid);
        false -> 
            {
                {X, Y},
                Next % Used to check if a merge is required
            }
    end.

moveTile(Cell, Vector, JsonData) ->

    Grid = proplists:get_value(grid, JsonData),
    Tile = grid:cellContent(Cell, Grid),

    case Tile =:= null of
        true -> JsonData;
        false ->
            { Farthest, Next } = findFarthestPosition(Cell, Vector, Grid),

            {struct, CurrJsonData} = Tile,
            CurrValue = proplists:get_value(value, CurrJsonData),

            NextTile = if
                Next =:= null -> null;
                true ->
                    grid:cellContent(Next, Grid)
            end,

            {NextValue, NextMerged} = if
                NextTile =:= null -> {null, null};
                true ->
                    NextJsonData = element(2, NextTile),
                    {proplists:get_value(value, NextJsonData), proplists:get_value(mergedFrom, NextJsonData)}
            end,

            if  CurrValue =:= NextValue,
                NextMerged =:= null
                ->
                    MergedValue = CurrValue * 2,
                    Merged = {
                        struct,
                        [
                            {value, MergedValue},
                            {mergedFrom, [Tile,NextTile]},
                            {previousPosition, null}
                        ]
                    },
                    NewGrid = grid:insertTile(Next, Merged, grid:removeTile(Cell, Grid)),

                    % Update the score
                    Score = proplists:get_value(score, JsonData) + MergedValue,

                    % The mighty 2048 tile
                    Won = if
                        MergedValue =:= 2048 -> true;
                        true -> false
                    end,

                    Removed = proplists:delete(score, proplists:delete(won, proplists:delete(grid, JsonData))),

                    [
                        {grid,NewGrid},
                        {won,Won},
                        {score,Score} |
                        Removed
                    ];
                true ->
                    [
                        {
                            grid,
                            grid:moveTile(Cell, Farthest, proplists:get_value(grid, JsonData))
                        }
                        | proplists:delete(grid, JsonData)
                    ]
            end
    end.

move(left, State) ->
    move(getVector(left), State);
move(right, State) -> 
    move(getVector(right), State);
move(up, State) -> 
    move(getVector(up), State);
move(down, State) -> 
    move(getVector(down), State);
move(Vector, State) ->
    {struct, JsonData} = State,

    case 
        proplists:get_value(over, JsonData) or (
            proplists:get_value(won, JsonData) and (not proplists:get_value(keepPlaying, JsonData))
        )
    of
        true -> State;
        _Else ->
            PreparedJsonData = updateBestScore(prepareTiles(JsonData)),

            { TraversalsX, TraversalsY } = buildTraversals(Vector),

            NewJsonData = process_travesals_y(
                TraversalsY,
                TraversalsX,
                Vector,
                PreparedJsonData
            ),

            NewGrid = proplists:get_value(grid, NewJsonData),
            Grid = proplists:get_value(grid, PreparedJsonData),

            if
                NewGrid =/= Grid -> %If changed - add new tile
                    
                    {struct, UserJsonData} = proplists:get_value(user, NewJsonData),

                    NewScore = proplists:get_value(score, NewJsonData),
                    Score = proplists:get_value(score, PreparedJsonData),

                    case NewScore > Score of true ->
                        db:insert(
                            proplists:get_value(score, NewJsonData),
                            proplists:get_value(id, UserJsonData)
                        );
                        _Else -> undefined
                    end,

                    Over = case movesAvailable(NewGrid) of
                        true -> false;
                        fale -> true % Game over!
                    end,
                    Removed = proplists:delete(grid, proplists:delete(over, NewJsonData)),
                    {struct,[{ grid, addRandomTile(NewGrid) }, { over, Over } | Removed ]};
                true -> %return state otherwise
                    {struct,PreparedJsonData}
            end
    end.

movesAvailable(_) ->
    true.

updateBestScore(JsonData) ->
    [{ scores, db:select() } | proplists:delete(scores, JsonData) ].


init function creates a new user if we haven’t created it yet. Or it can take a user from the previous game.

init(State) ->

    StateUser = proplists:get_value(user, element(2, State)),
    StateUserJsonData = element(2, StateUser),

    User = case proplists:get_value(id, StateUserJsonData) of
        null ->
            Name = proplists:get_value(name, StateUserJsonData),
            {rowid, Id} = db:createUser(Name),
            { struct, [{name, Name},{id, Id}]};
        _Else ->
            StateUser
    end,

    {
        struct,
        [
            {grid ,addStartTiles(grid:build())},
            {user , User},
            {score,0},
            {scores, db:select()},
            {won, false},
            {over, false},
            {keepPlaying, false}
        ]
    }.

move is the main function. It’s in charge of recalculating the game field. I had some difficulties here; mostly due to the lack of experience in functional programming. Let me know if there is a better way to write this code.

move(left, State) ->
    move(getVector(left), State);
move(right, State) -> 
    move(getVector(right), State);
move(up, State) -> 
    move(getVector(up), State);
move(down, State) -> 
    move(getVector(down), State);
move(Vector, State) ->
    {struct, JsonData} = State,

    case 
        proplists:get_value(over, JsonData) or (
            proplists:get_value(won, JsonData) and (not proplists:get_value(keepPlaying, JsonData))
        )
    of
        true -> State;
        _Else ->
            PreparedJsonData = updateBestScore(prepareTiles(JsonData)),

            { TraversalsX, TraversalsY } = buildTraversals(Vector),

            NewJsonData = process_travesals_y(
                TraversalsY,
                TraversalsX,
                Vector,
                PreparedJsonData
            ),

            NewGrid = proplists:get_value(grid, NewJsonData),
            Grid = proplists:get_value(grid, PreparedJsonData),

            if
                NewGrid =/= Grid -> %If changed - add new tile
                    
                    {struct, UserJsonData} = proplists:get_value(user, NewJsonData),

                    NewScore = proplists:get_value(score, NewJsonData),
                    Score = proplists:get_value(score, PreparedJsonData),

                    case NewScore > Score of true ->
                        db:insert(
                            proplists:get_value(score, NewJsonData),
                            proplists:get_value(id, UserJsonData)
                        );
                        _Else -> undefined
                    end,

                    Over = case movesAvailable(NewGrid) of
                        true -> false;
                        fale -> true % Game over!
                    end,
                    Removed = proplists:delete(grid, proplists:delete(over, NewJsonData)),
                    {struct,[{ grid, addRandomTile(NewGrid) }, { over, Over } | Removed ]};
                true -> %return state otherwise
                    {struct,PreparedJsonData}
            end
    end.

In order to find out whether the move has been made we should compare the old state with the new one. We don’t use an external variable as in JS variant. I’m not sure, whether it’s going to reduce the performance. So that we wouldn’t have to make unnecessary requests to the database, it’s better to control whether the score has changed.
It’s a rare occasion in functional approach, when it’s necessary to pass a lot of parameters to the function. I am most confused by the fact that I pass TraversalsY, TraversalsX, Vector to process_travesals_y, though TraversalsY and TraversalsX already depend on Vector. But for now I decided to leave it this way.

In order not to repeat availableCells experience I wrote process_travesals_y function in details. But now it’s separate for X and Y axes. As a result, it calls moveTile for every nonzero element of the game field, which almost completely corresponds to JS original.

moveTile(Cell, Vector, JsonData) ->

    Grid = proplists:get_value(grid, JsonData),
    Tile = grid:cellContent(Cell, Grid),

    case Tile =:= null of
        true -> JsonData;
        false ->
            { Farthest, Next } = findFarthestPosition(Cell, Vector, Grid),

            {struct, CurrJsonData} = Tile,
            CurrValue = proplists:get_value(value, CurrJsonData),

            NextTile = if
                Next =:= null -> null;
                true ->
                    grid:cellContent(Next, Grid)
            end,

            {NextValue, NextMerged} = if
                NextTile =:= null -> {null, null};
                true ->
                    NextJsonData = element(2, NextTile),
                    {proplists:get_value(value, NextJsonData), proplists:get_value(mergedFrom, NextJsonData)}
            end,

            if  CurrValue =:= NextValue,
                NextMerged =:= null
                ->
                    MergedValue = CurrValue * 2,
                    Merged = {
                        struct,
                        [
                            {value, MergedValue},
                            {mergedFrom, [Tile,NextTile]},
                            {previousPosition, null}
                        ]
                    },
                    NewGrid = grid:insertTile(Next, Merged, grid:removeTile(Cell, Grid)),

                    % Update the score
                    Score = proplists:get_value(score, JsonData) + MergedValue,

                    % The mighty 2048 tile
                    Won = if
                        MergedValue =:= 2048 -> true;
                        true -> false
                    end,

                    Removed = proplists:delete(score, proplists:delete(won, proplists:delete(grid, JsonData))),

                    [
                        {grid,NewGrid},
                        {won,Won},
                        {score,Score} |
                        Removed
                    ];
                true ->
                    [
                        {
                            grid,
                            grid:moveTile(Cell, Farthest, proplists:get_value(grid, JsonData))
                        }
                        | proplists:delete(grid, JsonData)
                    ]
            end
    end.

I guess, that’s about it for WebSocket requests processing by means of Erlang. As this is my first Erlang project, I'd be glad if you could share some feedback regarding the code itself. Please advise what needs to be improved. Happy to answer all your questions.

Write your own articles at Kukuruku Hub

0 comments

Read Next