Exercising an HTTP server, in order to test it, typically involves sending a request, extracting some information in the response, validating the response and, if the response is valid, use the extracted information to form the next request to the server (or to some other server if indicated by the information).
“Extracting some information” is in the context of this series simply “pattern matching” (template:match if we want to refer to the template library[1] we built in part II) and “forming the next request” is to fill in the values of a template (template:replace) before sending it to some server again. This means that, if we want to do some testing of some HTTP endpoint that we have developed we could use our template library, add some HTTP client code and we are good to go. That is what we will do in this blog post and the end result, called Ionbeam (for lack of a better name, where “beam”, at least, could be seen as Erlang related), can be found on github[2] as before.
Forming the Ionbeam
A test suite consists of a sequence of tasks where each task is defined as having a request template which is filled in with values from some input context. Performing the task and validating and extracting information from the response will produce an output context that can be used as input context for other tasks further down the sequence.
A task, in Ionbeam, is represented by an Erlang map with fields of two categories – one that describes the request (such as method, host, path and headers fields) and one that details how the response is to be validated and what information should be passed to the output context. Another way of looking at the response fields is that they put constraints on the response.
If we then imagine, to continue the example, that the ListItemsTask requires authentication and that this authentication is done by inserting a header X-Token with the TOKEN value and that it will return json document in response to a GET request, its definition becomes something like:
Suppose now that we WOULD like to put constraints on the body, but we know that the body could be huge and might not be fit to be parsed by the generic matcher library (or that the validation logic might not easily be expressed by a matching function). In this case we would, instead of specifying a match template, specify a validation function that can, given some domain knowledge, in a more efficient way parse and validate the body.
Running it
When you have written all your tasks, and put them together in a sequence, you can then run them using the ionbeam:run_script function. This function will manage your input and output contexts for you so that you use them throughout the sequence and it will catch and report errors occurring.
ionbeam:run_script([
%% do login
{LoginTask, #{"USER_NAME" => "alice",
"PASSWORD" => "secret"}, 'LoginCtx'},
%% do list items
{ListItemsTask, 'LoginCtx', 'ListItemsCtx'},
...
])
Summary
Pattern matching is a core concept in programming as it provides powerful tools that can be used within many different contexts. Throughout this series of posts about pattern matching I have tried to show how diverse use cases one can have for it, such as implementing some simple language processing (like Eliza in part III) or by implementing an HTTP server testing framework like in this post. Both problems are very different in context, but essentially solved in the same way – by matching patterns against literal strings. And it can be iterated once more, that pattern matching is not only a powerful way of expressing yourself, it also enhances the creative energy while programming, thus making programming more fun and rewarding.
In this post we will continue enhancing the template matcher[1] we developed in part II of this series. We add some functionality so that we can match and process slightly more complex patterns. The usefulness of matching e.g. palindromes could be debated though, so consider this to be an exercise we do because of the fact that pattern matching is…is fun! And palindromes are fun too, right?
To make it possible to present match examples in a brief manner, let us first introduce a notation for the function call template:match. Instead of every time writing out template:match(Template, String) below we will from now on simply write Template = String but it still means that it is a function call in our Erlang library. Ok? The resulting dictionary from the match will be written on the form {Key1 => Val1, Key2 => Val2, …}.
Suppose now that you would like to, for instance, match recurring patterns – like a pattern A, followed by some characters, say “xyz”, and then followed by another A. How would you write this in our current pattern matcher? It would be something like:
"$(A)xyz$(A)" = "abaxyzaba"
{A => "aba"}
Suppose now if we would like to do the above, but match only iff $(A) occurs twice after the string xyz? Can we do this? Well, of course we can, we just type $(A)$(A) twice there after “xyz”, but it would be more convenient with some expression that meant “occurs twice” or “occurs 4711 times” and such an expression we do not support yet in the implementation of our template matcher.
Or say that we would like to be able to match a pattern that starts with a pattern A and is then followed by another A, but a reversed A (this is a complicated way of describing “even length palindromes” such as “helloolleh”)? How would we do that when we cannot express “should occur again, but in reverse”? It would be fun if we could express things like ‘occurs in reverse’ as well or simply apply any function that transform one string value to another. Sounds like fun? Well, let us do it then! Let us introduce a generic transformation function to our template matcher that can transform the variable while we are doing the matching and see if the end result is interesting or not.
The syntax we introduce for this is $(A|<body>) where <body> will be converted to an erlang function body that will be applied to the variable A. By using Erlang’s “eval” capabilities we can actually include any Erlang code in the body of the transformation function. This means that, if you write $(A|lists:reverse(A)) the transformation function created would be:
fun(A) ->
lists:reverse(A)
end
, which would be applied to the variable during the matching, returning the transformed value (in this case the string in reverse).
Using this syntax we can then do the matches we discussed above.
Suppose we would like to match expressions that occur again, like above, but with some modification, say, with the first character “b” removed from A. This could be written using the ‘—‘ operator in Erlang, thus an example would be:
Suppose now that you would match expressions like the one above, but also match out what comes after such a combination of A followed by A — “b”. With some disappointment ahead of you, you might boldly try and write this as:
The reason why the solution above resulted in such disappointment is because the current template matcher will always halt with the first match it finds and it will always find shorter solutions before longer. Here the shortest solution for A is of course to bind A to the empty string “” (or [] as it is also written in Erlang) because removing a “b” from the empty string is also the empty string.
Is there some way around this? Is there some way to enforce longer matches? Well, yes, there is! We can use the transformation function itself, not only to modify the string, but also to enforce constraints on the match. If the transformation function make sure that the match will fail if certain constraints are not fulfilled we will force the matcher to continue searching. For instance, we could check if A, in this case, is the empty string and return some unlikely string instead which would make the match fail for empty strings. The result of this is that we would therefore get the more interesting binding instead. Let’s try that:
Another interesting example is the one that finds the first occurrence of an integer where the integer is followed by itself plus one:
Implementation
Implementation of the transformation function was done in commit 6df8227ac1245eb4296822fb0ee9b427e3db035a [2] and mostly involves a new parser for the new variable syntax, thus a new read_var_name function, but also a new eval function that, given a variable name, a body and a value, creates an Erlang function (a “fun”) from the body and applies the function on the value, like so:
eval(_, identity, Val) ->
%% this clause is taken when we do not have a transform defined, like only a variable $(A)
Val;
eval(VarName, Body, Val) ->
FunStr = "fun (" ++ VarName ++ ") -> " ++ Body ++ " end.",
{ok, Tokens, _} = erl_scan:string(FunStr),
{ok, [Form]} = erl_parse:parse_exprs(Tokens),
{value, Fun, _} = erl_eval:expr(Form, erl_eval:new_bindings()),
Fun(Val).
Then, whenever the template matcher would like to bind a variable A with a transform B it will first apply B on A before continuing with the match.
I am not sure that this transformation stuff actually has any big value – or any good use case – other than that it is fun to play around with it – like a puzzle. It was more or less just added because, well, because I could. In the next episode of this series on pattern matching I will however put the template matcher to do something more useful (in contrast to the exercises above) as I will show that the same template matcher can be used to implement an HTTP API testing framework – something that makes HTTP requests against some HTTP endpoints and validates that it gets the correct answers back. Stay tuned!
I was fascinated by artificial intelligence already when my interests in computers started. One of the earlier games I enjoyed on my C64 were the different text based adventures, like Zork [1], that used different text parsers to extract meaning from your text input. You typed commands such as “attack grue with sword”, the game parsed the text and produced some output.
Later, when I did an assignment in school (a Turbo Pascal Othello/Reversi game that my class mates enjoyed playing – I guess the school’s computers did not have many games back then) I became fascinated with the fact that my classmates so easily put a higher meaning to my computer program, referring to it as a “thinking machine”, getting angry at it for “tricking them on purpose” etc, when I knew how stupidly simple the algorithm behind the game was. I started reading about the Turing test [2] and then came across Joseph Weizenbaum’s work on Eliza [3] and his thoughts about the so called Eliza effect[4] and this tied together my fascination for text based adventures with my classmates’ reaction to my Othello game and with the Turing test and the Eliza effect.
ELIZA is an early natural language processing computer program created from 1964 to 1966 […] at the MIT Artificial Intelligence Laboratory by Joseph Weizenbaum. […] Created to demonstrate the superficiality of communication between man and machine, Eliza simulated conversation by using a ‘pattern matching’ and substitution methodology that gave users an illusion of understanding on the part of the program […]. Directives on how to interact were provided by ‘scripts’, […], which allowed ELIZA to process user inputs and engage in discourse following the rules and directions of the script.
Eliza has, since then, always returned to me in different ways. I wrote a version of it myself in Java back in the 90s when you could make web pages interactive through a, now dead, technology called “Java Applets”, I got to implement one version in Scheme in computer science class at KTH and when I started using Emacs I many times kicked off M-x doctor. I return to it now once again within the context of pattern matching and the template matcher that we developed in the previous part of this series of blog posts. Just as I don’t understand why pattern matching is so fascinating to me I do not understand why this simple Eliza program and its effect on people is so fascinating to me.
The template matcher we wrote in the previous post has a match function that takes a template string and a string and, if it can find a match, it produces a dictionary where the variables in the template string has been assigned a value. The template matcher library also has the inverse function that, given a template and a dictionary it can replace all the variables in the template with the bindings in the dictionary. It turns out that this is all you need to implement Eliza and to have yet another meaningful discussion with a computer.
To create our own Eliza version by using the template matcher, we start by defining a set of patterns (or templates) that we should match user input against. Only your imagination is the limitation here but you should put more complex patterns first and then have simpler, catch-all patterns towards the bottom because we will try to match user input from top to bottom. It also turns out that it is good if the catch-all phrases at the bottom tries to lead the conversation someplace else, like starting with a question (ok, the “my sister was once bitten by a moose” below is more a sign of my fascination with Monty Python rather than trying to make a meaningful conversation).
patterns() ->
[
{"$(x)Where are you from$(y)",
"I'm from $(c)",
"I live in $(c)",
"My country is $(c)"},
{"$(x)my name is $(y)",
"$(y)!. What a beautiful name!",
"When I was young I wished my name was $(y)",
"My name is $(n) but you probably knew that already",
"$(y)? ... $(y)? Isn't there a movie star called $(y)?"},
{"$(x)I am from $(y)",
"From $(y)!? I am from $(c) myself",
"So do you like it in $(y) then?",
"I come from $(c) if you wondered",
"$(y). Is that far from $(c)?"},
{"$(x)I remember $(y)",
"Do you often think of $(y)?",
"Does thinking of $(y) bring anything else to mind?",
"What else do you remember?",
"Why do you recall $(y) right now?",
"What in the present situation reminds you of $(y) ?",
"What is the connection between me and $(y) ?"},
{"$(x)do you remember $(y)",
"Did you think I would forget $(y)?",
"What about $(y)?",
"Why do you think I should recall $(y) now?",
"You mentioned $(y)?"},
...
{"$(x)",
"Do you like computers then since you are using the Internet?",
"So, where do you live?",
"Can you play the saxophone?",
"Why do you speak so much?",
"Why are you here",
"Where are you from?",
"What age are you?",
"What's your name then?",
"Please tell me more about your family",
"What are you interested in?",
"Do you have any problems?",
"I don't have a family and that's bothering me a bit",
"I like coffee",
"Very interesting. Please tell me more",
"I hate you. Do you know that?",
"I like you sometimes. Did you know that?",
"I'm a lumberjack and I'm ok...",
"I don't understand what you mean really. Please explain",
"Can you explain that a bit more",
"To be or not to be that is the question",
"My sister was bitten by a moose once",
"Moose bites can be very dangerous, you know",
"I apologize for everything I said so far",
"I am sorry I disturbed you",
"Do you know how to stop chatting?",
"I've been here all my life and I'm getting pretty tired of it",
"How long is the TTL-field in an IP-header?",
"Do you think it's possible to program a computer to speak like a human beeing",
"I dreamt about a giant hedgehog last night",
"I remember that you mentioned something like that earlier",
"Did you know that I can't think?"}
].
The first line in the pattern tuples is the pattern we match against and the rest of the patterns are the answers we could return if that pattern matches. The variables, as you might see, will carry over from the match to the later replace on the selected answer (where the answer is selected with just a random index).
What one also normally do in any Eliza implementation is to switch pronouns in the user input according to fixed rules. So if the user would write “I remember you saying so” it might match the pattern “${X}I remember ${Y}” and if we would like to send back an answer pattern such as “Can you really remember ${Y} ?” we would have to switch “you” to “me” before we send back the pattern. So the match would produce a dictionary
#{"X" => "", "Y" => "you saying so"}
, we apply the switch rules and produce the dictionary
#{"X" => "", "Y" => "me saying so"}
which would create the answer “Can you really remember me saying so?”.
So the whole Eliza process becomes something like:
, where find_first_match tries to find a matching template in the pattern list from top to bottom and, if it’s found, returns the Answer template, and the resulting Dictionary we should use to form an answer. The function switch_pronouns will modify the dictionary by replacing “you” with “me” etc and then we form the answer by calling template:replace. That’s all. Below follows a short example of what a conversation with this program would be like. The full code is at github.
Using the template matcher to implement Eliza is actually a bit of an overkill as a simple regexp match would be enough. The template matcher offers more than regexps, such as enforcing equal binding of repeating patterns in the template, but this is not needed in this Eliza implementation. In the next part of this series on pattern matching however, we will extend the template matching library to support more advanced matching functionality – things that you normally cannot do with simple regexp matching.
In “The joy of pattern matching – part I” we used a simple template language as an example to talk about pattern matching. Let us review that language again. It includes sequences of upper- and lowercase characters where lowercase characters are literals and uppercase characters represent any lowercase character sequence.
Consider now that we try to match the template sequence “aAa” with the sequence “abba”.
Would the Erlang matcher be able to do this match if the sequences were represented as Erlang lists, binary strings, or whatever Erlang term we might represent the sequences with? No, not really. The reason is, that for Erlang matching to work [1], the left-hand side must have the same structure as the right-hand side – a fair constraint as this makes the matching process both more efficient and more well-defined (such as having at most one possible match, not many, to choose from). In our example above, one could say, that the two sides do not have the same structure because the A in “aAa” can, in our template language, represent any number of lowercase characters, thus it has a different structure than the right-hand side flat list, which has exactly four elements. So the Erlang matcher would not handle this. It does not magically realise that A must be the string “bb” in order for the two sequences to match.
If one were to unify the structures of the two sides in order to help the Erlang matcher, one could construct an example such as
[a, A, a] = [a, [b, b], a]
instead. Both sides now have three elements and the Erlang matcher is therefore able to match the A against the intended [b, b] (A is matched to be the complete list element [b, b]), but by doing this structure change we also turned the problem into a simpler one. Therefore, the answer to the question if the Erlang matcher would be able to match “aAa = abba” and figure out that A should be “bb”, remains “no”. The Erlang matcher is just not built that way.
As mentioned in part I there is some syntactic sugar in Erlang to match the tail portion of a list. A match expression such as “aA = aba” would then actually be possible in Erlang and can be written either as
"a" ++ A = "aba".
or
[$a | A] = [$a, $b, $c].
, if you prefer the list syntax. This works because the tail of a list (the part after the “|” character above, or after the “++” in the string syntax version) is always part of the list structure, thus both sides in this case share the same structure – a flat list. It does “not” work however if the prefix (“a” in this case) is a bound variable – it can only work on literal strings unfortunately. Erlang cannot either do the reverse – to match A ++ “a” = “aba”. This is an “illegal pattern” in Erlang because there is no way to match out a unbound prefix out of a list like this in Erlang. There is not even a syntax available for it. Even worse would be to attempt matching A ++ “b” ++ “c” ++ B = “abcd” which gives you yet another “illegal pattern” of course. The Erlang pattern matcher is cool and all, but it does not do magic for you.
All hope is not lost however. We can still have fun with more advanced pattern matching in Erlang as a more adept pattern matcher (a matcher that would support the powers of our template language) is fairly easy to write in Erlang (you just won’t get the nice, compact syntactic sugar for it as you get with the built-in Erlang matcher). So let us, as an exercise, now build that template matcher and see where that takes us, shall we?
Building the template matcher
In our template language we let uppercase characters represent placeholders (or variable names) that could match against lowercase sequences (where the empty sequence is the shortest such sequence). If we want such a template matcher library to be a bit more useful in different programming contexts we could instead let the sequences contain any characters and define the template variables to have a more seldom seen pattern – such as for instance the pattern $(VARIABLE_NAME). This means that templates could now look like the following examples.
The last of the examples shows a repeated variable – in the string “a$(A)$(A)a” the variable A occurs twice. When we now implement the template matcher we would like to maintain the Erlang approach that says that, once a variable is bound to a variable it will remain bound to that variable and the match should fail if it would cause a variable to change its value at a later stage in the matching process.
Implementation
First, let us define the API. It is a function called match that takes two arguments – a template string and a string that you should attempt to match the template against, so calling match(Template, String) would be equivalent to do a Template = Sequence in our template language.
The matching process then. It consists of iterating through the template and string arguments while maintaining a dictionary of discovered variable bindings. If we manage to reach the end of both strings at the same time, without detecting a conflict where a variable is re-bound to a new, different value we have found a match. The high-level function would look like the following piece of code where we start the matching process with an empty dictionary (line 6 – empty maps are denoted #{} in Erlang). The return value of the match function is the resulting dictionary of variable bindings which can be used for other computations, or, if the match fails, an error tuple {error, Reason}.
What does match/3 look like then? First of all, if the template is empty and the string is empty, then we have found a match and we return the resulting dictionary
match([], [], D) ->
D;
If the beginning of the template string is the start of a variable – “$(” – we read the variable name up until its ending “)” (line 16), return the variable name and what remains of the template string after the variable and check if this variable is already bound in the dictionary (line 18). If the variable is not bound (line 19) we return the resulting dictionary where we iteratively try to bind and match the variable name to a larger and larger value, starting with the empty value [], in what remains of the template against the string. If, on the other hand, the variable already had a value (CurrentValue – line 22) we replace the variable name in the template with the value of that variable and return the result of trying to match the new template against the string using the dictionary, D.
match("$(" ++ Rest, String, D) ->
{ok, VarName, RemainsAfterVariable} = read_var_name(Rest),
case maps:get(VarName, D, undefined) of
undefined -> %% if we don't have an existing binding we try all possible bindings
bind(VarName, [], RemainsAfterVariable, String, D);
CurrentValue -> %% have existing binding, substitute the value of the variable and try to match
match(lists:flatten([CurrentValue | RemainsAfterVariable]), String, D)
end;
If the first characters in the template and the string are equal (line 25 – see how we use the Erlang’s matcher to enforce equality by using C in both first and second argument) and is not the beginning of a variable name – does not start with “$(” – we return the match result we get when we just remove the first character in both arguments and then match the remaining strings against each other (note: since this clause comes after the clause above we know that C is not the beginning of “$(” in this case because otherwise we would have chosen that clause instead)
Otherwise, if none of the clauses above was chosen (because they did not match) we know that we do not have a match, so we return an error tuple.
match(_, _, _) ->
{error, no_match}.
If it were not for the length of the name, the function bind should have perhaps better been called bind_and_match, because what it does is to try and bind a variable name to a value and then return the result of the first successful match it finds (or none). So what does the bind function look like?
First, if there is nothing remaining in the Template nor the String we simply extend the dictionary, D, with the VarName pointing to the Value we have found so far and return the dictionary (the lists:reverse is because we build up the value in reverse as we scan through the string – a well-known Erlang approach)
Then, if we try to bind a variable VarName when there is nothing left after the variable in the template, then the value of that variable is simply what remains in the string, so we extend D by letting VarName bind to what is left in the string
If we reach the end of the string but we have characters left in the template, we extend the dictionary, D, with the Value we have found so far and then return the result of matching the remainder of the template against the empty string – which would of course fail unless the template contains only variables that can be bound to zero length values.
If the rest of the template is the same as the string, we bind the accumulated value AccValue to the variable name and return the dictionary, D, (once again, note how the Erlang matcher constrains the two variables to be equal – this clause would not be taken unless its arguments matches the clause, thus argument 3 and 4 must be equal.
Then, lastly, we are in the process of finding the value for VariableName and have so far found the value AccValue and the rest of the string starts with some character C (line 46). We try to create a new dictionary, NewD, by binding the variable to AccValue (line 47 – once again we do lists:reverse because we have accumulated the value in reverse), then we try to match the remainder using this new dictionary (line 48). If this fails (line 49), we instead add C to the accumulated variable value and try, recursively, to bind the variable name to that value instead, using what is left of the string after having removed C (line 50). However, if we find a match (on line 48) we return yet another dictionary, YetAnotherD (line 53), which is our resulting dictionary.
(The read_var_name function is left as an exercise for the reader, or you can have a look at the full code in the git repository[2])
Test drive
So now we can try our template matcher with some examples
1> template:match("$(A)", "Hello world!").
#{"A" => "Hello world!"}
2> template:match("Stefan $(SURNAME)", "Stefan Hellkvist").
#{"SURNAME" => "Hellkvist"}
3> template:match("Because I think $(SOMETHING) is better than $(SOMETHING_ELSE)", "Because I think Mesi is better than Ronaldo").
#{"SOMETHING" => "Mesi","SOMETHING_ELSE" => "Ronaldo"}
4> template:match("a$(A)$(A)a", "abba").
#{"A" => "b"}
5> template:match("$(A)ab$(A)$(B)$(A)", "abb").
#{"A" => [],"B" => "b"}
6> template:match("a$(A)a$(B)", "abaa").
#{"A" => "b","B" => "a"}
7> template:match("a$(A)$(B)a", "abba").
#{"A" => [],"B" => "bb"}
, where [] in the answers denote the empty string (strings and lists are the same thing in Erlang…unfortunately).
Note that, the 7th example is our example from part I which has more than one solution. Although our method manages to find a match (A=””, B=”bb”) it might not be the one you expected to see perhaps. The template matcher will give you the first solution it finds, not all of them.
The template library on github also includes the reverse function of the match – the replace. This function takes a template and a dictionary and will replace variables in the template with whatever binding these variables have in the dictionary. That implementation is much more straight forward though.
In part III of this series about pattern matching I will make use of this template match (and replace) library to try to do some rudimentary natural language processing.
Let us assume a template language of all character sequences containing any number of lowercase and uppercase characters ([A-Za-z]*), where lowercase characters are literals – constants with a name – and uppercase characters are placeholders for any sequence of lowercase characters (including the empty sequence).
Then, given such a template, play the game of trying to match the template with a sequence containing only lowercase characters, where “match” is the problem of finding values for all the uppercase characters so that the two sequences become equal. For instance, try to figure out what sequences the uppercase characters would represent in the below examples:
I’m curious. Did you enjoy playing this game? And did you think about all the different solutions for the fourth example? For me, even this simple game gives me a very odd satisfaction which I cannot really explain. Could it be some kind of OCD[1]?
I returned to using Erlang some time around year 2000 after having spent several years building systems in Pascal, C, C++, Python, Perl, PHP, Javascript and (far too much) Java. From the start, Erlang just felt “right” and over the years I have grown more and more fond of it. I often wonder why it has the appeal it has on me. Why does not Go (I do a lot of Go programming as well) have the same appeal as Erlang? I sometimes give vague reasons like “Erlang matches well how I solve computer science problems” without knowing what I really mean, or I try to find more well-defined reasons like “on a multi-core CPU it really is an awesome way to make good use of the hardware” or “the fail-fast methodology with supervision trees makes for very robust software”, but the more I think about it, what really attracts me, is the pattern matching abilities of this beautiful language in combination with its functional programming paradigm.
In computer science, pattern matching is the act of checking a given sequence of tokens for the presence of the constituents of some pattern. […] The patterns generally have the form of either sequences or tree structures. Uses of pattern matching include outputting the locations (if any) of a pattern within a token sequence, to output some component of the matched pattern, and to substitute the matching pattern with some other token sequence (i.e., search and replace).
In Erlang the matching operator is the equal sign, ‘=’ (which is a bit confusing for people coming from other programming languages where an equal sign means “assign a value to a variable”). In Erlang, the equal sign simply means that you match the left-hand side with whatever is on the right-hand side with the side effect that you, if the match succeeds, bind any variables found in the pattern on the left-hand side. In Erlang, once a variable is bound to a value as a result of a match, it will always represent that value within that scope, forever. You can never “re-bind” a variable to a new value (or “re-assign” if you think in more traditional terms). This can be shown in our invented sequence language from above with the following three sequence example
Here we realize that the three sequences together cannot match as the first two sequences would bind A to bc (in some imaginary “context” where we store our bindings) which would make the third sequence bcbc, which does not match the other two sequences. In Erlang, when you try to match and fail doing so, you get an exception, like in the below Erlang example
A = 1,
A = 2.
** exception error: no match of right hand side value c
, where you get an exception on line 2 because A is on line 1 bound to the integer 1 and integer 1 cannot ever match integer 2.
1 = 2.
** exception error: no match of right hand side value 2
but the below code is fine of course as 1 matches 1 (although it is code seldom seen in real life I suppose)
1 = 1.
Are you still reading this? Ok, then perhaps you must have the same odd fascination for pattern matching as I do, or perhaps you suffer from something else 🙂
The pattern matching in Erlang [3] not only makes your code expressive and therefore short (which is an important beauty aspect of a program), but it also gives you these extremely charming puzzles (like the game above) to solve while you program which brings some kind of creative energy to the programming experience. There just is something charming with taking two patterns and see how they would match (if they would match at all). Pattern matching is however by no means unique to Erlang. It exists in many other languages such as Snobol, Haskell and nowadays somewhat even in Python and Javascript. In languages where it does not exist however I nowadays dearly miss its powers.
Pattern matching in Erlang
Pattern matching plays a large part in any Erlang program. One example is how Erlang “selects” function clauses to execute as in the example below where sum_list/2 has two clauses starting on lines 6 and 9 and the clause to execute is selected depending on matching of the two arguments (where in this case the value of the second argument plays no role) – if the list is empty, take the first clause, otherwise select the second clause.
%% calculate the sum of all numbers in a list
sum_list(Ls) ->
sum_list(Ls, 0).
sum_list([], C) ->
C;
sum_list([A | Rest], C) ->
sum_list(Rest, C + A).
You can match on any term, any type, in Erlang just as long as the left-hand side of the match follows the same structure as the right-hand side. The left-hand side may include unbound variables but the right-hand side can only include bound variables.
You can match lists
[1, A | B] = [1, 2, 3, 4, 5].
%% A = 2,
%% B = [3, 4, 5]
You can match strings (which are lists, but there is a syntactical sugar for matching strings which is worth noting)
"prefix" ++ A = "prefixa".
%% A = "a"
You can match binaries (where you have the option to use special bit-field specifiers)
%% matching out the header fields from a binary IP Packet
<<?IP_VERSION:4, HLen:4, SrvcType:8, TotLen:16,
ID:16, Flgs:3, FragOff:13,
TTL:8, Proto:8, HdrChkSum:16,
SrcIP:32,
DestIP:32, RestDgram/binary>> = Packet
You can match maps
#{a := A, b := #{c := C}} = #{a => 1, b => #{c => 2}}.
%% A = 1
%% C = 2
You can match tuples
{A, B} = {1, 2}.
%% A = 1
%% B = 2
…and well, any term constructed from any combination of types you can think of
{A, [#{key := "abc" ++ C}, B]} = {a, [#{key => "abcdef"}, 2]}.
%% A = a
%% B = 2
%% C = "def"
Is this not beautiful? Making use of matching can make your code very dense and expressive and, to some (like me), it also enhances the pleasure of writing code. Pattern matching can also be used to enforce constraints on your data structures so that, if a match fails, you know that your program is in a bad state and should be restarted (in Erlang you just let things crash and have some supervisor restart the failed service).
I will continue writing about pattern matching in more general terms in part two of this post.