~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to system/doc/efficiency_guide/efficiency_guide.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-module(efficiency_guide).
 
2
-compile(export_all).
 
3
 
 
4
%% DO NOT
 
5
naive_reverse([H|T]) ->
 
6
    naive_reverse(T)++[H];
 
7
naive_reverse([]) ->
 
8
    [].
 
9
 
 
10
%% OK
 
11
naive_but_ok_reverse([H|T], Acc) ->
 
12
    naive_but_ok_reverse(T, [H]++Acc);
 
13
naive_but_ok_reverse([], Acc) ->
 
14
    Acc.
 
15
 
 
16
%% DO
 
17
vanilla_reverse([H|T], Acc) ->
 
18
    vanilla_reverse(T, [H|Acc]);
 
19
vanilla_reverse([], Acc) ->
 
20
    Acc.
 
21
    
 
22
    
 
23
multiple_setelement(T0) ->
 
24
    T1 = setelement(9, T0, bar),
 
25
    T2 = setelement(7, T1, foobar),
 
26
    setelement(5, T2, new_value).
 
27
 
 
28
 
 
29
my_list_to_binary(List) ->
 
30
    my_list_to_binary(List, <<>>).
 
31
 
 
32
my_list_to_binary([H|T], Acc) ->
 
33
    my_list_to_binary(T, <<Acc/binary,H>>);
 
34
my_list_to_binary([], Acc) ->
 
35
    Acc.
 
36
 
 
37
my_old_list_to_binary(List) ->
 
38
    my_old_list_to_binary(List, []).
 
39
 
 
40
my_old_list_to_binary([H|T], Acc) ->
 
41
    my_old_list_to_binary(T, [Acc,H]);
 
42
my_old_list_to_binary([], Acc) ->
 
43
    list_to_binary(Acc).
 
44
 
 
45
my_binary_to_list(<<H,T/binary>>) ->
 
46
    [H|my_binary_to_list(T)];
 
47
my_binary_to_list(<<>>) -> [].
 
48
 
 
49
my_complicated_binary_to_list(Bin) ->
 
50
    my_complicated_binary_to_list(Bin, 0).
 
51
 
 
52
my_complicated_binary_to_list(Bin, Skip) ->
 
53
    case Bin of
 
54
        <<_:Skip/binary,Byte,_/binary>> ->
 
55
            [Byte|my_complicated_binary_to_list(Bin, Skip+1)];
 
56
        <<_:Skip/binary>> ->
 
57
            []
 
58
    end.
 
59
 
 
60
after_zero(<<0,T/binary>>) ->
 
61
    T;
 
62
after_zero(<<_,T/binary>>) ->
 
63
    after_zero(T);
 
64
after_zero(<<>>) ->
 
65
    <<>>.
 
66
 
 
67
all_but_zeroes_to_list(Buffer, Acc, 0) ->
 
68
    {lists:reverse(Acc),Buffer};
 
69
all_but_zeroes_to_list(<<0,T/binary>>, Acc, Remaining) ->
 
70
    all_but_zeroes_to_list(T, Acc, Remaining-1);
 
71
all_but_zeroes_to_list(<<Byte,T/binary>>, Acc, Remaining) ->
 
72
    all_but_zeroes_to_list(T, [Byte|Acc], Remaining-1).
 
73
 
 
74
non_opt_eq([H|T1], <<H,T2/binary>>) ->
 
75
    non_opt_eq(T1, T2);
 
76
non_opt_eq([_|_], <<_,_/binary>>) ->
 
77
    false;
 
78
non_opt_eq([], <<>>) ->
 
79
    true.
 
80
 
 
81
opt_eq(<<H,T1/binary>>, [H|T2]) ->
 
82
    opt_eq(T1, T2);
 
83
opt_eq(<<_,_/binary>>, [_|_]) ->
 
84
    false;
 
85
opt_eq(<<>>, []) ->
 
86
    true.
 
87
 
 
88
match_head(List, <<_:10,Data/binary>>) ->
 
89
    match_body(List, Data).
 
90
 
 
91
match_body([0|_], <<H,_/binary>>) ->
 
92
    done;
 
93
match_body([H|T1], <<H,T2/binary>>) ->
 
94
    {T1,T2}.
 
95
 
 
96
count1(<<_,T/binary>>, Count) -> count1(T, Count+1);
 
97
count1(<<>>, Count) -> Count.
 
98
 
 
99
count2(<<H,T/binary>>, Count) -> count2(T, Count+1);
 
100
count2(<<>>, Count) -> Count.
 
101
 
 
102
count3(<<_H,T/binary>>, Count) -> count3(T, Count+1);
 
103
count3(<<>>, Count) -> Count.
 
104
 
 
105
fib(N) ->
 
106
    fib(N, 0, 1, []).
 
107
 
 
108
fib(0, _Current, _Next, Fibs) ->
 
109
    lists:reverse(Fibs);
 
110
fib(N, Current, Next, Fibs) -> 
 
111
    fib(N - 1, Next, Current + Next, [Current|Fibs]).
 
112
 
 
113
recursive_fib(N) ->
 
114
    recursive_fib(N, 0, 1).
 
115
 
 
116
recursive_fib(0, _Current, _Next) ->
 
117
    [];
 
118
recursive_fib(N, Current, Next) -> 
 
119
    [Current|recursive_fib(N - 1, Next, Current + Next)].
 
120
 
 
121
bad_fib(N) ->
 
122
    bad_fib(N, 0, 1, []).
 
123
 
 
124
bad_fib(0, _Current, _Next, Fibs) ->
 
125
    Fibs;
 
126
bad_fib(N, Current, Next, Fibs) -> 
 
127
    bad_fib(N - 1, Next, Current + Next, Fibs ++ [Current]).
 
128
 
 
129
tail_recursive_fib(N) ->
 
130
    tail_recursive_fib(N, 0, 1, []).
 
131
 
 
132
tail_recursive_fib(0, _Current, _Next, Fibs) ->
 
133
    lists:reverse(Fibs);
 
134
tail_recursive_fib(N, Current, Next, Fibs) -> 
 
135
    tail_recursive_fib(N - 1, Next, Current + Next, [Current|Fibs]).
 
136
 
 
137
append([H|T], Tail) ->
 
138
    [H|append(T, Tail)];
 
139
append([], Tail) ->
 
140
    Tail.
 
141
 
 
142
kilo_byte() ->
 
143
    kilo_byte(10, [42]).
 
144
 
 
145
kilo_byte(0, Acc) ->
 
146
    Acc;
 
147
kilo_byte(N, Acc) ->
 
148
    kilo_byte(N-1, [Acc|Acc]).
 
149
    
 
150
recursive_sum([H|T]) ->
 
151
    H+recursive_sum(T);
 
152
recursive_sum([]) -> 0.
 
153
 
 
154
sum(L)          -> sum(L, 0).
 
155
 
 
156
sum([H|T], Sum) -> sum(T, Sum + H);
 
157
sum([], Sum)    -> Sum.
 
158
 
 
159
days_in_month(M) ->
 
160
    element(M, {31,28,31,30,31,30,31,31,30,31,30,31}).
 
161
    
 
162
atom_map1(one) -> 1;
 
163
atom_map1(two) -> 2;
 
164
atom_map1(three) -> 3;
 
165
atom_map1(Int) when is_integer(Int) -> Int;
 
166
atom_map1(four) -> 4;
 
167
atom_map1(five) -> 5;
 
168
atom_map1(six) -> 6.
 
169
 
 
170
atom_map2(one) -> 1;
 
171
atom_map2(two) -> 2;
 
172
atom_map2(three) -> 3;
 
173
atom_map2(four) -> 4;
 
174
atom_map2(five) -> 5;
 
175
atom_map2(six) -> 6;
 
176
atom_map2(Int) when is_integer(Int) -> Int.
 
177
 
 
178
atom_map3(Int) when is_integer(Int) -> Int;
 
179
atom_map3(one) -> 1;
 
180
atom_map3(two) -> 2;
 
181
atom_map3(three) -> 3;
 
182
atom_map3(four) -> 4;
 
183
atom_map3(five) -> 5;
 
184
atom_map3(six) -> 6.
 
185
    
 
186
    
 
187
map_pairs1(_Map, [], Ys) ->
 
188
    Ys;
 
189
map_pairs1(_Map, Xs, [] ) ->
 
190
    Xs;
 
191
map_pairs1(Map, [X|Xs], [Y|Ys]) ->
 
192
    [Map(X, Y)|map_pairs1(Map, Xs, Ys)].
 
193
 
 
194
map_pairs2(_Map, [], Ys) ->
 
195
    Ys;
 
196
map_pairs2(_Map, [_|_]=Xs, [] ) ->
 
197
    Xs;
 
198
map_pairs2(Map, [X|Xs], [Y|Ys]) ->
 
199
    [Map(X, Y)|map_pairs2(Map, Xs, Ys)].
 
200
 
 
201
explicit_map_pairs(Map, Xs0, Ys0) ->
 
202
    case Xs0 of
 
203
        [X|Xs] ->
 
204
            case Ys0 of
 
205
                [Y|Ys] ->
 
206
                    [Map(X, Y)|explicit_map_pairs(Map, Xs, Ys)];
 
207
                [] ->
 
208
                    Xs0
 
209
            end;
 
210
        [] ->
 
211
            Ys0
 
212
    end.
 
213
                            
 
214