Archive

Archive for the ‘Erlang探索’ Category

节点间通讯的通道微调

September 23rd, 2009 10 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: 节点间通讯的通道微调

erlang节点间通讯是可以配置的,默认的是inet_tcp 。当2个节点要沟通的时候,net_kernel模块会负责建立必要的连接。 inet_tcp会调用底层的gen_tcp进行数据发送接受。 rpc或者节点间的消息交互都是通过这个port出去的。

在分布节点间,有时候会有大量的消息流动,那么所有的消息都是通过这个port出去 进来,所以这个port的性能极大的影响了节点间通讯的效率。那么有时候, 我们会想微调这个port的参数,根据业务的特点实现效率最大化,但是port如何得到呢?

node_port(Node)->
    {_, Owner}=lists:keyfind(owner, 1, element(2, net_kernel:node_info(Node))),
    hd([P|| P<-erlang:ports(), erlang:port_info(P, connected) == {connected,Owner}])

有了Port, 那么我们就可以设置tcp port的水位线,buffer等等。

inet:setopts(node_port('xx@nd-desktop'), [{high_watermark, 131072}]).

另外要注意 nodeup nodedown可能会换了个tcp链接 要注意重新获取。

还有另外一种方法,设置所有gen_tcp的行为, 比如以下方法:

erl -kernel inet_default_connect_options '[{sndbuf, 1048576}, {high_watermark, 131072}]'

但是这个影响面非常大, 影响到正常tcp的参数了。

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: , ,

实验Erlang语法对应的opcode 让你对erlang理解更深

September 20th, 2009 2 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: 实验Erlang语法对应的opcode 让你对erlang理解更深

Erlang作为一门FP语言,和传统的语言结构一样, 有模块, 有函数, 有语句, 有判断, 有循环, 还有特别的模式匹配。 那么这些在底层是如何运作的。 我在底下给大家做个简单的实验,让大家一窥内部的细节,让大家写码的时候知道个大概。

erlang的VM作为register based的VM, 大概有400条指令.指令分为hot, normal, cold 3大类别。beam_emu.c是vm的实现,hot和cold指令在编译的时候 由脚本生成的,include到beam_emu去的。 hot是热门的操作如list, tuple操作, cold的就是比较偏的指令。

erlang的编译器支持生成汇编码, 让我们的研究成可能,具体用法是 erlc +”‘S'” m.erl
会生成m.S 这个汇编文件.

root@nd-desktop:~# cat gram.erl
-module(gram).
-export([start/1]).

start([X])->
   %% bif
    X1 = list_to_integer(atom_to_list(X)),

%% list
    W =[1,2,3],
    W1 = [4|W],

    K=[W1,9],

    %% constant fold
    A = 1 + 2,
   
  %% if
    B =
        if X1 + A > 0 -> 5;
           true -> 4
        end,

   %% case
    C =
    case B of
        {x, T} -> T;
        5 -> a1;
        3 -> a2;
        2 -> 1.0;
        other -> 2;
        true -> 3
    end,

   %% receive
    D =
    receive
        a1 ->
            2 + 1.2;
        2 -> 3;
        {tag, N}->N;
        a2 -> 5;
        _ -> ok
    after A ->
            timeout
    end,
   
    %% anon fun
    E = fun (1)-> D;
            (x)-> 2;
            (y)-> C;
            (<<"12">>)->1;
            (_) -> error
            end,

    F = E(D),

    %% fun
    G = f(B),

    io:format("~p~p~p~p~n",[F, G,W,K]),

    done.


f(1)-> 1;
f(2) ->2;
f(3) ->3;
f(4) ->4;
f(5) ->5;
f(x1) ->1;
f(x2) ->2;
f(x3) ->3;
f(x4) ->4;
f(x5) ->5;
f({x,1}) -> 1;
f({x,2}) ->2;
f({x,3}) ->3;
f({x,4}) ->4;
f({x,5}) ->5;
f(<<1:8, X:32, "xyz", F/float>>) -> {X, F};
f(_) -> err.
root@nd-desktop:~# erlc +"'S'" gram.erl
root@nd-desktop:~# cat gram.S
{module, gram}.  %% version = 0
{exports, [{module_info,0},{module_info,1},{start,1}]}.

{attributes, []}.

{labels, 45}. %%每个标签是跳转地址

%%每个指令对应这相应的opcode,在beam_emu中都可以找到。

{function, start, 1, 2}.
  {label,1}.
    {func_info,{atom,gram},{atom,start},1}.
  {label,2}.
    {test,is_nonempty_list,{f,1},[{x,0}]}.
    {get_list,{x,0},{x,1},{x,2}}.
    {test,is_nil,{f,1},[{x,2}]}. 
    {allocate_zero,2,2}.
    {move,{x,1},{x,0}}.
   %% bif调用
    {call_ext,1,{extfunc,erlang,atom_to_list,1}}.
    {call_ext,1,{extfunc,erlang,list_to_integer,1}}.
    %% 符号也是bif
   %% 3= 1 +2 const fold
    {gc_bif,'+',{f,3},1,[{x,0},{integer,3}],{x,1}}.
    %% if 语句是如此简单
    {test,is_lt,{f,3},[{integer,0},{x,1}]}.
    {move,{integer,5},{x,0}}.
    {jump,{f,4}}.
  {label,3}.
    {move,{integer,4},{x,0}}.
  {label,4}.
    {move,{x,0},{y,1}}.
   %% case语句同样是个if else的判断
   
    %% tuple是如何匹配的 效率高
    {test,is_tuple,{f,5},[{x,0}]}.
    {test,test_arity,{f,21},[{x,0},2]}.
    {get_tuple_element,{x,0},0,{x,1}}.
    {get_tuple_element,{x,0},1,{x,2}}.
    {test,is_eq_exact,{f,21},[{x,1},{atom,x}]}.
    {move,{x,2},{x,0}}.
    {jump,{f,12}}.
  {label,5}.
    {test,is_atom,{f,8},[{x,0}]}.
    %% 2分查找
    {select_val,{x,0},{f,21},{list,[{atom,true},{f,6},{atom,other},{f,7}]}}.
  {label,6}.
    {move,{integer,3},{x,0}}.
    {jump,{f,12}}.
  {label,7}.
    {move,{integer,2},{x,0}}.
    {jump,{f,12}}.
  {label,8}.
    {test,is_integer,{f,21},[{x,0}]}.
   %% 编译器会聪明的做这类事情
    {select_val,{x,0},
                {f,21},
                {list,[{integer,2},
                       {f,9},
                       {integer,3},
                       {f,10},
                       {integer,5},
                       {f,11}]}}.
  {label,9}.
    {move,{float,1.0},{x,0}}.
    {jump,{f,12}}.
  {label,10}.
    {move,{atom,a2},{x,0}}.
    {jump,{f,12}}.
  {label,11}.
    {move,{atom,a1},{x,0}}.
  {label,12}.
    {move,{x,0},{y,0}}.

%% receive语句
  {label,13}.
    {loop_rec,{f,19},{x,0}}.
    {test,is_tuple,{f,14},[{x,0}]}.
    {test,test_arity,{f,18},[{x,0},2]}.
    {get_tuple_element,{x,0},0,{x,1}}.
    {get_tuple_element,{x,0},1,{x,2}}.
    {test,is_eq_exact,{f,18},[{x,1},{atom,tag}]}.
   
    %%从消息队列移除
    remove_message.
    {move,{x,2},{x,0}}.
    {jump,{f,20}}.
  {label,14}.
    {test,is_atom,{f,17},[{x,0}]}.
    {select_val,{x,0},{f,18},{list,[{atom,a2},{f,15},{atom,a1},{f,16}]}}.
  {label,15}.
    remove_message.
    {move,{integer,5},{x,0}}.
    {jump,{f,20}}.
  {label,16}.
    remove_message.
    {move,{float,3.2},{x,0}}.
    {jump,{f,20}}.
  {label,17}.
    {test,is_eq_exact,{f,18},[{x,0},{integer,2}]}.
    remove_message.
    {move,{integer,3},{x,0}}.
    {jump,{f,20}}.
  {label,18}.
    remove_message.
    {move,{atom,ok},{x,0}}.
    {jump,{f,20}}.
  {label,19}.
    %% timeout添加到定时器
    {wait_timeout,{f,13},{integer,3}}.
    timeout.
    {move,{atom,timeout},{x,0}}.
  {label,20}.
    %% 闭包
    {move,{x,0},{x,1}}.
    {move,{y,0},{x,0}}.
    {move,{x,1},{y,0}}.
    {make_fun2,{f,39},0,133275192,2}.
    {move,{x,0},{x,1}}.
    {move,{y,0},{x,0}}.
    {trim,1,1}.
    {call_fun,1}.
    {move,{x,0},{x,1}}.
    {move,{y,0},{x,0}}.
    {move,{x,1},{y,0}}.
    {call,1,{f,23}}.
    {test_heap,4,1}.
    %% 列表操作
    {put_list,{x,0},{literal,[[1,2,3],[[4,1,2,3],9]]},{x,0}}.
    {put_list,{y,0},{x,0},{x,1}}.
    {trim,1,0}.
    {move,{literal,"~p~p~p~p~n"},{x,0}}.
    {call_ext,2,{extfunc,io,format,2}}.
    {move,{atom,done},{x,0}}.
    {deallocate,0}.
    return.
  {label,21}.
    {case_end,{x,0}}.


{function, f, 1, 23}.
  {label,22}.
    {func_info,{atom,gram},{atom,f},1}.
  {label,23}.
    {test,bs_start_match2,{f,24},1,[{x,0},0],{x,0}}.
    {test,bs_match_string,{f,33},[{x,0},8,{string,[1]}]}.
    {test,bs_get_integer2,
          {f,33},
          1,
          [{x,0},
           {integer,32},
           1,
           {field_flags,[{anno,[78,{file,"./gram.erl"}]},unsigned,big]}],
          {x,1}}.
    {test,bs_match_string,{f,33},[{x,0},24,{string,"xyz"}]}.
    {test,bs_get_float2,
          {f,33},
          2,
          [{x,0},
           {integer,64},
           1,
           {field_flags,[{anno,[78,{file,"./gram.erl"}]},unsigned,big]}],
          {x,2}}.
    {test,bs_test_tail2,{f,33},[{x,0},0]}.
    {test_heap,3,3}.
    {put_tuple,2,{x,0}}.
    {put,{x,1}}.
    {put,{x,2}}.
    return.
  {label,24}.
    {test,is_tuple,{f,25},[{x,0}]}.
    {test,test_arity,{f,33},[{x,0},2]}.
    {get_tuple_element,{x,0},0,{x,1}}.
    {get_tuple_element,{x,0},1,{x,2}}.
    {test,is_eq_exact,{f,33},[{x,1},{atom,x}]}.
    {test,is_integer,{f,33},[{x,2}]}.
    {select_val,{x,2},
                {f,33},
                {list,[{integer,5},
                       {f,26},
                       {integer,4},
                       {f,27},
                       {integer,3},
                       {f,28},
                       {integer,2},
                       {f,29},
                       {integer,1},
                       {f,30}]}}.
  {label,25}.
    {test,is_atom,{f,31},[{x,0}]}.
    {select_val,{x,0},
                {f,33},
                {list,[{atom,x5},
                       {f,26},
                       {atom,x4},
                       {f,27},
                       {atom,x3},
                       {f,28},
                       {atom,x2},
                       {f,29},
                       {atom,x1},
                       {f,30}]}}.
  {label,26}.
    {move,{integer,5},{x,0}}.
    return.
  {label,27}.
    {move,{integer,4},{x,0}}.
    return.
  {label,28}.
    {move,{integer,3},{x,0}}.
    return.
  {label,29}.
    {move,{integer,2},{x,0}}.
    return.
  {label,30}.
    {move,{integer,1},{x,0}}.
    return.
  {label,31}.
    {test,is_integer,{f,33},[{x,0}]}.
    {select_val,{x,0},
                {f,33},
                {list,[{integer,5},
                       {f,32},
                       {integer,4},
                       {f,32},
                       {integer,3},
                       {f,32},
                       {integer,2},
                       {f,32},
                       {integer,1},
                       {f,32}]}}.
  {label,32}.
    return.
  {label,33}.
    {move,{atom,err},{x,0}}.
    return.

%%这2个函数是complier要硬性加上去的

{function, module_info, 0, 35}.
  {label,34}.
    {func_info,{atom,gram},{atom,module_info},0}.
  {label,35}.
    {move,{atom,gram},{x,0}}.
    {call_ext_only,1,{extfunc,erlang,get_module_info,1}}.


{function, module_info, 1, 37}.
  {label,36}.
    {func_info,{atom,gram},{atom,module_info},1}.
  {label,37}.
    {move,{x,0},{x,1}}.
    {move,{atom,gram},{x,0}}.
    {call_ext_only,2,{extfunc,erlang,get_module_info,2}}.

%%匿名函数的命名
{function, '-start/1-fun-0-', 3, 39}.
  {label,38}.
    {func_info,{atom,gram},{atom,'-start/1-fun-0-'},3}.
  {label,39}.
    {test,bs_start_match2,{f,40},3,[{x,0},0],{x,0}}.
    {test,bs_match_string,{f,44},[{x,0},16,{string,"12"}]}.
    {test,bs_test_tail2,{f,44},[{x,0},0]}.
    %% bitstring的代码很优化。
    {move,{integer,1},{x,0}}.
    return.
  {label,40}.
    {test,is_atom,{f,43},[{x,0}]}.
    {select_val,{x,0},{f,44},{list,[{atom,y},{f,41},{atom,x},{f,42}]}}.
   %% 一类的数据放在一起 用二分查找匹配
  {label,41}.
    {move,{x,1},{x,0}}.
    return.
  {label,42}.
    {move,{integer,2},{x,0}}.
    return.
  {label,43}.
    {test,is_eq_exact,{f,44},[{x,0},{integer,1}]}.
    {move,{x,2},{x,0}}.
    return.
  {label,44}.
    {move,{atom,error},{x,0}}.
    return.

所以无论函数match, 表达式match在vm层面都是if else这样的判断。从这个角度来讲if, case这些都只是erlang的语法糖。事实上也是,这些语法都是后来添加的,取悦用户的。

函数匹配是erlang的所有事情的核心。

结论:erlang的compiler很智能,这个VM和lua的非常像, 效率也相当。

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: , ,

erlang定时器的强度测试

September 15th, 2009 3 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: erlang定时器的强度测试

erlang的定时器在做网络程序的时候几乎无所不在, 语法层面的receive after,IO操作超时,driver内部等都大量使用timer,特别是tcp 在发送接收都有个超时。 如果你有大量的tcp链接, 就意味着大量的定时器。 那么定时器的性能就是个很大的考验。erts的定时器是个timer_wheel实现, 和linux内核用的差不多,大概支持百万级别的规模。 测试如下:

并发开N个进程 每个进程里面0-10秒的随机定时,模拟tcp超时的情况。每个定时器事件的流程是这样的 进程检查消息队列 没消息 注册定时器事件 进程换出 定时器超时 进程换入 处理定时器事件。

root@nd-desktop:~/test# cat ttimer.erl 
-module(ttimer). 
-export([start/1]). 

upmap(F, L) -> 
    Parent = self(), 
    Ref = make_ref(), 
    [receive {Ref, Result} -> Result end 
     || _ <- [spawn(fun() -> Parent ! {Ref, F(X)} end) || X <- L]]. 

loop(0)-> 
    ok; 

loop(Cnt)-> 
        receive after random:uniform(10000) -> cont end, 
        loop(Cnt-1). 

start([A1, A2]) -> 
         Start= now(), 
         N= list_to_integer(atom_to_list(A1)), 
         Cnt = list_to_integer(atom_to_list(A2)), 
         io:format("spawn ~w process, loop ~w~n", [N, Cnt]), 
         upmap(fun loop/1, lists:duplicate(N, Cnt)), 
         io:format("run ~w ms~n", [round(timer:now_diff(now(), Start) /1000)]), 
         done. 
root@nd-desktop:~/test# erl -smp disable -noshell +P 9999999 -s ttimer start 500000 10 -s erlang halt 
spawn 500000 process, loop 10 
run 63201 ms 

单cpu保持在70-80%, 63秒处理了500W个定时器事件, 大概每秒8W.

root@nd-desktop:~/test# cat /proc/cpuinfo 
model name      : Pentium(R) Dual-Core  CPU      E5200  @ 2.50GHz 
bogomips        : 4987.08 

结论: 定时器处理还是比较费时间的。

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags:

高強度的port(Pipe)的性能測試

September 13th, 2009 3 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: 高強度的port(Pipe)的性能測試

在我的項目里面, 很多運算logic是由外部的程序來計算的 那么消息先透過pipe發到外部程序,外部程序讀到消息, 處理消息, 寫消息, erlang程序讀到消息, 這條鏈路很長,而且涉及到pipe讀寫,上下文切換,這個開銷是很大的.但是具體是多少呢?

我設計了個這樣的ring. 每個ring有N個環組成, 每個環開個port. 當ring收到個數字的時候 如果數字不為0, 那么把這個數字發到外部成程序,這個外部程序echo回來數字,收到echo回來的消息后,把數字減1,繼續傳遞.當數字減少到0的時候 銷毀整個ring.
/* 注意這個數字非常重要 它影響了Erlang程序3個地方 1. epoll的句柄集大小 2. MAX_PORT 以及port的表格大小 3. open_port的時候 子進程關閉的文件句柄大小*/

root@nd-desktop:~/test#ulimit -n 1024 
root@nd-desktop:~/test# cat pipe_ring.erl 
-module(pipe_ring). 

-export([start/1]). 
-export([make_relay/1, run/3]). 

make_relay(Next)-> 
    Port = open_port({spawn, "/bin/cat"}, [in, out, {line, 128}]), 
    relay_loop(Next, Port). 

relay_loop(Next, Port) -> 
    receive 
        {Port, {data, {eol, Line}}} -> 
            Next ! (list_to_integer(Line) - 1), 
            relay_loop(Next, Port); 
        K when is_integer(K) andalso K > 0 -> 
            port_command(Port, integer_to_list(K) ++ "\n"), 
            relay_loop(Next, Port); 
        K when is_integer(K) andalso K =:=0 -> 
            port_close(Port), 
            Next ! K 
end. 

build_ring(K, Current, N, F) when N > 1 -> 
    build_ring(K, spawn(?MODULE, make_relay, [Current]), N - 1, F); 

build_ring(_, Current, _, F) -> 
    F(), 
    make_relay(Current). 

run(N, K, Par) -> 
    Parent = self(), 
    Cs = [spawn(fun ()-> Parent!run1(N, K, P) end) || P<-lists:seq(1, Par)], 
    [receive _-> ok end || _<-Cs]. 
    
run1(N, K, P)-> 
    T1 = now(), 
    build_ring(K, self(), N, fun ()-> io:format("(ring~w setup time: ~ws)~n", [P, timer:now_diff(now(), T1) /1000]), self() ! K end). 

start(Args) -> 
    Args1 = [N, K, Par] = [list_to_integer(atom_to_list(X)) || X<-Args], 
    {Time, _} = timer:tc(?MODULE, run, Args1), 
    io:format("(total run (N:~w K:~w Par:~w) ~wms ~w/s)~n", [N, K, Par, round(Time/1000), round(K*Par*1000000/Time)]), 
    halt(0). 
root@nd-desktop:~/test# erl +Bd -noshell +K true -smp disable -s pipe_ring start 10 100000 8 
(ring1 setup time: 0.021s) 
(ring2 setup time: 0.02s) 
(ring3 setup time: 0.019s) 
(ring4 setup time: 0.03s) 
(ring5 setup time: 0.018s) 
(ring6 setup time: 0.031s) 
(ring7 setup time: 0.027s) 
(ring8 setup time: 0.039s) 
(total run (N:10 K:100000 Par:8) 23158ms 34546/s) 

參數的意義:
N K Par
N:ring有幾個環 每個環開一個port
K:每個環傳遞多少消息
Par: 多少ring一起跑

總的消息數是 K * Par.

我們可以看到 每秒可以處理大概 3.4W個消息 我有2個核心. 也就是說每個消息的開銷大概是 30us. 每個port的創建時間不算多, 1ms一個.

root@nd-desktop:~/test# dstat 
----total-cpu-usage---- -dsk/total- -net/total- ---paging-- ---system-- 
usr sys idl wai hiq siq| read  writ| recv  send|  in   out | int   csw 
33  18  50   0   0   1|   0     0 | 438B 2172B|   0     0 |5329    33k 
42  11  48   0   0   0|   0     0 | 212B  404B|   0     0 |5729    58k 
41  11  49   0   0   0|   0     0 | 244B 1822B|   0     0 |5540    59k 
40  11  49   0   0   0|   0     0 | 304B  404B|   0     0 |4970    60k 

注意上面的csw 達到6W每秒.

root@nd-desktop:~/test# pstree 
├─sshd─┬─sshd─┬─bash───pstree 
     │      │      └─bash───man───pager 
     │      ├─sshd───bash─┬─beam─┬─80*[cat] 
     │      │             │      └─{beam} 
     │      │             └─emacs 
     │      ├─sshd───bash───emacs 
     │      └─sshd───bash───nmon 

我們運行了80個echo程序(/bin/cat)

讀者有興趣的話可以用systemtap 詳細了解 pipe的讀寫花費,以及context_switch情況, 具體腳本可以向我索要.

root@nd-desktop:~# cat /proc/cpuinfo 
processor       : 1 
vendor_id       : GenuineIntel 
cpu family      : 6 
model           : 23 
model name      : Pentium(R) Dual-Core  CPU      E5200  @ 2.50GHz 
stepping        : 6 
cpu MHz         : 1200.000 
cache size      : 2048 KB 
physical id     : 0 
siblings        : 2 
core id         : 1 
cpu cores       : 2 
apicid          : 1 
initial apicid  : 1 
fdiv_bug        : no 
hlt_bug         : no 
f00f_bug        : no 
coma_bug        : no 
fpu             : yes 
fpu_exception   : yes 
cpuid level     : 10 
wp              : yes 
flags           : fpu vme de pse tsc msr pae mce cx8 apic sep mtrr pge mca cmov pat pse36 clflush dts acpi mmx fxsr sse sse2 ss ht tm pbe nx lm constant_tsc arch_perfmon pebs bts pni dtes64 monitor ds_cpl em 
bogomips        : 4987.44 
clflush size    : 64 
power management: 

結論是: 用port的這種架構的開銷是可以接受的.

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: , , ,

转:CPU密集型计算 erlang和C 大比拼

August 30th, 2009 Comments off

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: 转:CPU密集型计算 erlang和C 大比拼

原文地址:http://pseudelia.wordpress.com/2009/08/23/erlang-native-code-benchmark/

Normalerweise compiliert Erlang Bytecode (heißt das so in Erlang?). Das coole daran ist, dass man die beam files leicht auf anderen Rechnern benutzen kann. Aber die Geschwindigkeit von diesem Code hat mich nicht überzeugen können. Darum habe ich ausprobiert wie gut der native Code ist den Erlang baut.

Der Versuchsaufbau ist einfach: Ich habe eine simple rekursive Funktion geschrieben, die Fibonaccizahlen berechnet. Dann wir 5-mal Fibonacci von 40 berechnet und die Zeit gemessen. Das ganze mache ich mit nur einem Kern. Diesen Test mache ich insgesamt 3-mal. Einmal mit nativem Erlangcode, einmal mit nicht nativem Erlangcode und einmal mit einem in C geschriebenen Programm. Der Benchmark besteht aus drei Dateien:

cpu_intensive.erl:

-module(cpu_intensive).
-compile(export_all).

fib_test() -&gt;
 fib(40), fib(40), fib(40), fib(40), fib(40).

fib(0) -&gt; 1;
fib(1) -&gt; 1;
fib(N) -&gt; fib(N-1) + fib(N-2).

cpu_intensive.c

unsigned int fib(unsigned int n) {
 if (n == 0 || n == 1) {
 return 1;
 }
 return fib(n-1) + fib(n-2);
}

int main() {
 fib(40); fib(40); fib(40); fib(40); fib(40);
 return 0;
}

Makefile:
all: native normal c

native:
@erlc +native cpu_intensive.erl
@echo “”
@echo “Fibonacci Erlang native code”
@time erl -noshell -s cpu_intensive fib_test -s erlang halt

normal:
@erlc cpu_intensive.erl
@echo “”
@echo “Fibonacci Erlang non-native code”
@time erl -noshell -s cpu_intensive fib_test -s erlang halt

c:
@gcc -O0 -o cpu_intensive cpu_intensive.c
@echo “”
@echo “Fibonacci written in C without optimizations”
@time ./cpu_intensive
Ich habe obige drei Dateien angelegt und die Makefile ausgeführt. Das Ergebnis war bei meinem Core 2 Duo 8400

Fibonacci Erlang native code
13,99 real        13,00 user         0,95 sys

Fibonacci Erlang non-native code
116,81 real       115,46 user         1,00 sys

Fibonacci written in C without optimizations
11,14 real        11,10 user         0,00 sys

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: , ,

erlang到底能够并发发起多少系统调用

August 25th, 2009 5 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: erlang到底能够并发发起多少系统调用

为了测试下erlang的多smp能够每秒并发发起多少系统调用,这个关系到erlang作为网络程序在高并发下的评估。

首先crack下otp_src,因为erlang:now() 是调用了clock_gettime这个系统调用,但是遗憾的是这个now里面设计到很多mutex会导致不可预期的futex调用,所以需要做如下修改,
调用最廉价的getuid系统调用:

root@ubuntu:~# emacs otp_src_R13B/erts/emulator/beam/erl_bif_info.c
BIF_RETTYPE statistics_1(BIF_ALIST_1)
{
Eterm res;
Eterm* hp;

if (BIF_ARG_1 == am_context_switches) {
Eterm cs = erts_make_integer(erts_get_total_context_switches(), BIF_P);
hp = HAlloc(BIF_P, 3);
res = TUPLE2(hp, cs, SMALL_ZERO);
BIF_RET(res);
<span style="color: red;"> } else if (BIF_ARG_1 == am_ok) { /* Line 2713 */
getuid();
BIF_RET( am_ok);
</span> } else if (BIF_ARG_1 == am_garbage_collection) {
...
}

重新make下otp_src

[root@localhost ~]# cat tsmp.erl
-module(tsmp).
-export([start/1]).

loop(I, N)->;
%%   erlang:now(),
%%   os:timestamp(),
erlang:statistics(ok), %% call getuid

case N rem 100000 of
0 ->;
io:format("#~p:~p~n", [I, N]);
_->;
skip
end,

loop(I, N + 1).

start([X])->;
N = list_to_integer(atom_to_list(X)),
[spawn_opt(fun () -> loop(I, 0) end, [{scheduler, I}]) || I <-lists:seq(1, N)],
receive
stop ->;
ok
after 60000 ->;
ok
end,
init:stop().
#otp_src_R13B02/bin/erl  -sct db  -s tsmp start 8
。。。
#7:226500000
#1:228000000
#8:152600000
#5:150200000
#4:225600000
#3:222000000
#2:224000000
#6:226400000
#7:226600000
#1:228100000
#4:225700000
#8:152700000
#3:222100000

对其中一个调度器线程的trace

[root@wes263 ~]#  /usr/bin/strace  -c -p 4667
Process 4667 attached - interrupt to quit
PANIC: attached pid 4667 exited with 0
% time     seconds  usecs/call     calls    errors syscall
------ ----------- ----------- --------- --------- ----------------
99.87    0.230051           0   3979319           getuid
0.08    0.000189           0      1924           poll
0.05    0.000116           0      1924           clock_gettime
0.00    0.000000           0       147        48 futex
------ ----------- ----------- --------- --------- ----------------
100.00    0.230356               3983314        48 total

调用序列是非常的合理的

机器配置是:

[yufeng@wes263 ~]$ cat /proc/cpuinfo
processor       : 0
vendor_id       : GenuineIntel
cpu family      : 6
model           : 23
model name      : Intel(R) Xeon(R) CPU           E5450  @ 3.00GHz
stepping        : 10
cpu MHz         : 1998.000
cache size      : 6144 KB
physical id     : 0
siblings        : 4
core id         : 0
cpu cores       : 4
fpu             : yes
fpu_exception   : yes
cpuid level     : 13
wp              : yes
flags           : fpu vme de pse tsc msr pae mce cx8 apic sep mtrr pge mca cmov pat pse36 clflush dts acpi mmx fxsr sse sse2 ss ht tm syscall nx lm constant_tsc pni monitor ds_cpl vmx est tm2 cx16 xtpr lahf_lm
bogomips        : 5988.98
clflush size    : 64
cache_alignment : 64
address sizes   : 38 bits physical, 48 bits virtual
power management:

8个核心。

1分钟 erlang发起了getuid()系统调个数 ecug的8核心机器 222,100,000 × 8个核心 = 1700M 合每秒30M个系统调用

结论是:如果合理安排的话 erlang的性能是非常高的 同时可以利用到erlang的smp的巨大优势。

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: , , ,

研究Erlang 4000小时以后

August 25th, 2009 9 comments

原创文章,转载请注明: 转载自系统技术非业余研究

本文链接地址: 研究Erlang 4000小时以后

历经2年半,花了4000小时以后,对erlang的研究有了很大的进步,从原来的兴趣, 到现在的随意的crack, 调优,改进, 指导erlang程序架构的设计,中间经历了很多。

从一个有20年历史的网络程序身上我学到很多,包括高级服务器程序的架构,调度公平性,网络事件处理, 内存管理, 锁管理, SMP管理, 平台移植, 虚拟机,语言的基本构件,用户交互,调试, 诊断, 调优,工具。 也学会了使用OS提供的工具如systemtap, oprofile,内存, CPU工具来诊断,来定位问题,这个可以参考rhel的调优白皮书。

这个成熟系统带来的经验感受如同你窥视一台精密设计的机器,一环套着一环。看似小小的系统,里面凝聚着多少片论文,多少方法改进,顺着Erlang的演化历史,你也随着成长,其中的快乐是无法抗拒的,从中学到的东西绝不是一个库或者一个小程序能够带给你的。从中你会体会到一个大型系统是如何变成一个活生生的系统,实现者如何妥协,如何稳健的持续的改进。每一个Roadmap都值得期待。

感谢erlang的开发小组给我们带来这么好的东西,研究还将继续。。。

距离上次写这篇blog的时候半年又过去了,Erlang代码已经看了3遍了。。。

Post Footer automatically generated by wp-posturl plugin for wordpress.

Categories: Erlang探索 Tags: