Erlang, Matching with list foreach - erlang

I've been making a chat application in Erlang for a school project, but I've run into an issue. I'm trying to make my program concurrent and in order to do so I start a new thread for each message a channel is sending. I do this using lists:foreach, but I want to make sure that I don't message the person who typed in the channel.
request(State, {message, {UserID,UserPID}, Token}) ->
case catch lists:member({UserID,UserPID}, State#channel.users) of
false ->
{{error, user_not_joined}, State};
true ->
spawn( fun() ->
ListOfUsers = State#channel.users,
UserPIDs = lists:map(fun ({_, V}) -> V end, ListOfUsers),
%spawn( fun() ->end)
lists:foreach(
fun(UserPID) -> ok end,
fun(PID) ->
spawn( fun() -> genserver:request(PID, {message_from_server, State#channel.name, UserID, Token}) end)
end, UserPIDs) end),
{ok, State}
end;
What I pretty much want to do is to match with the UserPID inside the foreach. As of now I only get warnings:
channel.erl:39: Warning: variable 'UserPID' is unused
channel.erl:39: Warning: variable 'UserPID' shadowed in 'fun'
Line 3 is fun(UserPID) -> ok end,
Cheers

The answer by legoscia is fine, but I'd add that often list comprehension is simpler to use and simpler to read than lists:foreach. Note that list comprehension is able to ignore values based on clauses. Consider the following example:
-module(filter).
-export([do/0]).
do() ->
Values = lists:seq(1,10),
IgnoreThisValue = 5,
%% print all values unequal to IgnoreThisValue
[io:format("Value: ~b~n", [Value]) ||
Value <- Values, Value =/= IgnoreThisValue],
ok.
Run it in the shell:
1> make:all([load]).
Recompile: filter
up_to_date
2> filter:do().
Value: 1
Value: 2
Value: 3
Value: 4
Value: 6
Value: 7
Value: 8
Value: 9
Value: 10
A side note on your code: Why do you spawn a thread per process? I assume that you are using the behaviour gen_server (correct me if I am wrong). If so, you should consider using the cast function to simply send a message. As you do not check the result of genserver:request/2, this might be a viable option which saves you a lot of processes.

Since the function argument shadows the existing variable, you need to use a guard for that:
fun(PID) when PID =:= UserPID -> ok end

Related

Implement a lists:map using case clauses instead of function clauses in Erlang

Can anyone tell me what this means? I am new to this and my friend recommended me to post in this website.
By the way I'm new to Erlang.
If possible I want to write a code in editor and I don't even understand the question any sample input/output and how it works an explanation will do. Thankyou
It seems to me that the question refers to the implementation of lists:map/2, a function that applies the same function (received as a parameter) to all elements of a list and returns the resulting list.
In other words, this function.
You can check the OTP Github repo to see how that function is implemented:
map(F, List) when is_function(F, 1) ->
case List of
[Hd | Tail] -> [F(Hd) | map_1(F, Tail)];
[] -> []
end.
map_1(F, [Hd | Tail]) ->
[F(Hd) | map_1(F, Tail)];
map_1(_F, []) ->
[].
Or you can conceive an even simpler implementation, as…
map(F, []) -> [];
map(F, [H|T]) -> [F(H) | map(F, T)].
Both of them (for the OTP version, I'm referring to map_1/2) use pattern-matching in function clause heads to distinguish between the base case and the recursive step of the function.
The request that you received is to implement the same algorithm using a single function clause with a case clause instead of the two function clauses you see above.
Here's a simple example showing how to use function clauses, then case statements to do the same thing. Put the following code in a file named a.erl in some directory:
-module(a).
-export([show_stuff/1, show_it/1]).
show_stuff(1) ->
io:format("The argument was 1~n");
show_stuff(2) ->
io:format("The argument was 2~n");
show_stuff(_)->
io:format("The argument was something other than 1 or 2~n").
show_it(X) ->
case X of
1 -> io:format("The argument was 1~n");
2 -> io:format("The argument was 2~n");
_ -> io:format("The argument was something other than 1 or 2~n")
end.
Note that the file name, a.erl and the module directive:
-module(a).
must match. So, if you named your file homework1.erl, then the module directive in the file must be:
-module(homework1).
To save a lot of typing, it's best to use very short module names (as you will see below).
In a terminal window, switch directories to the directory containing a.erl:
~$ cd erlang_programs/
then launch the erlang shell:
~/erlang_programs$ erl
Erlang/OTP 24 [erts-12.0.2] [source] [64-bit] [smp:4:4] [ds:4:4:10] [async-threads:1]
Eshell V12.0.2 (abort with ^G)
Next, execute the following statements:
1> c(a). <--- Compiles the code in your file
{ok,a} <--- Or, you may get errors which must be corrected, then try recompiling.
2> a:show_stuff(1).
The argument was 1
ok
3> a:show_stuff(4).
The argument was something other than 1 or 2
ok
4> a:show_it(1).
The argument was 1
ok
5> a:show_it(4).
The argument was something other than 1 or 2
ok
6>
Note the syntax for calling a function defined in a file/module:
module_name:function_name(arg1, arg2, ... argn).
any sample input/output and how it works an explanation will do
In the documentaion linked in Brujo Benavides's answer, you can see:
Takes a function from As to Bs, and a list of As and produces a list of Bs by applying the function to every element in the list. This function is used to obtain the return values.
So F is a function (of a single argument) such as fun(X) -> X*2 end. See https://www.erlang.org/doc/programming_examples/funs.html#syntax-of-funs or https://www.erlang.org/doc/reference_manual/expressions.html#funs to understand fun expressions. List1 is a list of values which the function F can work on (in this case numbers) such as [1,2,3]. Then list:map(fun(X) -> X*2 end, [1,2,3]) calls fun(X) -> X*2 end on each element of list [1,2,3] and returns the list of return values [2,4,6]. Your function should give the same result on these arguments.

How to communicate between different case situation in erlang case

I'm trying to do something like this:
test(Tester) ->
case Tester of
start -> X = 4
ok -> X = X + 5,
Y = X/5;
terminate -> Y
end.
But not exactly this. I Know it can be achieved with tail or simple recursion.
normally X and Y are unbound.
Is there any way to communicate between these cases without the usage of erlang global variables?
Erlang is a functional language it means we don't communicate between different parts of the code or store values in variables without purpose, we just compute to return value (and sometimes make some sideeffect). If we have common computation in different branches of code we can simply place it in common function.
test(Tester) ->
case Tester of
start -> 4;
ok -> computeY();
terminate -> computeY()
end.
computeY() ->
X = 4 + 5,
X/5.
If you need to access a variable in any clause body of a case statement, You have to assign it before case statement or sometimes you can assign it in case clause pattern:
test(Arg) ->
Size = get_size(Arg), % I will use 'Size' in each clause body
case Arg of
#{foo := Foo} -> % if Arg is an Erlang map and has key 'foo'
% I can use 'Foo' only here:
io:format("It's a map with size ~p and has key foo with value ~p\n", [Size, Foo]);
[Baz|_] -> % if Arg is an Erlang list with at least one element
% I can use 'Baz' only here and for example i can NOT use 'Foo' here:
io:format("It's a list with size ~p and its first element is ~p\n", [Size, Baz]);
_ ->
io:format("Unwanted argument ~p with ~p size\n", [Arg, Size])
end.
get_size(X) when is_map(X) -> map_size(X);
get_size(X) when is_list(X) -> length(X);
get_size(_) -> unknown.
I put above code in an Erlang fun named Test to using it in shell without need to compile a module file:
1> Test([5,4,3,2,1]).
It's a list with size 5 and its first element is 5
ok
2> Test(#{key => value, foo => ':)'}).
It's a map with size 2 and has key foo with value ':)'
ok
3> Test([]).
Unwanted argument [] with 0 size
ok
4> Test(#{key => value}).
Unwanted argument #{key => value} with 1 size
ok
5> Test(13).
Unwanted argument 13 with unknown size
ok
If you are curious about variable binding in case, I recommend to read this article
To do this in Erlang you would start (spawn) a process that would hold X in memory as well as the PID (process id) of the process it is supposed to reply to unless you want to pass it a different PID every time along with start/ok/terminate. Processes in Erlang have their own memory, state or loopData. After you spawn a process that knows how to handle specific messages, you pass it the messages and it replies by sending a message back.
start_test() ->
TestPID = spawn(?MODULE, test, [self()]),
TestPID ! start,
receive
X -> io:format("X is: ~p~n",[X]
end,
TestPID ! ok,
receive
{X,Y} -> io:format("X is: ~p, Y is: ~p~n",[X, Y]
end,
TestPID ! terminate,
receive
Y -> io:format("Y is: ~p~n",[Y]
end.
test(PID) ->
receive
start -> PID ! 4,
test(4, undefined, PID);
terminate -> undefined
end.
test(X, Y, PID) ->
receive
ok -> PID ! {X+5, (X+5)/5},
test(X+5, (X+5)/5, PID);
terminate -> PID ! Y
end.
Don't forget to create a module and export start_test/0 and test/1
If you run start_test() you should get an output of
X is: 4
X is: 9, Y is: 1.8
Y is: 1.8

idiomatic process synchronisation in Erlang

I am looking at how to code "map reduce" type scenarios directly in erlang. As a toy example, imagine I want to decide which of several files is the biggest. Those files might be anywhere on the internet, so getting each one might take some time; so I'd like to gather them in parallel. Once I have them all, I can compare their sizes.
My assumed approach is as follows:
A 'main' process to co-ordinate the work and determine which is biggest;
A 'worker' process for each file, which fetches the file and returns the size to the main process.
Here's a clunky but functioning example (using local files only, but it shows the intent):
-module(cmp).
-export([cmp/2]).
cmp(Fname1, Fname2) ->
Pid1 = fsize(Fname1),
Pid2 = fsize(Fname2),
{Size1, Size2} = collect(Pid1, Pid2),
if
Size1 > Size2 ->
io:format("The first file is bigger~n");
Size2 > Size1 ->
io:format("The second file is bigger~n");
true ->
io:format("The files are the same size~n")
end.
fsize(Fname) ->
Pid = spawn(?MODULE, fsize, [self(), Fname]),
Pid.
fsize(Sender, Fname) ->
Size = filelib:file_size(Fname),
Sender ! {self(), Fname, Size}.
collect(Pid1, Pid2) ->
receive
{Pida, Fnamea, Sizea} ->
io:format("Pid: ~p, Fname: ~p, Size: ~p~n", [Pida, Fnamea, Sizea])
end,
receive
{Pidb, Fnameb, Sizeb} ->
io:format("Pid: ~p, Fname: ~p, Size: ~p~n", [Pidb, Fnameb, Sizeb])
end,
if
Pida =:= Pid1 -> {Sizea, Sizeb};
Pida =:= Pid2 -> {Sizeb, Sizea}
end.
Specific Questions
Is the approach idiomatic? i.e. hiving off each 'long running' task into a separate process, then collecting results back in a 'master'?
Is there a library to handle the synchronisation mechanics? Specifically, the collect function in the example above?
Thanks.
--
Note: I know the collect function in particular is clunky; it could be generalised by e.g. storing the pids in a list, and looping until all had completed.
In my opinion it's best to learn from an example, so I had a look at how they do that in otp/rpc and based on that I implemented a bit shorter/simpler version of the parallel eval call.
call(M, F, ArgL, Timeout) ->
ReplyTo = self(),
Keys = [spawn(fun() -> ReplyTo ! {self(), promise_reply, M:F(A)} end) || A <- ArgL],
Yield = fun(Key) ->
receive
{Key, promise_reply, {error, _R} = E} -> E;
{Key, promise_reply, {'EXIT', {error, _R} = E}} -> E;
{Key, promise_reply, {'EXIT', R}} -> {error, R};
{Key, promise_reply, R} -> R
after Timeout -> {error, timeout}
end
end,
[Yield(Key) || Key <- Keys].
I am not a MapReduce expert but I did had some experience using this 3rd party mapreduce module. So I will try to answer your question based on my current knowledge.
First, your input should be arranged as pairs of keys and values in order to properly use the mapreduce model. In general, your master process should first start workers processes (or nodes). Each worker receives a map function and a pair of key and value, lets name it {K1,V1}. It then executes the map function with the key and value and emits a new pair of key and value {K2,V2}. The master process collects the results and waits for all workers to finish their jobs. After all workers are done, the master starts the reduce part on the pairs {K2,List[V2]} that were emited by the workers. This part can be executed in parallel or not, it used to combine all the results into a single output. Note that the List[V2] is because there can be more then one value that was emited by the workers for a single K2 key.
From the 3rd party module I mentioned above:
%% Input = [{K1, V1}]
%% Map(K1, V1, Emit) -> Emit a stream of {K2,V2} tuples
%% Reduce(K2, List[V2], Emit) -> Emit a stream of {K2,V2} tuples
%% Returns a Map[K2,List[V2]]
If we look into Erlangs' lists functions, the map part is actually equal for doing lists:map/2 and the reduce part is in some way similar to lists:foldl/3 or lists:foldr/3 and the combination between them are: lists:mapfoldl/3, lists:mapfoldr/3.
If you are using this pattern of mapreduce using sets of keys and values, there is no need for special synchronization if that is what you mean. You just need to wait for all workers to finish their job.
I suggest you to go over the 3rd party module I mentioned above. Take also a look at this example. As you can see, the only things you need to define are the Map and Reduce functions.

ERLANG - Pattern Matching

I have a variable:
Data = [[<<>>,
[<<"10">>,<<"171">>],
[<<"112">>,<<"Gen20267">>],
[<<"52">>,<<"20100812-06:32:30.687">>]]
I am trying to pattern match for two specific cases..
One where anything that resembles the outside structure - simply []
Anything inside goes I have tried [ _ ] but no go?
The Second, for a specific pattern inside, like when I see a <<"10">> or <<"112">> or <<"52">> then I am going to take the right side which is the actual data into an atom.
Basically the <<"10">> or <<"112">> or <<"52">> are the fields, the right side the data.
I have tried statements like [<<"10">>, _ ] still no go
Here is the rest of the code:
dataReceived(Message) ->
receive
{start} ->
ok;
[ _ ] -> %%No go
io:format("Reply 1 = ~p~n", [Message]);
[<<"10">>, _ ] -> %%No go
io:format("Reply 1 = ~p~n", [Message])
end.
As a note the Message is not sent as a tuple it is exactly like Data =
Can anyone lead me in the right direction?
Thanks and Goodnight!
-B
UPDATE
Ok now I think Im getting warmer, I have to pattern match whatever comes in.
So if I had say
Message = = [[<<>>],
[<<"10">>,<<"171">>],
[<<"112">>,<<"Gen20267">>],
[<<"52">>,<<"20100812-06:32:30.687">>]]
And I was looking to pattern match the field <<"112">>
Such as the 112 is always going to say 112, but the Gen2067 can change whenever to whatever.. its the data, it will be stored in a variable.
loop() ->
receive
[_,[<<"112">>, Data], _] when is_list(X) -> %% Match a list inside another.
?DEBUG("Got a list ~p~n", [X]),
loop();
_Other ->
?DEBUG("I don't understand ~p~n", [_Other]),
loop()
end.
I feel im close, but not 100%
-B
Update OP is trying to pass an argument to the function and not send messages.
As the name indicates the receive block is used to receive and process messages sent to a process. When you call dataReceived with an argument it proceeds to wait for messages. As no messages are sent it will continue to wait endlessly. Given the current code if you want it to do something then you'll have to spawn the function, get the process ID and then send a message to the process ID.
You probably need a function where the argument is pattern matched and not messages.
Something like this:
dataReceived([Message]) when is_list(Message) ->
io:format("Got a list as arg ~p~n", [Message]);
dataReceived(_Other) ->
io:format("Unknown arg ~p~n", [_Other]).
On a side note your third pattern [X] when is_list(X) will never match as the second pattern is a superset of the third. Anything that matches [X] when is_list(X) will always match [X] and therefore your third match clause will never get triggered.
Original Answer
I am not sure I understand your question. Are you trying to send a message to the function or are you passing it an argument?
This is a partial answer about how to match a list of lists in case you are sending a message.
-module(mtest).
-export([run/0]).
-ifdef(debug).
-define(DEBUG(Format, Args), io:format(Format, Args)).
-else.
-define(DEBUG(Format, Args), void).
-endif.
loop() ->
receive
[X] when is_list(X) -> %% Match a list inside another.
?DEBUG("Got a list ~p~n", [X]),
loop();
_Other ->
?DEBUG("I don't understand ~p~n", [_Other]),
loop()
end.
Take a look at the first clause in the receive block. [X] when is_list(X) will bind the inner list to the name X. I tested it with the value of Data you provided and it worked.
%% From the shell.
1> c(mtest, {d, debug}).
{ok,mtest}
2> Pid = mtest:run().
<0.40.0>
3> Data = [[<<>>, [<<"10">>,<<"171">>], [<<"112">>,<<"Gen20267">>], [<<"52">>,<<"20100812-06:32:30.687">>]]].
[[<<>>,
[<<"10">>,<<"171">>],
[<<"112">>,<<"Gen20267">>],
[<<"52">>,<<"20100812-06:32:30.687">>]]]
4> Pid ! Data.
[[<<>>,
[<<"10">>,<<"171">>],
[<<"112">>,<<"Gen20267">>],
[<<"52">>,<<"20100812-06:32:30.687">>]]]
Got a list [<<>>,
[<<"10">>,<<"171">>],
[<<"112">>,<<"Gen20267">>],
[<<"52">>,<<"20100812-06:32:30.687">>]]
5>

Convert a string into a fun

I'm trying to get around a problem with file:consult/1 not allowing tuples with fun in them like in this example:
{add_one, fun(X) -> X+1 end}.
To get around this I'm considering writing the fun inside a string and evaluating it
{add_one, "fun(X) -> X+1 end"}.
The question is. How do I convert the string into a fun?
parse_fun_expr(S) ->
{ok, Ts, _} = erl_scan:string(S),
{ok, Exprs} = erl_parse:parse_exprs(Ts),
{value, Fun, _} = erl_eval:exprs(Exprs, []),
Fun.
Note that you need a period at the end of your fun expression, e.g. S = "fun(X) -> X + 1 end.".
file:script/1 almost does what you want - it evaluates a series of erlang expressions from a file and returns the last result. You could use it in place of file:consult/1 but you'd need to change the format of the file from "term. term. term." giving [term, term ,term] to "[term, term , term]." giving [term, term, term] - place a single expression in the file instead of a sequence.
I'd like to point out that Zed's answer creates an interpreted fun. When the fun is called it enters the evaluator which starts to evaluates the abstract syntax tree returned by erl_parse:parse_exprs/1 that it has captured. Looking at the fun created:
11> erlang:fun_info(Fun, env).
{env,[[],none,none,
[{clause,1,
[{var,1,'X'}],
[],
[{op,1,'+',{var,1,'X'},{integer,1,1}}]}]]}
12> erlang:fun_info(Fun, module).
{module,erl_eval}
One can see that it has closed over the parsed abstract syntax tree as seen in the env info, and it is a fun created inside erlang_eval as seen in the module info.
It is possible to use the erlang compiler to create a compiled module at runtime, and a pointer toward that is compile:forms/2 and code:load_binary/3. But the details of that should probably go into another stackoverflow question.
Maybe by using the erl_eval module?
2> F =fun(Str,Binding) ->
{ok,Ts,_} = erl_scan:string(Str),
Ts1 = case lists:reverse(Ts) of
[{dot,_}|_] -> Ts;
TsR -> lists:reverse([{dot,1} | TsR])
end,
{ok,Expr} = erl_parse:parse_exprs(Ts1),
erl_eval:exprs(Expr, Binding) end.
#Fun<erl_eval.12.111823515>
3> F("A=23.",[]).
{value,23,[{'A',23}]}
5> F("12+B.",[{'B',23}]).
{value,35,[{'B',23}]}

Resources