Message Boards Message Boards

[WSS17] Complete The Wolfram Expression: interactive web games

The aim of the project is to design an interactive browser game where you can improve your skill with Wolfram language, starting from a topic of your interest the system will show you a Wolfram Expression with a missing part to complete, in a growing of difficulty and fun.

Abstract

The goal of the project is to develop a web application that let people enjoy playing and learning Wolfram Mathematica Languages, forcing the user to explore the documentation. A tool that can be used in the future to test the skills of proposed candidates, and an instrument for teachers to appeal students to the languages. An application where people of different ages can compete to the top position and have fun sharing their results with friends. Developing a web application's game based on Wolfram's stack technology, focusing on exploring safe examples for the game in a dynamic self configuring context. Application is ready for a public deployment, but with such a vast number of example more tests are required to verify the stability of this alpha release.

Design

The game is fully developed in Wolfram Mathematica Language, is composed with 3 different component: The URLDispatcher redirect each http request on the correspondent template, it's the entry point of the game and the most important part of the application.

$CompleteExpressionApp := With[{
	playOrLoginTemplate     = templateLoader["playOrLogin.html"],
	categoryTemplate     	= templateLoader["category.html"], 
	profileTemplate     	= templateLoader["profile.html"], 
	leaderBoardTemplate    	= templateLoader["leaderboard.html"], 
	difficultyTemplate     	= templateLoader["difficulty.html"], 
	playTemplate			= templateLoader["play.html"], 
	detail   				= templateLoader["selectLoginPlay.html"],
	winTemplate				= templateLoader["win.html"],
	loseTemplate			= templateLoader["lose.html"],
	notfound 				= templateLoader["404.html"],
	keys = Values[$DataBase["CategoriesNames"]],
	category = Keys[$DataBase["CategoriesNames"]]
	},
	URLDispatcher[{
		"/" ~~ EndOfString :> templateResponse[
					playOrLoginTemplate, {
				}],
		"/category/" ~~ EndOfString :>
		 				chooseCategory[categoryTemplate,$DataBase["CategoriesNames"]],
		"/profile/" ~~ EndOfString :>
		 				showProfile[profileTemplate],
		"/leaderboard/" ~~ EndOfString :>
		 				showLeaderBoard[leaderBoardTemplate],
		"/category/" ~~ cat : category .. ~~ "/" ~~ EndOfString :>
		 				chooseDifficulty[difficultyTemplate,cat],
		"/category/" ~~ cat : category .. ~~ "/" ~~ difficulty : difficulties ~~ "/" ~~EndOfString :>
		 				generateSeed[cat,keys,difficulty],
		"/category/" ~~ cat : category .. ~~ "/" ~~ exerciseInfo : (WordCharacter | ":" | "-") .. ~~ "/" ~~EndOfString :>
						(**Replace[HTTPRequestData["FormRules"], {} -> None],**)
						victoryDispatcher[playTemplate, notfound, cat,exerciseInfo],
		"/category/" ~~ cat : category .. ~~ "/success/"  ~~ exerciseInfo : (WordCharacter | ":" | "-") ..
 ~~ "/" ~~ solution : (WordCharacter | ":") .. ~~ "/" ~~EndOfString :>
		 				winGame[winTemplate,cat,exerciseInfo,StringSplit[solution,":"]],
		"/category/" ~~ cat : category .. ~~ "/lose/"  ~~ exerciseInfo : (WordCharacter | ":" | "-") .. 
~~ "/" ~~ solution : (WordCharacter | ":") .. ~~ "/" ~~EndOfString :>
		 				loseGame[loseTemplate,cat,exerciseInfo,StringSplit[solution,":"]],
		___ :> templateResponse[
			notfound,
			<||>,
			<|"StatusCode" -> 404|>
			]
		}
	]
];

Current graph of the web page that URLDispatcher manage to present.

Current graph of the web page that URLDispatcher manage to present.

The second most important aspect of the game is the function that's tweaks a working Wolfram expression and replace a Symbol with a Placeholder.

expression before the tweaks

expression after the tweaks

During the process is important to pay attention that the expressions are not evaluated, as some functions like "Now" can get interpreted on the fly and produce unexpected results if not managed correctly.

Finally another section of this project is related to the classification of the exercise and the realization of a subset of instruction that can be used during the game. Some Expression can be really dangerous for Wolfram Kernel. Expressions like Quit or Import, Export can compromise the user's Wolfram account. So while the system is designed to accept a big range of expressions, it will present only the examples from the documentation that contain expressions in the safe subset

List of examples divided by categories

List of examples divided by categories

Implementation

Smart use of seed in Random

The development of the web interface leads to develop a restful website, in order to do so, some effort was spent in making the API consistent. When a user connect to a specific game the random symbol removed must be always the same, in order to accomplish this we encode the seed of the tweak function in the URL.

When an user request a new exercise http://$AppRoot/category/BasicSymbols/easy/ the system generate a new list made by: difficulty seed exerciseId hash than redirect the user to a different URL, for example:

http://$AppRoot/category/BasicSymbols/easy:294:10uwnetq30jhf:1j5e7hz091u8wyhllpctx5q3n04rxsm87l087qfowcxu00qjgo/

This design was meant to keep integrity in the request made by the users, but the hash was added to the first tree values in the end in order to prevent that a user can manipulate the random seed and move the missing part and be able to discover the correct answer.

(*uuid stored in the server*)
$uuid = 
  "secret string stored in the server";
(*hashing function*)

customHash[expr_, rest___] := 
 IntegerString[Hash[{expr, $uuid}, rest], 36]
(* function that given an arbitrary list return a string with the \
list and the hash of the list divided by colon *)

signList[s_List] := 
 With[{l = Map[ToString, s]}, 
  StringJoin[Riffle[Append[l, customHash[l, "SHA256"]], ":"]]]
(* function that given a string and a kind of hash try to unpack the \
list if and only if the hash is correct, elsewhere fail *)

unsign[{l__, h_}] := 
 If[MatchQ[customHash[{l}, "SHA256"], h], {l}, $Failed]
unsign[s_String] := unsign[StringSplit[s, ":"]]
unsign[__] := $Failed
s = signList[{"easy", 294, "10uwnetq30jhf"}]
unsign [s]

Output of sign: easy:294:10uwnetq30jhf:4jww2nqwqvud5jtu7r2mkepojfzbq0dwd8uebxo7zfzjqrp9zk

Output of unsign: {"easy", "294", "10uwnetq30jhf"}

(* if we try to manipulate the seed in order to tweak different expression *)
unsign["easy:42:10uwnetq30jhf:4jww2nqwqvud5jtu7r2mkepojfzbq0dwd8uebxo7zfzjqrp9zk"]

Output: $Failed

Multiple answer for a specific question

Wolfram Mathematica language has a huge amount of functions in its core, and some of them can be used interchangeably to solve the same problem.

With[{Set[x, 3]}, x + 5]
With[{SetDelayed[y, 3]}, y + 5]
8
8

In order to prevent false negative by checking only the user input it has been implemented a smart function that check victory from the output of the problem.

victoryChecker[difficulty_,
  			seed_,
  			exId_,
  			expression_,
  			response_,
  			urlWin_,
  			urlLose_] := 
 If[MatchQ[Values[getSolution[expression]], Values[response]],
  (
   	addPoint[difficulty, seed, exId, 
    calculateScore[difficulty, seed, exId]];
   	HTTPRedirect[urlWin]
   ),
  If[SubsetQ[$wholewhitelist, Values@response], 
   With[{number = RandomInteger[{1, 1000000}]},
    (
     SeedRandom[number];
     res1 = Identity @@@ $DataBase["Examples"][exId];
     SeedRandom[number];
     res2 = 
      Check[Identity @@@ 
        relaseAllPlaceholder[expression, 
         Map[ToExpression[#, StandardForm] &, 
           Values@response]], $superPrideFailSoRainbow];
     If[res1 === res2,
      (
       addPoint[difficulty, seed, exId, 
        calculateScore[difficulty, seed, exId]];
       HTTPRedirect[urlWin]
       ), HTTPRedirect[urlLose]]
     )
    ],
   HTTPRedirect[urlLose]]
  ]

This function redirect the user to a victory page if the Head inserted from the user match with the one removed by the system, otherwise the system try to compare the output of the computation, if and only if, the Symbol inserted by the user is in the safe Symbol subset. ($wholewhitelist)

Atomic expression and removing head

During the development of the software some function present a wrong behavior for example, Images from documentation like:

Image[{{0.1, 0.2, 0.3}, {0.4, 0.5, 0.6}, {0.7, 0.7, 0.9}}]

black and white matrix

Basically an Image is just a List of Symbols and this could leads to trouble if we just apply a tweak function on an object like this. This happens because tweak traverse the whole tree of the expression and can break the Image making it hard to understood from the user what is meant to be in the beginning. Expression like this should be considered as atomic, because removing something from this code make it barely readable. So it has been decided to keep unaltered some expressions like Image or Random*, only to maintain the game experience enjoyable and presents code as people are used to see. It's an important aspect on learning coding skill, the possibility of doing exercises in an "ecological" environment. With "ecological", a term used in psychology, we mean an environment that mimics a real world setting as closely as possible, opposite to an artificial environment created in the laboratory.

removeExpressionPart[expr_, patt___] := 
 With[{pattern = 
    Alternatives[_Image, _Graph, _Graphics, _Graphics3D, _Random, 
_RandomWord, _RandomInteger, _RandomReal, _RandomChoice, 
_RandomSample, List, Rule, RuleDelayed, patt]
   }, expr /. pattern -> garbage]

removeExpression on multiple Image

Ouput: Hold[ImageCompose[garbage, garbage]]

As you can see the system removes the two images and replace them with a placeholder named garbage.

Classification of expressions between different categories

During this project a lot of difficulties have been encountered around the classification of the different functions in the Wolfram language. First approach starts from a book of Stephen Wolfram: An elementary introduction to the Wolfram Language. The notebook was imported and the functions that occurs in each chapters have been divided by the category suggested by the book. This work lead to a first draft of safe and easy Symbols that represent different categories. However, given that the book is targeted to beginners of the Wolfram Language, the amount of symbols we were able to derive was relatively small. So, each category was expanded by:

  1. Downloading for each Symbol examples of it from the documentation.
  2. Extracting all the new Symbols of each expressions retrieved.

This created the dataset contained in categories.m, which we consider a very good starting point for the project, as each Symbol is safe, and does not have dangerous side effects. However this setup is not useful for splitting the exercise in different categories. After some work and some refactoring a function from the documentation solve the problem.

newCatByFun = First /@
  	DeleteMissing[
   	AssociationMap[
    		WolframLanguageData[#, "FunctionalityAreas"] &,
    		$wholewhitelist]
   	]

This function retrieve the category of each Symbols presents in the $wholewhitelist and create an Association with it. After this step some Functionality Areas are low populated and were get manually joined in macro areas. This leads to a macro category named Basic Symbols and few other categories with at least 40 Examples.

List of examples divided by categories

Screenshot

home

home

categories

categories

example of game section

example of game section

profile page

profile

Conclusion

During this project I developed a Web Service to support a game created for the understanding and learning of the Wolfram Language. The whole exercise has been incredibly useful for me to better understand the power of the language itself, and its new functionality for cloud deployment The project is now working well locally but an error was discovered in the 11.1 version of the wolfram kernel that do not let deploy the $CompleteExpressionApp on the cloud. The error occur when you try to traverse a link in the deployed object the system keep redirecting you to core page or to 404 page. Future release of Mathematica should fix this issue.

All the software developed are available online in the GitHub page.

Reply to this discussion
Community posts can be styled and formatted using the Markdown syntax.
Reply Preview
Attachments
Remove
or Discard

Group Abstract Group Abstract