Erlang Tips

Erlang に関する情報を,自分用メモを兼ねて作成しました. 間違い等見つけた方はブログのエントリまで連絡いただけるとうれしいです.
最終更新:2007/07/04 23:56

目次

目次を生成中です・・・

Erlangの特性

Erlangは以下のような特徴があります.
簡単に言うと,ネットワークサーバを書くのに向いています.

得意なこと
・大量の並列処理
・複数サーバでの分散処理(ただしEthernet経由で通信するので専用インターコネクトほどは速くないと思います)

苦手なこと
・純粋な計算処理(C言語の10倍程度遅いようです)
・GUIアプリケーション(WingsというErlangでかかれたGUIアプリはあるが,GUI周りの情報は少ないです)

ありそうな勘違い
・マルチコア・SMP環境にすれば,コア数に比例して性能が向上する.
 →もちろん条件によるので,必ず比例するわけではありません.
  SMPサポートは条件によってはかえって性能が低下するケースもあります.
  (spawnの処理やドライバ経由のアクセスは排他制御が入る分,遅くなります.)
・関数型なので難しい
 →他の関数型言語にあるような,副作用の話とかモナドとかそういう難しいモノはありません.
  言語の仕様自体はシンプルですし,Perlなどと比べて,ループの書き方と変数の扱いが多少違うくらいです.
・関数型なので副作用がない言語
 →見た目は関数型ですが,副作用がある関数が多数あります.
  実行は逐次的に行われて,遅延評価などはされません.
・グローバル変数が無い
 →プロセスディクショナリというものがあり,プロセスローカルのグローバル変数として使うことが出来ます.
  また,プロセスをまたがる場合は,etsという内蔵オンメモリDBが利用できます.
・書き換え可能なオブジェクトがない
 →プロセスディクショナリやetsがあるので,(表面上は)書き換え可能なオブジェクトを作ることが出来ます.
  実際に,Erlangのライブラリの中には,オブジェクト指向のメソッドのように,自身のオブジェクトを更新していく仕様のものもあります.(digraph)
・プロセス間でのデータ共有がない
 →ets・detsなど,プロセス間でデータを共有するための方法がいくつかあります.
  プロセス間で排他制御をすることも可能です.(global:transなど)
・ネイティブコンパイラ(HiPE)があるから速い
 →おそらく期待するほどは速くなりません.
  動的な型を採用した宿命です.JavaやCよりは遅いです.
  The Computer Language Benchmarks Gameベンチマーク比較が参考になります.

エラー時に行番号を表示させる

Erlangは,通常エラーが起きたときにスタックトレースを出してくれるのだけど,行番号の情報が含まれません.
少し長めの関数を書いていたりすると,関数の中のどこでエラーが出たのかなかなかわからないことがあります.

以下の方法でエラーが発生した行番号を表示させることが出来ます.

ErlangのFAQにも書いてある内容です.
5.19. ...find out which line my Erlang program crashed at?

インストール

コンパイル済みのを http://pepper.sherry.jp/mikage/smart_exceptions.tar.gz に置いておいてありますので,ダウンロードした後,Erlangのライブラリディレクトリ以下に解凍します.

ライブラリディレクトリは,
$ erl -noshell -eval 'io:format("~p~n", [code:lib_dir()]),halt().'
"/usr/local/lib/erlang/lib"
のようにして調べられます.

上記の場合,/usr/local/lib/erlang/lib で smart_exceptions.tar.gz を解凍してください.

自前でコンパイルする場合は, smart_exceptionsからソースをダウンロード.
ディレクトリ構造はそのままダウンロードしてきます.
src/smart_exceptions.erl の中に,以下のような部分があるので,-define の行だけコメントを外します.

%% define r10 means 'try' is used in the generated code rather
%% than 'catch'. Note that try is _handled_ by default.
%% -define(r10, true).

この修正を忘れると,throw文が正常に機能しなくなります.
修正後,srcの中のファイルをコンパイルしてebinの中に入れます..
(Makefile自体はjungerlのサポートファイルが必要なので手作業でコンパイルした方が早いと思います. jungerl自体に,正常にコンパイルできないコードが多く含まれるようですので)
その後,smart_exceptions を先ほどのライブラリディレクトリの場所に置けばOKです.

使い方

次のように使用します.

erlc +'{parse_transform, smart_exceptions}' test.erl
のようにオプションをつけてコンパイルします.

あとは普通に実行すれば,
1> test:test().
** exited: {{test,test,0},{line,10},match,[5]} **
というようにエラーが表示されます.

ただし,すべての場合に表示されるわけではなく,エラーによっては行番号が表示されないことがあるようです.
作者によると十分なテストはされてないということなので,例外関係で動作が変と感じたら一度使用をやめてみて確認した方が良いようです.

メモリの消費量

Erlangのメモリ消費量で知っていた方が良いポイントがあります.

・文字列は,1文字あたり32bit環境で8バイト,64bit環境では16バイトも消費します.
 これを節約するためには,文字列ではなく,バイナリとして保存します.
 バイナリのメモリ消費量は,32bit環境で12~24バイト+文字数,64bit環境では24~48バイト+文字数です.
 さらに,可能であれば同じ文字列のデータ部分は共有されます.
 文字列とバイナリは,list_to_binary,binary_to_list で相互に変換できます.

詳細なメモリ消費量は以下のURLを参考にしてください.
Efficiency Guide の Advancedに詳細が書いてあります.
※MLの投稿によると,64bit環境では Integer で32bitより大きい範囲まで 1 word で表現できるようです.(マニュアルの内容が古い?)

正規表現を使う

Erlangには,regexpモジュールがありますが,マッチしか行えず,速度も遅いものです.
そのほかにもいくつかの正規表現モジュールがjungerlにあり, 正規表現ライブラリの鬼車を利用するoregexpもあります.
また,perlreを使うことで,Perlの正規表現をそのまま利用できます.

perlre
 わたしの環境ではもっとも高速.
 Perlの正規表現は速度も機能も最強なので,このモジュールがおすすめです.  UTF-8 の文字列マッチも利用できます.
 おまけとして(?),任意のperlコードを実行できるperlevalモジュールも付いてきます.
 perlre-docsにドキュメントがあります.
oregexp
 わたしの環境でperlreの次に速いです.
 鬼車という正規表現ライブラリを使用しています.(Rubyで利用されています.)
 普段Rubyを利用されている方はこちらの方がいいかもしれません.
 oregexpパッケージだけでは,make test に失敗しますが,気にせずインストールすれば動くと思います.

そのほかはすべてErlangで書かれたものと思いますが,Erlangで書かれたものは速度が出ないようです. perlreやoregexpとは1桁以上違う速度となります.
ただし,perlreやoregexpなどは,正規表現の処理が同時に1つしか実行されません. このため,マルチコアやSMPの恩恵を受けることは出来ないので,その点には注意する必要があります.

perlre の Tips

スケジューラスレッドと async thread pool

Erlang には,2種類のスレッドが存在します.

スケジューラスレッドは,Erlang のコード自体を実行するスレッドで,SMPオプションをつけたときだけ,2つ以上起動します. SMPオプションを使用したときのデフォルト値は,CPUのコア数になります. それ以外の場合は,1つだけ起動します.

async thread pool は,スケジューラスレッドとは別に起動するスレッドで,SMPオプションの有無にかかわらず使用することが出来ます. ファイル操作など時間がかかる可能性がある処理を async thread pool で実行することで,スケジューラスレッドが Erlang コードの実行に専念できるようにします. こちらのデフォルト値は 0 です.
つまり,デフォルトでは時間がかかる可能性がある処理もスケジューラスレッドが処理し,応答があるまで Erlang コードの実行は止まります.

これらのオプションは,erl 起動時に,-smp,+S,+A オプションで指定することが出来ます.

-smp
SMPモードで起動します.-smpをつけると,+S オプションが使用できるようになります.
+S [スケジューラスレッド数]
スケジューラスレッドの数を指定します.デフォルトは CPU のコア数になります.
スケジューラスレッドを増やすと,Erlang コードが並列で動作するようになりますが, ドライバを利用したものに関しては同時に実行されないので注意が必要です.
(openssl を利用する crypto モジュールや,perlre,oregexp モジュールなどがドライバを利用しています.)
+A [async thread pool数]
async thread pool 数を指定します.
いくつかの時間がかかる処理が,async thread pool の方で実行されるようになります.
async thread pool で実行される処理に何があるのかの一覧は無いようですが, fileモジュールによるファイルアクセスなどが,async thread pool で実行されるようです.
R11B-4 のリリースでは,Linux での +A オプションの実装にバグがあるので,
[erlang-bugs] +A option causes segmentation fault on Linux
にあるパッチを適用する必要があります.


次のような file:sync を使ったコードで,実際の効果を測定してみました.
-module(writetest).
-compile(export_all).

-define(DIR, "/tmp/"). % /で終わること
-define(PARALLEL, 50).
-define(COUNT, 50).

test() ->
        test(?PARALLEL, ?COUNT),
        wait(?PARALLEL).

test(Parallel, _Count) when Parallel == 0 ->
        ok;
test(Parallel, Count) ->
        spawn(?MODULE, write_process, [self(), Parallel, Count]),
        test(Parallel - 1, Count).

wait(Parallel) when Parallel == 0 ->
        ok;
wait(Parallel) ->
        receive
                Any -> Any
        end,
        wait(Parallel - 1).

write_process(Parent, _Parallel, Count) when Count == 0 ->
        Parent ! ok;
write_process(Parent, Parallel, Count) ->
        {ok, Fd} = file:open(?DIR ++ integer_to_list(Parallel) ++ "_" ++ integer_to_list(Count), [write, raw, binary]),
        ok = file:write(Fd, <<"test">>),
        ok = file:sync(Fd),
        ok = file:close(Fd),
        write_process(Parent, Parallel, Count - 1).

実行すると以下のようになります.
$ time erl -noshell -s writetest test -s init stop
real    0m6.409s
user    0m0.384s
sys     0m0.940s

$ time erl +A 5 -noshell -s writetest test -s init stop
real    0m2.293s
user    0m0.619s
sys     0m1.165s

$ time erl +A 50 -noshell -s writetest test -s init stop
real    0m1.920s
user    0m0.379s
sys     0m1.432s

$ time erl -smp -noshell -s writetest test -s init stop
real    0m6.162s
user    0m0.360s
sys     0m0.890s

$ time erl -smp +S 5 -noshell -s writetest test -s init stop
real    0m4.949s
user    0m0.360s
sys     0m0.927s

$ time erl -smp +S 50 -noshell -s writetest test -s init stop
real    0m2.015s
user    0m0.393s
sys     0m1.456s

+A オプションを使うことで,実行時間を短縮できることがわかります.
このテストプログラムでは,同時に50プロセスがファイルを書き込んでいます. 50スレッドを起動した場合は,+A も +S も同様に処理が最大限に高速化されていることがわかります.
しかし,スレッド数が少ない場合は,+A オプションの方が効率的に高速化が行えるようです.

処理時間の計測

Erlangで,実行速度を高めるために処理速度を測定する場合,以下のような方法が利用できます.

timer:tc() を使う
目的の関数を timer:tc で呼び出します.結果はマイクロ秒で返ります.
timer:now_diff() を使う
測定開始・終了で時刻を取り,timer:now_diff で差分を計算します.結果はマイクロ秒です.
eprof を使う
プロファイルモジュールの eprof を使用します.
コードの実行時間は長くかかるようになりますが,関数単位で実行回数と処理時間の%を取得することが出来ます.
fprof を使う
プロファイルモジュールの fprof を使用します.
コードの実行時間は長くかかるようになりますが,関数単位で実行回数と処理時間,関数の呼び出し関係を把握することが出来ます.
ただし,実行後の解析処理にかなり長い時間がかかりますので,長時間実行されるようなコードの測定には適しません.

サンプルコード

-module(time).
-compile(export_all).

-define(TESTCOUNT, 10000).

timertc() ->
        Ret = timer:tc(?MODULE, testcode, [?TESTCOUNT]),
        io:format("~p~n", [Ret]).

timerdiff() ->
        Start = erlang:now(),
        testcode(?TESTCOUNT),
        End = erlang:now(),
        io:format("~p~n", [timer:now_diff(End, Start)]).

eprof() ->
        eprof:start(),
        io:format("eprof run testcode~n"),
        eprof:profile([], ?MODULE, testcode, [?TESTCOUNT]),
        io:format("eprof run testcode done.~n"),
        eprof:analyse(),
        eprof:stop(),
        io:format("eprof end.~n").

fprof() ->
        fprof:start(),
        io:format("fprof run testcode~n"),
        fprof:apply(?MODULE, testcode, [?TESTCOUNT]),
        io:format("fprof run testcode done.~n"),
        fprof:profile(),
        fprof:analyse(),
        fprof:stop(),
        io:format("fprof end.~n").


testcode(0) ->
        ok;
testcode(N) ->
        _Val = calendar:datetime_to_gregorian_seconds(calendar:now_to_local_time(erlang:now())),
        testcode(N - 1).

実行結果

timertc() の結果
{205005,ok}
timerdiff() の結果
220786
eprof() の結果
eprof run testcode
eprof: Starting profiling.....
eprof: Stop profiling
eprof run testcode done.
FUNCTION                                       CALLS      TIME

****** Process <0.34.0>    -- 100 % of profiled time ***
calendar:date_to_gregorian_days/3              10000      8 %
calendar:day_to_year/1                         10000      7 %
calendar:year_day_to_date/2                    10000      7 %
calendar:dty/3                                 20000      6 %
calendar:dm/1                                  10000      6 %
time:testcode/1                                10001      6 %
calendar:gregorian_seconds_to_datetime/1       10000      6 %
calendar:datetime_to_gregorian_seconds/1       10000      5 %
calendar:df/2                                  10000      5 %
calendar:seconds_to_time/1                     10000      5 %
calendar:dy/1                                  30000      5 %
calendar:gregorian_days_to_date/1              10000      5 %
calendar:now_to_local_time/1                   10000      4 %
calendar:year_day_to_date2/2                   10000      4 %
calendar:now_to_datetime/1                     10000      4 %
calendar:date_to_gregorian_days/1              10000      3 %
calendar:is_leap_year1/1                       20000      3 %
calendar:is_leap_year/1                        20000      2 %
erlang:now/0                                   10000      2 %
erlang:universaltime_to_localtime/1            10000      2 %
calendar:time_to_seconds/1                     10000      1 %
calendar:last_day_of_the_month/2               10000      1 %
calendar:last_day_of_the_month1/2              10000      1 %
calendar:now_to_universal_time/1               10000      1 %
eprof:call/4                                   1          0 %

Total time: 0.98
Measurement overhead: 0.76
eprof end.
fprof() の結果
fprof run testcode
fprof run testcode done.
Reading trace data...
..................................................
.................................................,
..................................................
.................................................,
..................................................
.................................................,
..................................................
.................................................,
..................................................
.................................................,
......
End of trace!
Processing data...
Creating output...
%% Analysis results:
{  analysis_options,
 [{callers, true},
  {sort, acc},
  {totals, false},
  {details, true}]}.

%                                               CNT       ACC       OWN
[{ totals,                                     293138, 1625.124, 1490.574}].  %%%


%                                               CNT       ACC       OWN
[{ "<0.1.0>",                                  293138,undefined, 1490.574}].   %%

{[{undefined,                                     0, 1625.124,    0.033}],
 { {fprof,apply_start_stop,4},                    0, 1625.124,    0.033},     %
 [{{time,testcode,1},                             1, 1625.091,    0.017},
  {suspend,                                       1,    0.000,    0.000}]}.

{[{{fprof,apply_start_stop,4},                    1, 1625.091,    0.017},
  {{time,testcode,1},                          10000,    0.000,  109.535}],
 { {time,testcode,1},                          10001, 1625.091,  109.552},     %
 [{{calendar,now_to_local_time,1},             10000,  848.722,   74.791},
  {{calendar,datetime_to_gregorian_seconds,1}, 10000,  616.977,   81.152},
  {{erlang,now,0},                             10000,   40.765,   38.583},
  {suspend,                                      65,    9.075,    0.000},
  {{time,testcode,1},                          10000,    0.000,  109.535}]}.

{[{{time,testcode,1},                          10000,  848.722,   74.791}],
 { {calendar,now_to_local_time,1},             10000,  848.722,   74.791},     %
 [{{calendar,now_to_universal_time,1},         10000,  722.975,   27.585},
  {{erlang,universaltime_to_localtime,1},      10000,   44.173,   40.936},
  {suspend,                                      53,    6.783,    0.000}]}.

{[{{calendar,now_to_local_time,1},             10000,  722.975,   27.585}],
 { {calendar,now_to_universal_time,1},         10000,  722.975,   27.585},     %
 [{{calendar,now_to_datetime,1},               10000,  692.367,   35.106},
  {suspend,                                      22,    3.023,    0.000}]}.

(略)

Done!
fprof end.

処理の高速化

Erlang では,大量のプロセスを使って並列処理が出来ますが,多数のリクエストを裁くためには,個々の処理が高速である必要があります.
同時1万接続で,それぞれの接続が毎秒1回ずつ処理をする場合,1リクエストあたり0.1msの時間しかありません.

Efficiency Guide をよく読む
高速化する上での基本事項が色々書いてあります.
特に,以下の点はよくチェックすると良いと思います.
なるべくBIFを使う
Erlang には,C言語で書かれたビルトイン関数(BIF)がいくつかあります.
見分けが付きにくいものもありますが,いくつかのモジュールの一部関数は BIF で提供されています.
Erlang でコードを書くより,同じ処理を BIF で実行した方が大幅に高速になります.
ソースの erts/emulator/beam/bif.tab に BIF の一覧があるので,なるべくこの関数を利用するようにしましょう.
特に lists 関数は一部関数が BIF になっており,高速化されています.
lists:member/2,lists:reverse/2,lists:keymember/3,lists:keysearch/3 の4関数です.

プロセスディクショナリ・ets・dets

Erlang には,便利に使える記憶場所として,プロセスディクショナリ,ets,dets があります.
また,ets・detsを使って実装された,Mnesiaという分散DBも利用できます. Mnesia は少し扱いにくい部分があるので,データベースとしては外部のMySQLなどを利用する方法もあります.
それぞれ以下のような特徴があります.

比較項目プロセスディクショナリetsdetsMnesia
共有範囲 プロセス内のみ 同一ノード内
またはプロセス内
同一ノード内
またはプロセス内
複数ノード間
速度 とても高速
大きなデータの入出力も速い
高速 低速 テーブルの種類によって
低速~高速
最大データサイズ 制限なし
(メモリ容量のみ)
制限なし
(メモリ容量のみ)
2GB 1フラグメント2GB
複数フラグメントに分割すれば
2GB以上可能
データの永続性 プロセス終了で消滅 ノード終了で消滅 ディスクに保持される テーブルの種類・分散状況によって異なる


利用する上で,以下の点に注意すると良いです.

静的解析によるチェック

Erlang は動的な型の言語ですが,ツールを使うことで,静的解析によるチェックを行うことが可能です. 型のチェックだけではなく,もう一歩進んだチェックを行うことが出来ます.
上手く利用することで,型エラーや,絶対に成立しない分岐などを,実行前に検出することが出来るようになります.

静的解析によるチェックを実行する dialyzer というツールと,各関数の静的解析情報をファイルに書き出す typer というツールが用意されています.

サンプルコード

以下のファイルを typetest.erl としてこの後利用します.

     1
     2  -module(typetest).
     3  -export([no_return/0, integertest/0, casetest/0, casetest2/0,
     4          returnnum1/0, returnnum2/0, exception/0, record/0, record2/0]).
     5
     6  no_return() ->                 % Function no_return/0 has no local return
     7          no_return().
     8
     9  integertest() ->               % Function integertest/0 has no local return
    10          Integer = random:uniform(100),
    11          want_integer(Integer),
    12          Float = random:uniform(),
    13          want_integer(Float).   % The call typetest:want_integer(Float::float()) will fail
    14                                 %   since the signature is typetest:want_integer/1 :: ((integer()) -> 'ok')
    15  want_integer(N) when is_integer(N) ->
    16          ok.
    17
    18  casetest() ->
    19          OkNg = get_okng(),
    20          case OkNg of
    21                  ok -> ok;
    22                  ng -> ng;
    23                  other -> other % The pattern 'other' can never match since previous clauses
    24          end.                   %   completely covered the type 'ng' | 'ok'
    25
    26  get_okng() ->
    27          case random:uniform(2) of
    28                  1 -> ok;
    29                  2 -> ng
    30          end.
    31
    32  casetest2() ->
    33          Number = get_12(),
    34          case Number of
    35                  1 -> ok;
    36                  2 -> ng;
    37                  3 -> other     % The pattern 3 can never match since previous clauses completely
    38          end.                   %   covered the type 1 | 2
    39
    40  get_12() ->
    41          case random:uniform(2) of
    42                  1 -> 1;
    43                  2 -> 2
    44          end.
    45
    46  returnnum1() ->
    47          random:uniform(10).
    48
    49  returnnum2() ->
    50          N = random:uniform(10),
    51          returnnum2(N).
    52  returnnum2(N) when N > 0 ->
    53          N.
    54
    55  exception() ->                 % 例外の場合は検出が出来ないようです
    56          try
    57                  exception_okng()
    58          catch
    59                  ok -> ok;
    60                  fail -> fail   % ここは絶対に実行されない
    61          end.
    62
    63  exception_okng() ->
    64          case random:uniform(2) of
    65                  1 -> throw(ok);
    66                  2 -> throw(ng)
    67          end.
    68
    69  record() ->                    % Function record/0 has no local return
    70          {A, B} = get_record(),
    71          want_integer(A),
    72          want_integer(B).       % The call typetest:want_integer(B::'ok') will fail since
    73                                 %   the signature is typetest:want_integer/1 :: ((integer()) -> 'ok')
    74  get_record() ->
    75          {123, ok}.
    76
    77  record2() ->                   % このくらい複雑な場合も検出できないようです
    78          {Type, Result} = get_record2(),
    79          case Type of
    80                  success ->
    81                          want_integer(Result);
    82                  fail ->
    83                          want_integer(Result) % ここは必ずエラー
    84          end.
    85
    86  get_record2() ->
    87          case random:uniform(2) of
    88                  1 -> {success, 123};
    89                  2 -> {fail, ng}
    90          end.
    91

dialyzerの使い方

erlファイルに対して,以下のように利用します.

dialyzer --succ_typings -c typetest.erl

--succ_typings を指定すると,強力な静的解析が行われます.
サンプルソースでは以下のような結果が出ます.

$ dialyzer --succ_typings -c typetest.erl
  Checking whether the initial PLT exists and is up-to-date... yes
  Proceeding with analysis...
typetest.erl:6: Function no_return/0 has no local return
typetest.erl:9: Function integertest/0 has no local return
typetest.erl:13: The call typetest:want_integer(Float::float()) will fail since the signature is typetest:want_integer/1 :: ((integer()) -> 'ok')
typetest.erl:23: The pattern 'other' can never match since previous clauses completely covered the type 'ng' | 'ok'
typetest.erl:37: The pattern 3 can never match since previous clauses completely covered the type 1 | 2
typetest.erl:69: Function record/0 has no local return
typetest.erl:72: The call typetest:want_integer(B::'ok') will fail since the signature is typetest:want_integer/1 :: ((integer()) -> 'ok')
done (warnings were emitted)

--succ_typings を指定しない場合は,以下のように検出されるエラーは少なくなります.

$ dialyzer -c typetest.erl
  Checking whether the initial PLT exists and is up-to-date... yes
  Proceeding with analysis...
typetest.erl:6: Function no_return/0 has no local return
typetest.erl:23: The pattern 'other' can never match since previous clauses completely covered the type 'ng' | 'ok'
typetest.erl:37: The pattern 3 can never match since previous clauses completely covered the type 1 | 2
done (warnings were emitted)

typerの使い方

以下のように実行すると,typer_ann ディレクトリの下にファイルが作成され,その中に解析結果が記録されます.

typer typetest.erl

サンプルの場合,以下のようになります.


-module(typetest).
-export([no_return/0, integertest/0, casetest/0, casetest2/0,
        returnnum1/0, returnnum2/0, exception/0, record/0, record2/0]).

%% @typer_spec no_return/0 :: (() -> unit())
no_return() ->
        no_return().

%% @typer_spec integertest/0 :: (() -> none())
integertest() ->
        Integer = random:uniform(100),
        want_integer(Integer),
        Float = random:uniform(),
        want_integer(Float).

%% @typer_spec want_integer/1 :: ((integer()) -> 'ok')
want_integer(N) when is_integer(N) ->
        ok.

%% @typer_spec casetest/0 :: (() -> 'ng' | 'ok')
casetest() ->
        OkNg = get_okng(),
        case OkNg of
                ok -> ok;
                ng -> ng;
                other -> other
        end.

%% @typer_spec get_okng/0 :: (() -> 'ng' | 'ok')
get_okng() ->
        case random:uniform(2) of
                1 -> ok;
                2 -> ng
        end.

%% @typer_spec casetest2/0 :: (() -> 'ng' | 'ok')
casetest2() ->
        Number = get_12(),
        case Number of
                1 -> ok;
                2 -> ng;
                3 -> other
        end.

%% @typer_spec get_12/0 :: (() -> 1 | 2)
get_12() ->
        case random:uniform(2) of
                1 -> 1;
                2 -> 2
        end.

%% @typer_spec returnnum1/0 :: (() -> integer())
returnnum1() ->
        random:uniform(10).            % uniformは正の値しか返しませんが検出できません

%% @typer_spec returnnum2/0 :: (() -> pos_integer())
returnnum2() ->
        N = random:uniform(10),
        returnnum2(N).
%% @typer_spec returnnum2/1 :: ((pos_integer()) -> pos_integer())
returnnum2(N) when N > 0 ->            % whenのガードをつけると,正の整数と認識されます
        N.

%% @typer_spec exception/0 :: (() -> 'fail' | 'ok')
exception() ->
        try
                exception_okng()
        catch
                ok -> ok;
                fail -> fail
        end.

%% @typer_spec exception_okng/0 :: (() -> none())
exception_okng() ->
        case random:uniform(2) of
                1 -> throw(ok);
                2 -> throw(ng)
        end.

%% @typer_spec record/0 :: (() -> none())
record() ->
        {A, B} = get_record(),
        want_integer(A),
        want_integer(B).

%% @typer_spec get_record/0 :: (() -> {123,'ok'})
get_record() ->
        {123, ok}.

%% @typer_spec record2/0 :: (() -> 'ok')
record2() ->
        {Type, Result} = get_record2(),
        case Type of
                success ->
                        want_integer(Result);
                fail ->
                        want_integer(Result)
        end.

%% @typer_spec get_record2/0 :: (() -> {'fail','ng'} | {'success',123})
get_record2() ->                       % 返される可能性のある構造が検出されます
        case random:uniform(2) of
                1 -> {success, 123};
                2 -> {fail, ng}
        end.

yawsの高速化

Erlangで書かれたWebサーバ,yaws は,通常の Erlang 上で動作するため,Erlang と同様にチューニングが出来ます.
以下の2点を行うことで,処理速度を数倍向上させることが出来ます.
実際にベンチマークを取得した結果が,ErlangなWebサーバyawsを速くする方法にあります.

-smpオプションを使う

yaws起動時に,以下のようにオプションを与えます.

yaws --erlarg '-smp' --daemon

+nativeコンパイルする

yaws の src/Makefile の ERLC_FLAGS の行を以下のように変更します.

ERLC_FLAGS+=-W $(DEBUG_FLAGS) -pa ../../yaws -smp +native

この修正を行ってから,make します.
上記の設定では,-smp オプションを渡しているため,「-smpオプションを使う」の対策と兼用してください.
実行時に -smp オプションを渡さない場合は,ERLC_FLAGS の行から -smp を消して,make してください.

リンク

Erlang本家サイト
Erlangの本家サイトです.落ちているときはミラーをどうぞ.
ミラー http://www.csd.uu.se/ftp/mirror/erlang/ (Uppsala University, Sweden)
ミラー www3.erlang.org (Stockholm University, Sweden [www3])
ミラー www4.erlang.org http://erlang.mirror.libertine.org/ (Libertine.org, US [www4])(←これは落ちている?)
Erlangクエックブック
Erlangのコード断片が多数紹介されているページ.
Programming Erlang
Erlang本家による入門書.PDFでの購入が安くて便利です.

更新履歴

2007/7/4
2007/6/22
2007/6/16
2007/6/15
2007/6/13
2007/6/11
2007/6/10



mikage's page.