Category Archives: Erlang Thursday

Erlang Thursday – dict:merge/3

Today’s Erlang Thursday is on dict:merge/3.

dict:merge/3 takes 3 arguments, the first argument is a merge function to be called when there is a key collision, and the second and third arguments are dictionaries.

The merge function is a function that takes the key as the first argument, the value from the first dictionary as the second argument, and the value from the second dictionary as the the third argument.

dict:merge(fun (_Key, Value1, Value2) -> [Value1, Value2] end,
           dict:from_list([{a, 1}, {b, 2}, {x, 5}]),
           dict:from_list([{x, 7}, {y, 8}, {z, 10}])).
% {dict,5,16,16,8,80,48,
%       {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
%       {{[],
%         [[a|1]],
%         [[b|2]],
%         [],[],[],[],[],
%         [[x,5,7]],
%         [[y|8]],
%         [[z|10]],
%         [],[],[],[],[]}}}

dict:merge(fun (_Key, Value1, Value2) -> Value1 * Value2 end,
           dict:from_list([{a, 1}, {b, 2}, {x, 5}]),
           dict:from_list([{x, 7}, {y, 8}, {z, 10}])).
% {dict,5,16,16,8,80,48,
%       {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
%       {{[],
%         [[a|1]],
%         [[b|2]],
%         [],[],[],[],[],
%         [[x|35]],
%         [[y|8]],
%         [[z|10]],
%         [],[],[],[],[]}}}

The merge function passed to dict:merge/3 only gets called in the case of a collision, as shown below. Note that there is a call to exit in the body of the function which would cause the process to terminate if the function was ever invoked.

dict:merge(fun (_Key, _Value1, _Value2) -> exit(merge_happened) end,
           dict:from_list([{a, 1}, {b, 2}]),
           dict:from_list([{x, 7}, {y, 8}, {z, 10}])).
% {dict,5,16,16,8,80,48,
%       {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
%       {{[],
%         [[a|1]],
%         [[b|2]],
%         [],[],[],[],[],
%         [[x|7]],
%         [[y|8]],
%         [[z|10]],
%         [],[],[],[],[]}}}

If you wish to treat the merge as an overlay of the second dictionary over the first, the merge function just needs to return the value from the second dictionary in the case of a key conflict.

dict:merge(fun (_Key, _Value1, Value2) -> Value2 end,
           dict:from_list([{a, 1}, {b, 2}, {x, 5}]),
           dict:from_list([{x, 7}, {y, 8}, {z, 10}])).
% {dict,5,16,16,8,80,48,
%       {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
%       {{[],
%         [[a|1]],
%         [[b|2]],
%         [],[],[],[],[],
%         [[x|7]],
%         [[y|8]],
%         [[z|10]],
%         [],[],[],[],[]}}}

If you want to keep all of the keys and values in the first dictionary, and just add the keys and values that are in the second dictionary, but not in the first dictionary, the merge function should just return the value associated with the first dictionary.

dict:merge(fun (_Key, Value1, _Value2) -> Value1 end,
           dict:from_list([{a, 1}, {b, 2}, {x, 5}]),
           dict:from_list([{x, 7}, {y, 8}, {z, 10}])).
% {dict,5,16,16,8,80,48,
%       {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
%       {{[],
%         [[a|1]],
%         [[b|2]],
%         [],[],[],[],[],
%         [[x|5]],
%         [[y|8]],
%         [[z|10]],
%         [],[],[],[],[]}}}

Just a peek into the new Maps that came in to Erlang in the 17.0 release.

–Proctor

Erlang Thursday – string:join/2

Today’s Erlang Thursday is on string:join/2.

string:join/2 takes a list of strings as its first argument, and a string separator used to join the strings together into a single string.

91> string:join(["a", "b", "c"], "").
"abc"
92> string:join(["a", "b", "c"], "-").
"a-b-c"

The separator string can be a string of any length, and doesn’t just have to be a single character.

93> string:join(["a", "b", "c"], "___").
"a___b___c"
94> string:join(["a", "b", "c"], " ").  
"a b c"

And as with any string, a list of characters, or even integers, can be used as the separator string.

string:join(["a", "b", "c"], [$A]).
# "aAbAc"
string:join(["a", "b", "c"], [52]).
# "a4b4c"

–Proctor

Erlang Thursday – string:tokens/2

Today’s Erlang Thursday is string:tokens/2.

string:tokens/2 takes a string as the first argument, and a list of separators to split the string on, and returns a list of token strings.

string:tokens("foo", "").
% ["foo"]
string:tokens("banana", "a").
% ["b","n","n"]
string:tokens("It was the best of times, it was the worst of times", " ").
% ["It","was","the","best","of","times,","it","was","the",
%  "worst","of","times"]

If consecutive separators appear in the string they will be treated as a single separator, and no empty strings will be returned.

string:tokens("Mississippi", "s").
% ["Mi","i","ippi"]
65> string:tokens("Mississippi", "sp").
% ["Mi","i","i","i"]
string:tokens("Mississippi", "is").
% ["M","pp"]

The order of the separators in the separator list passed to string:tokens/2 does not matter, and can be specified in any order.

string:tokens("Mississippi", "ps").
% ["Mi","i","i","i"]
65> string:tokens("Mississippi", "sp").
% ["Mi","i","i","i"]

And as the separator list is just simply a list of separators, instead of passing a string, the integer values for the characters to use as the separators can be passed as a list, as a list of the integers is the same as a string.

$s.
% 115
$p.
% 112
[115, 112].
% "sp"
string:tokens("Mississippi", [115]).
% ["Mi","i","ippi"]
string:tokens("Mississippi", [115, 112]).
% ["Mi","i","i","i"]

–Proctor

Erlang Thursday – lists:dropwhile/2

Today’s Erlang Thursday is lists:dropwhile/2.

lists:dropwhile/2 takes a predicate function and a list, and returns a list where the first series of items for which the predicate function returned true have been removed.

lists:dropwhile(fun erlang:is_atom/1, [hello, 'World', foo, 1, 3, 4]).
% [1,3,4]
lists:dropwhile(fun (X) -> X > 0 end, [-1, 0, 1, 2, 3]).
% [-1,0,1,2,3]
lists:dropwhile(fun (X) -> X > 0 end, [-2, -1, 0, 1, 2, 3]).
% [-2,-1,0,1,2,3]
lists:dropwhile(fun (X) -> X < 0 end, [-2, -1, 0, 1, 2, 3]).
% [0,1,2,3]
lists:dropwhile(fun (X) -> X < 0 end, [0, -1, -2, -3, -4, -5]). 
% [0,-1,-2,-3,-4,-5]
lists:dropwhile(fun (X) -> true end, [hello, 'World', foo, 1, 3, bar, 4]). 
% []
lists:dropwhile(fun (X) -> false end, [hello, 'World', foo, 1, 3, bar, 4]).
% [hello,'World',foo,1,3,bar,4]

Unlike lists:filter/2, lists:dropwhile/2 stops checking the list as soon as the predicate function returns false. This means that elements for which the predicate function would return true can still appear in the result list, as if they occur after an element for which the predicate function returns false.

lists:dropwhile(fun erlang:is_atom/1, [hello, 'World', foo, 1, 3, bar, 4]).
% [1,3,bar,4]
lists:filter(fun (X) -> not is_atom(X) end, [hello, 'World', foo, 1, 3, bar, 4]).     
% [1,3,4]
lists:dropwhile(fun (X) -> X < 0 end, [-2, -1, 0, 1, -5, 3, 7]).
% [0,1,-5,3,7]
lists:filter(fun (X) -> X >= 0 end, [-2, -1, 0, 1, -5, 3, 7]).   
% [0,1,3,7]

–Proctor

Erlang Thursday – lists:filter/2

Today’s Erlang Thursday is on lists:filter/2.

lists:filter/2 takes two arguments, a predicate function and a list to iterate over. The return value is a list of items for which the predicate function returns true for that item.

lists:filter(fun (X) -> X rem 2 =:= 1 end, [1, 2, 3, 4, 5]).
% [1,3,5]
lists:filter(fun erlang:is_atom/1, [1, a, 3, {a, b}, 'World', foo]).
% [a,'World',foo]
lists:filter(fun (X) -> X > 0 end, [1, 0, -3, foo, -13, 43]).
% [1,foo,43]
lists:filter(fun (X) -> X > 0 end, []).                      
% []
lists:filter(fun (X) -> false end, [1, 2, 3, 4, 5]).
% []
lists:filter(fun (X) -> true end, [1, 2, 3, 4, 5]). 
% [1,2,3,4,5]

–Proctor

Erlang Thursday – httpc:request/1 and httpc:request/4

Today’s Erlang Thursday is on httpc:request/1 and httpc:request/4. The httpc module is Erlang’s HTTP 1.1 client, and the request function is a powerful way to make web requests using Erlang.

To start using the httpc module, you first have to make sure inets has been started.

inets:start().
% ok

httpc:request/1 takes one argument, and that is the URL, as a Erlang string, you want to make the request against.

httpc:request("http://www.example.com").
% {ok,{{"HTTP/1.1",200,"OK"},
%      [{"cache-control","max-age=604800"},
%       {"date","Thu, 22 Jan 2015 02:57:06 GMT"},
%       {"accept-ranges","bytes"},
%       {"etag",""359670651""},
%       {"server","ECS (ftw/FBE4)"},
%       {"content-length","1270"},
%       {"content-type","text/html"},
%       {"expires","Thu, 29 Jan 2015 02:57:06 GMT"},
%       {"last-modified","Fri, 09 Aug 2013 23:54:35 GMT"},
%       {"x-cache","HIT"},
%       {"x-ec-custom-error","1"}],
%      "<!doctype html>n<html>n<head>n    <title>Example Domain</title>nn    <meta ..."}}

httpc:request/1 is the equivalent of the httpc:request/4 function called as httpc:request(get, {Url, []}, [], []).

httpc:request(get, {"http://www.example.com", []}, [], []).
% {ok,{{"HTTP/1.1",200,"OK"},
%      [{"cache-control","max-age=604800"},
%       {"date","Thu, 22 Jan 2015 03:04:31 GMT"},
%       {"accept-ranges","bytes"},
%       {"etag",""359670651""},
%       {"server","ECS (ftw/FBE4)"},
%       {"content-length","1270"},
%       {"content-type","text/html"},
%       {"expires","Thu, 29 Jan 2015 03:04:31 GMT"},
%       {"last-modified","Fri, 09 Aug 2013 23:54:35 GMT"},
%       {"x-cache","HIT"},
%       {"x-ec-custom-error","1"}],
%      "<!doctype html>n<html>n<head>n    <title>Example Domain</title>nn    <meta ..."}}

You can specify headers as part of your request. For example, say we want to get DuckDuckGo’s page in Swedish in honor of Erlang being created by Ericsson. To do that, we add a tuple of {"Accept-Language", "sv"} to the headers list as part of the request.

httpc:request(get, {"http://duckduckgo.com/", [{"Accept-Language", "sv"}]}, [], []).
% {ok,{{"HTTP/1.1",200,"OK"},
%      [{"cache-control","max-age=1"},
%       {"connection","keep-alive"},
%       {"date","Thu, 22 Jan 2015 03:19:29 GMT"},
%       {"accept-ranges","bytes"},
%       {"etag",""54bfe2a8-1488""},
%       {"server","nginx"},
%       {"content-length","5256"},
%       {"content-type","text/html; charset=UTF-8"},
%       {"expires","Thu, 22 Jan 2015 03:19:30 GMT"}],
%      "<!DOCTYPE html>n<!--[if IEMobile 7 ]> <html lang="sv_SE" class="no-js iem7"> ..."}}

The third argument of httpc:request/4 is a list of HTTP option tuples. For example, you need to set timeouts on the response in order to avoid waiting on a response from an irresponsive or slow website because if it doesn’t respond in time, the requesting code needs to back off and try again later to avoid triggering the equivalent of a Denial of Service attack. In this case, I am specifying a timeout of 0, expressed in milliseconds, to ensure a timeout happens for illustrative purposes.

httpc:request(get, {"http://erlang.org/", []}, [{timeout, 0}], []).
{error,{failed_connect,[{to_address,{"erlang.org",80}},
                        {inet,[inet],timeout}]}}

As it’s final argument, httpc:request/4 takes a list of other options, these options are for how the Erlang side of things should work. Maybe you want to make a request asynchronously, and want to receive a message when it is complete. To do that you can specify an option tuple of {sync, false}.

{ok, RequestId} = httpc:request(get, {"http://www.example.com", []}, [], [{sync, false}]).
% {ok,#Ref<0.0.0.179>}
receive {http, {RequestId, Result}} -> Result after 500 -> error end.
% {{"HTTP/1.1",200,"OK"},
%  [{"cache-control","max-age=604800"},
%   {"date","Thu, 22 Jan 2015 03:08:41 GMT"},
%   {"accept-ranges","bytes"},
%   {"etag",""359670651""},
%   {"server","ECS (ftw/FBE4)"},
%   {"content-length","1270"},
%   {"content-type","text/html"},
%   {"expires","Thu, 29 Jan 2015 03:08:41 GMT"},
%   {"last-modified","Fri, 09 Aug 2013 23:54:35 GMT"},
%   {"x-cache","HIT"},
%   {"x-ec-custom-error","1"}],
%  <<"<!doctype html>n<html>n<head>n    <title>Example Domain</title>nn    <meta "...>>}

Or maybe you want to get the response body back as an Erlang binary instead of a string.

httpc:request(get, {"http://www.example.com", []}, [], [{body_format, binary}]).
% {ok,{{"HTTP/1.1",200,"OK"},
%      [{"cache-control","max-age=604800"},
%       {"date","Thu, 22 Jan 2015 03:58:55 GMT"},
%       {"accept-ranges","bytes"},
%       {"etag",""359670651""},
%       {"server","ECS (ftw/FBE4)"},
%       {"content-length","1270"},
%       {"content-type","text/html"},
%       {"expires","Thu, 29 Jan 2015 03:58:55 GMT"},
%       {"last-modified","Fri, 09 Aug 2013 23:54:35 GMT"},
%       {"x-cache","HIT"},
%       {"x-ec-custom-error","1"}],
%      <<"<!doctype html>n<html>n<head>n    <title>Example Domain</title>nn    <meta "...>>}}

This post just scratches the surface of what you can do with httpc:request/4, and I highly recommend checking out the Erlang documentation for the httpc module. For more examples and information, also check out the Erlang inets User Guide, and the chapter “HTTP Client“.

–Proctor

Erlang Thursday – erlang:apply/3

Today’s Erlang Thursday is on erlang:apply/3.

With functional languages we love to pass functions around as the first class citizens that they are. But sometimes we don’t know which function it is that we will need to invoke, causing us to be unsure of the arguments the function takes up front. If we knew, we could just invoke it as Fun(Arg1, Arg2, ..., ArgN), but that doesn’t work if we could get different functions of varying arities. Enter erlang:apply/3.

erlang:apply/3, takes the module name, the function name, and a list of the arguments to be passed to the function. The function passed to erlang:apply/3 must also have been exported, otherwise an error will be raised.

erlang:apply(lists, max, [[7, 3, 5, 11, 1]]).
% 11
erlang:apply(lists, merge, [[1, 2, 3], [a, b, c]]).        
% [1,2,3,a,b,c]
erlang:apply(lists, merge, [[1, 2, 3], [a, b, c]]).           
% [1,2,3,a,b,c]

The Erlang documentation points out that this should be used only when the number of arguments is not known at compile time. Otherwise we could just do the a normal function invocation, even if passed a anonymous function.

fun lists:max/1([1, 2, 3, 4]).
4

The erlang module also includes a version erlang:apply/2 that takes a function as it’s first argument, and a list of the arguments to be passed to the function as it’s second argument.

erlang:apply(fun lists:merge/2, [[1, 2, 3], [a, b, c]]).
% [1,2,3,a,b,c]

While erlang:apply/2 and erlang:apply/3 will not be part of your common usage, there are cases where it is needed, like last weeks timer:tc. And though your usage of it will likely be rare, it is still good to know that you have it handy.

–Proctor

Erlang Thursday – timer:tc/3

Today’s Erlang Thursday is on timer:tc/3.

I am sure we have all written some timing code where we capture the current time, do something, capture the current time again and then find the difference to find out how long something took to execute. In Erlang, that generally looks something like the following:

Time1 = now().
% {1420,519186,111375}
timer:sleep(4000).  % Do something
% ok
Time2 = now().
% {1420,519190,118280}
timer:now_diff(Time2, Time1).
% 4006905

Note that we have to use timer:now_diff/2, since the now() function returns the timestamp as a tuple, and we can’t just do normal subtraction on that tuple like we might be able to in other languages.

Of course as good “engineers”, we know that since we need to do timings in various places of the app we can just create our own function to do that, and have that live in just one place.

The downside is: the wise people on the Erlang language team have done that for us already and provided it in the form of timer:tc/3.

timer:tc/3 takes the module name, function name, and a list of the arguments to be passed to the function. And since we usually want the result of the function we are calling, in addition to the timing, the return value is a tuple of the time in microseconds, and the result of applying the function passed to timer:tc/3.

timer:tc(timer, sleep, [4000]). 
% {4003097,ok}
timer:tc(lists, foldl, [fun(X, Accum) -> X + Accum end, 0, lists:seq(1, 2000000)]). 
% {5099481,2000001000000}

There is also timer:tc/1 which takes just a function and applies it, and timer:tc/2 which takes a function and applies it with the given arguments.

timer:tc(fun() -> lists:foldl(fun(X, Accum) -> X + Accum end, 0, lists:seq(1, 2000000)) end).
% {5709293,2000001000000}
timer:tc(fun lists:foldl/3, [fun(X, Accum) -> X + Accum end, 0, lists:seq(1, 2000000)]).
% {5766480,2000001000000}

–Proctor

Erlang Thursday – lists:any/2

Today’s Erlang Thursday function of the week is lists:any/2.

lists:any/2 takes a predicate function as the first argument, and a list to iterate over as its second argument. lists:any/2 returns true if the predicate function returns true for any of the elements in the given list, otherwise, lists:any/2 returns false.

lists:any(fun erlang:is_atom/1, [1, 2, 3, 4, 5, 6, 7]).
% false
lists:any(fun erlang:is_atom/1, [1, 2, 3, 4, a, 6, 7]).
% true
lists:any(fun erlang:is_atom/1, [{1, 2}, 3, 4, a, 6, 7]). 
% true
lists:any(fun(X) -> X rem 2 == 1 end, [1, 2, 4]).
% true
lists:any(fun(X) -> X rem 2 == 1 end, [0, 2, 4]).    
% false

lists:any/2 is eager, and will return with a result of true as soon as it is found, and will ignore processing the rest of the list.

timer:tc(lists, any, [fun(X) -> X rem 2 == 1 end, lists:seq(2, 200000, 2)]).
% {248410,false}
timer:tc(lists, any, [fun(X) -> X rem 2 == 0 end, lists:seq(2, 200000, 2)]).
% {13,true}

The lists module also contains a function lists:all/2, similar to lists:any/2, but checks if the predicate function returns true for every element in the supplied list.

lists:all(fun erlang:is_number/1, [1, 2, 3, 4, a, 6, 7]).
% false
lists:all(fun erlang:is_number/1, [1, 2, 3, 4, 5, 6, 7]).
% true

lists:all/2 is also eager, and will return with a result of false as soon as it is found, and will ignore processing the rest of the list.

timer:tc(lists, all, [fun(X) -> X rem 2 == 0 end, lists:seq(2, 200000, 2)]).
% {235276,true}
timer:tc(lists, all, [fun(X) -> X rem 2 == 1 end, lists:seq(2, 200000, 2)]).
% {14,false}

–Proctor

Erlang Thursday – lists:partition/2

Today’s Erlang Thursday is lists:partition/2.

lists:partition/2 takes two arguments, a predicate function that will be called for every entry in the list, and returns a boolean value. The second argument to lists:partition/2 is the list to be partitioned.

lists:partition/2 returns a two-tuple, with the first item in the tuple being the list of those items for which the predicate function returns true. The second item in the tuple is a list of those items for which the predicate function returned false.

lists:partition(fun(X) -> X rem 2 == 1 end, [1, 2, 3, 4, 5, 6, 7]).
% {[1,3,5,7],[2,4,6]}
lists:partition(fun(X) -> X rem 3 == 0 end, [1, 2, 3, 4, 5, 6, 7]).
% {[3,6],[1,2,4,5,7]}
lists:partition(fun erlang:is_atom/1, [a, 1, [b, c], 'B', fun lists:sum/1]).
% {[a,'B'],[1,[b,c],#Fun<lists.sum.1>]}
lists:partition(fun erlang:is_atom/1, [a, 1, {b, [z]}, 'B', fun lists:sum/1]).
% {[a,'B'],[1,{b,[z]},#Fun<lists.sum.1>]}
lists:partition(fun erlang:is_atom/1, []).                                    
% {[],[]}

–Proctor