~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/inets/src/tftp/tftp_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
19
19
         decode_msg/1,
20
20
         encode_msg/1,
21
21
         replace_val/3,
22
 
         to_lower/1
 
22
         to_lower/1,
 
23
         host_to_string/1
23
24
        ]).
24
25
 
25
26
%%-------------------------------------------------------------------
43
44
parse_config(Options) ->
44
45
    parse_config(Options, #config{}).
45
46
 
46
 
parse_config([{Key, Val} | Tail], Config) when record(Config, config) ->
 
47
parse_config(Options, Config) ->
 
48
    do_parse_config(Options, Config).
 
49
 
 
50
do_parse_config([{Key, Val} | Tail], Config) when record(Config, config) ->
47
51
    case Key of
48
52
        debug ->
49
53
            case Val of
50
54
                none ->
51
 
                    parse_config(Tail, Config#config{debug_level = Val});
 
55
                    do_parse_config(Tail, Config#config{debug_level = Val});
 
56
                error ->
 
57
                    do_parse_config(Tail, Config#config{debug_level = Val});
52
58
                brief ->
53
 
                    parse_config(Tail, Config#config{debug_level = Val});
 
59
                    do_parse_config(Tail, Config#config{debug_level = Val});
54
60
                normal ->
55
 
                    parse_config(Tail, Config#config{debug_level = Val});
 
61
                    do_parse_config(Tail, Config#config{debug_level = Val});
56
62
                verbose ->
57
 
                    parse_config(Tail, Config#config{debug_level = Val});
 
63
                    do_parse_config(Tail, Config#config{debug_level = Val});
58
64
                all ->
59
 
                    parse_config(Tail, Config#config{debug_level = Val});
 
65
                    do_parse_config(Tail, Config#config{debug_level = Val});
60
66
                _ ->
61
67
                    exit({badarg, {Key, Val}})
62
68
            end;
63
69
        host ->
64
70
            if
65
71
                list(Val) ->
66
 
                    parse_config(Tail, Config#config{udp_host = Val});
 
72
                    do_parse_config(Tail, Config#config{udp_host = Val});
 
73
                tuple(Val), size(Val) == 4 ->
 
74
                    do_parse_config(Tail, Config#config{udp_host = Val});
 
75
                tuple(Val), size(Val) == 8 ->
 
76
                    do_parse_config(Tail, Config#config{udp_host = Val});
67
77
                true ->
68
78
                    exit({badarg, {Key, Val}})
69
79
            end;
70
80
        port ->
71
81
            if
72
82
                integer(Val), Val >= 0 ->
73
 
                    parse_config(Tail, Config#config{udp_port = Val});
 
83
                    Config2 = Config#config{udp_port = Val, udp_options = Config#config.udp_options},
 
84
                    do_parse_config(Tail, Config2);
74
85
                true ->
75
86
                    exit({badarg, {Key, Val}})
76
87
            end;
77
88
        port_policy ->
78
89
            case Val of
79
90
                random ->
80
 
                    parse_config(Tail, Config#config{port_policy = Val});
 
91
                    do_parse_config(Tail, Config#config{port_policy = Val});
81
92
                0 ->
82
 
                    parse_config(Tail, Config#config{port_policy = random});
 
93
                    do_parse_config(Tail, Config#config{port_policy = random});
83
94
                MinMax when integer(MinMax), MinMax > 0 ->
84
 
                    parse_config(Tail, Config#config{port_policy = {range, MinMax, MinMax}});
 
95
                    do_parse_config(Tail, Config#config{port_policy = {range, MinMax, MinMax}});
85
96
                {range, Min, Max} when Max >= Min, 
86
97
                integer(Min), Min > 0,
87
98
                integer(Max), Max > 0 ->
88
 
                    parse_config(Tail, Config#config{port_policy = Val});
 
99
                    do_parse_config(Tail, Config#config{port_policy = Val});
89
100
                true ->
90
101
                    exit({badarg, {Key, Val}})
91
102
            end;
99
110
                        exit({badarg, {udp, [V]}})
100
111
                end,
101
112
            UdpOptions = lists:foldl(Fun, Config#config.udp_options, Val),
102
 
            parse_config(Tail, Config#config{udp_options = UdpOptions});
 
113
            do_parse_config(Tail, Config#config{udp_options = UdpOptions});
103
114
        use_tsize ->
104
115
            case Val of
105
116
                true ->
106
 
                    parse_config(Tail, Config#config{use_tsize = Val});
 
117
                    do_parse_config(Tail, Config#config{use_tsize = Val});
107
118
                false ->
108
 
                    parse_config(Tail, Config#config{use_tsize = Val});
 
119
                    do_parse_config(Tail, Config#config{use_tsize = Val});
109
120
                _ ->
110
121
                    exit({badarg, {Key, Val}})
111
122
            end;
112
123
        max_tsize ->
113
124
            if
114
125
                Val == infinity ->
115
 
                    parse_config(Tail, Config#config{max_tsize = Val});
 
126
                    do_parse_config(Tail, Config#config{max_tsize = Val});
116
127
                integer(Val), Val >= 0 ->
117
 
                    parse_config(Tail, Config#config{max_tsize = Val});
 
128
                    do_parse_config(Tail, Config#config{max_tsize = Val});
118
129
                true ->
119
130
                    exit({badarg, {Key, Val}})
120
131
            end;
121
132
        max_conn ->
122
133
            if
123
134
                Val == infinity ->
124
 
                    parse_config(Tail, Config#config{max_conn = Val});
 
135
                    do_parse_config(Tail, Config#config{max_conn = Val});
125
136
                integer(Val), Val > 0 ->
126
 
                    parse_config(Tail, Config#config{max_conn = Val});
 
137
                    do_parse_config(Tail, Config#config{max_conn = Val});
127
138
                true ->
128
139
                    exit({badarg, {Key, Val}})
129
140
            end;
131
142
            Key2 = to_lower(Key),
132
143
            Val2 = to_lower(Val),
133
144
            TftpOptions = replace_val(Key2, Val2, Config#config.user_options),
134
 
            parse_config(Tail, Config#config{user_options = TftpOptions});
 
145
            do_parse_config(Tail, Config#config{user_options = TftpOptions});
135
146
        reject ->
136
147
            case Val of
137
148
                read ->
138
149
                    Rejected = [Val | Config#config.rejected],
139
 
                    parse_config(Tail, Config#config{rejected = Rejected});
 
150
                    do_parse_config(Tail, Config#config{rejected = Rejected});
140
151
                write ->
141
152
                    Rejected = [Val | Config#config.rejected],
142
 
                    parse_config(Tail, Config#config{rejected = Rejected});
 
153
                    do_parse_config(Tail, Config#config{rejected = Rejected});
143
154
                _ when list(Val) ->
144
155
                    Rejected = [Val | Config#config.rejected],
145
 
                    parse_config(Tail, Config#config{rejected = Rejected});
 
156
                    do_parse_config(Tail, Config#config{rejected = Rejected});
146
157
                _ ->
147
158
                    exit({badarg, {Key, Val}})
148
159
            end;
156
167
                                                 module   = Mod,
157
168
                                                 state    = State},
158
169
                            Callbacks = Config#config.callbacks ++ [Callback],
159
 
                            parse_config(Tail, Config#config{callbacks = Callbacks});
 
170
                            do_parse_config(Tail, Config#config{callbacks = Callbacks});
160
171
                        {error, Reason} ->
161
172
                            exit({badarg, {Key, Val}, Reason})
162
173
                    end;
166
177
        _ ->
167
178
            exit({badarg, {Key, Val}})
168
179
    end;
169
 
parse_config([], Config) when record(Config, config) ->
170
 
    UdpOptions  = lists:reverse(Config#config.udp_options),
 
180
do_parse_config([], Config) when record(Config, config) ->
 
181
    UdpOptions = Config#config.udp_options,
 
182
    IsInet6 = lists:member(inet6, UdpOptions),
 
183
    IsInet  = lists:member(inet, UdpOptions),
 
184
    Host    = Config#config.udp_host,
 
185
    Host2 = 
 
186
        if
 
187
            (IsInet and not IsInet6); (not IsInet and not IsInet6) -> 
 
188
                case inet:getaddr(Host, inet) of
 
189
                    {ok, Addr} ->
 
190
                        Addr;
 
191
                    {error, Reason} ->
 
192
                        exit({badarg, {host, Reason}})
 
193
                end;
 
194
            (IsInet6 and not IsInet)  ->
 
195
                case inet:getaddr(Host, inet6) of
 
196
                    {ok, Addr} ->
 
197
                        Addr;
 
198
                    {error, Reason} ->
 
199
                        exit({badarg, {host, Reason}})
 
200
                end;
 
201
            true ->
 
202
                %% Conflicting options
 
203
                exit({badarg, {udp, [inet]}})
 
204
        end,
 
205
    UdpOptions2 = lists:reverse(UdpOptions),
171
206
    TftpOptions = lists:reverse(Config#config.user_options),
172
 
    Config#config{udp_options = UdpOptions, user_options = TftpOptions};
173
 
parse_config(Options, Config) when record(Config, config) ->
 
207
    Config#config{udp_host = Host2, udp_options = UdpOptions2, user_options = TftpOptions};
 
208
do_parse_config(Options, Config) when record(Config, config) ->
174
209
    exit({badarg, Options}).
175
210
 
 
211
host_to_string(Host) ->
 
212
    case Host of
 
213
        String when list(String) ->
 
214
            String;
 
215
        {A1, A2, A3, A4} -> % inet
 
216
            lists:concat([A1, ".", A2, ".", A3, ".",A4]);
 
217
        {A1, A2, A3, A4, A5, A6, A7, A8} -> % inet6
 
218
            lists:concat([
 
219
                          int16_to_hex(A1), "::",
 
220
                          int16_to_hex(A2), "::",
 
221
                          int16_to_hex(A3), "::",
 
222
                          int16_to_hex(A4), "::",
 
223
                          int16_to_hex(A5), "::",
 
224
                          int16_to_hex(A6), "::",
 
225
                          int16_to_hex(A7), "::",
 
226
                          int16_to_hex(A8)
 
227
                         ])
 
228
    end.
 
229
 
 
230
int16_to_hex(0) ->
 
231
    [$0];
 
232
int16_to_hex(I) ->
 
233
    N1 = ((I bsr 8) band 16#ff),
 
234
    N2 = (I band 16#ff),
 
235
    [code_character(N1 div 16), code_character(N1 rem 16),
 
236
     code_character(N2 div 16), code_character(N2 rem 16)].
 
237
 
 
238
code_character(N) when N < 10 ->
 
239
    $0 + N;
 
240
code_character(N) ->
 
241
    $A + (N - 10).
 
242
 
176
243
%%-------------------------------------------------------------------
177
244
%% Decode
178
245
%%-------------------------------------------------------------------