~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/options1_tests_SUITE_data/src/compiler/core_lint.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: core_lint.erl,v 1.1 2008/12/17 09:53:42 mikpe Exp $
 
17
%%
 
18
%% Purpose : Do necessary checking of Core Erlang code.
 
19
 
 
20
%% Check Core module for errors.  Seeing this module is used in the
 
21
%% compiler after optimisations wedone more checking than would be
 
22
%% necessary after just parsing.  Don't check all constructs.
 
23
%%
 
24
%% We check the following:
 
25
%%
 
26
%% All referred functions, called and exported, are defined.
 
27
%% Format of export list.
 
28
%% Format of attributes
 
29
%% Used variables are defined.
 
30
%% Variables in let and funs.
 
31
%% Patterns case clauses.
 
32
%% Values only as multiple values/variables/patterns.
 
33
%% Return same number of values as requested
 
34
%% Correct number of arguments
 
35
%%
 
36
%% Checks to add:
 
37
%%
 
38
%% Consistency of values/variables
 
39
%% Consistency of function return values/calls.
 
40
%%
 
41
%% We keep the names defined variables and functions in a ordered list
 
42
%% of variable names and function name/arity pairs.
 
43
 
 
44
-module(core_lint).
 
45
 
 
46
 
 
47
-export([module/1,module/2,format_error/1]).
 
48
 
 
49
-import(lists, [reverse/1,all/2,foldl/3]).
 
50
-import(ordsets, [add_element/2,is_element/2,union/2]).
 
51
%-import(ordsets, [subtract/2]).
 
52
 
 
53
-include("core_parse.hrl").
 
54
 
 
55
%% Define the lint state record.
 
56
 
 
57
-record(lint, {module=[],                       %Current module
 
58
               func=[],                         %Current function
 
59
               errors=[],                       %Errors
 
60
               warnings=[]}).                   %Warnings
 
61
 
 
62
%% Keep track of defined
 
63
-record(def, {vars=[],
 
64
              funs=[]}).
 
65
 
 
66
%%-deftype retcount() -> any | unknown | int().
 
67
 
 
68
%% format_error(Error)
 
69
%%  Return a string describing the error.
 
70
 
 
71
format_error(invalid_exports) -> "invalid exports";
 
72
format_error(invalid_attributes) -> "invalid attributes";
 
73
format_error({undefined_function,{F,A}}) ->
 
74
    io_lib:format("function ~w/~w undefined", [F,A]);
 
75
format_error({undefined_function,{F1,A1},{F2,A2}}) ->
 
76
    io_lib:format("undefined function ~w/~w in ~w/~w", [F1,A1,F2,A2]);
 
77
format_error({illegal_expr,{F,A}}) ->
 
78
    io_lib:format("illegal expression in ~w/~w", [F,A]);
 
79
format_error({illegal_guard,{F,A}}) ->
 
80
    io_lib:format("illegal guard expression in ~w/~w", [F,A]);
 
81
format_error({illegal_pattern,{F,A}}) ->
 
82
    io_lib:format("illegal pattern in ~w/~w", [F,A]);
 
83
format_error({illegal_try,{F,A}}) ->
 
84
    io_lib:format("illegal try expression in ~w/~w", [F,A]);
 
85
format_error({pattern_mismatch,{F,A}}) ->
 
86
    io_lib:format("pattern count mismatch in ~w/~w", [F,A]);
 
87
format_error({return_mismatch,{F,A}}) ->
 
88
    io_lib:format("return count mismatch in ~w/~w", [F,A]);
 
89
format_error({arg_mismatch,{F,A}}) ->
 
90
    io_lib:format("argument count mismatch in ~w/~w", [F,A]);
 
91
format_error({unbound_var,N,{F,A}}) ->
 
92
    io_lib:format("unbound variable ~s in ~w/~w", [N,F,A]);
 
93
format_error({duplicate_var,N,{F,A}}) ->
 
94
    io_lib:format("duplicate variable ~s in ~w/~w", [N,F,A]);
 
95
format_error({not_var,{F,A}}) ->
 
96
    io_lib:format("expecting variable in ~w/~w", [F,A]);
 
97
format_error({not_pattern,{F,A}}) ->
 
98
    io_lib:format("expecting pattern in ~w/~w", [F,A]);
 
99
format_error({not_bs_pattern,{F,A}}) ->
 
100
    io_lib:format("expecting bit syntax pattern in ~w/~w", [F,A]).
 
101
 
 
102
%% module(CoreMod) ->
 
103
%% module(CoreMod, [CompileOption]) ->
 
104
%%      {ok,[Warning]} | {error,[Error],[Warning]}
 
105
 
 
106
module(M) -> module(M, []).
 
107
 
 
108
module(#c_module{name=M,exports=Es,attrs=As,defs=Ds}, _Opts) ->
 
109
    Defined = defined_funcs(Ds),
 
110
    St0 = #lint{module=M#c_atom.val},
 
111
    St1 = check_exports(Es, St0),
 
112
    St2 = check_attrs(As, St1),
 
113
    St3 = module_defs(Ds, Defined, St2),
 
114
    St4 = check_state(Es, Defined, St3),
 
115
    return_status(St4).
 
116
 
 
117
%% defined_funcs([FuncDef]) -> [Fname].
 
118
 
 
119
defined_funcs(Fs) ->
 
120
    foldl(fun (#c_def{name=#c_fname{id=I,arity=A}}, Def) ->
 
121
                  add_element({I,A}, Def)
 
122
          end, [], Fs).
 
123
 
 
124
%% return_status(State) ->
 
125
%%      {ok,[Warning]} | {error,[Error],[Warning]}
 
126
%%  Pack errors and warnings properly and return ok | error.
 
127
 
 
128
return_status(St) ->
 
129
    Ws = reverse(St#lint.warnings),
 
130
    case reverse(St#lint.errors) of
 
131
        [] -> {ok,[{St#lint.module,Ws}]};
 
132
        Es -> {error,[{St#lint.module,Es}],[{St#lint.module,Ws}]}
 
133
    end.
 
134
 
 
135
%% add_error(ErrorDescriptor, State) -> State'
 
136
%% add_warning(ErrorDescriptor, State) -> State'
 
137
%%  Note that we don't use line numbers here.
 
138
 
 
139
add_error(E, St) -> St#lint{errors=[{none,core_lint,E}|St#lint.errors]}.
 
140
 
 
141
%%add_warning(W, St) -> St#lint{warnings=[{none,core_lint,W}|St#lint.warnings]}.
 
142
 
 
143
check_exports(Es, St) ->
 
144
    case all(fun (#c_fname{id=Name,arity=Arity}) when
 
145
                       atom(Name), integer(Arity) -> true;
 
146
                 (_) -> false
 
147
             end, Es) of
 
148
        true -> St;
 
149
        false -> add_error(invalid_exports, St)
 
150
    end.
 
151
 
 
152
check_attrs(As, St) ->
 
153
    case all(fun (#c_def{name=#c_atom{},val=V}) -> core_lib:is_literal(V);
 
154
                 (_) -> false
 
155
             end, As) of
 
156
        true -> St;
 
157
        false -> add_error(invalid_attributes, St)
 
158
    end.
 
159
 
 
160
check_state(Es, Defined, St) ->
 
161
    foldl(fun (#c_fname{id=N,arity=A}, St1) ->
 
162
                  F = {N,A},
 
163
                  case is_element(F, Defined) of
 
164
                      true -> St1;
 
165
                      false -> add_error({undefined_function,F}, St)
 
166
                  end
 
167
          end, St, Es).
 
168
%     Undef = subtract(Es, Defined),
 
169
%     St1 = foldl(fun (F, St) -> add_error({undefined_function,F}, St) end,
 
170
%               St0, Undef),
 
171
%     St1.
 
172
 
 
173
%% module_defs(CoreBody, Defined, State) -> State.
 
174
 
 
175
module_defs(B, Def, St) ->
 
176
    %% Set top level function name.
 
177
    foldl(fun (Func, St0) ->
 
178
                  #c_fname{id=F,arity=A} = Func#c_def.name,
 
179
                  St1 = St0#lint{func={F,A}},
 
180
                  function(Func, Def, St1)
 
181
          end, St, B).
 
182
 
 
183
%% functions([Fdef], Defined, State) -> State.
 
184
 
 
185
functions(Fs, Def, St0) ->
 
186
    foldl(fun (F, St) -> function(F, Def, St) end, St0, Fs).
 
187
 
 
188
%% function(CoreFunc, Defined, State) -> State.
 
189
 
 
190
function(#c_def{name=#c_fname{},val=B}, Def, St) ->
 
191
    %% Body must be a fun!
 
192
    case B of
 
193
        #c_fun{} -> expr(B, Def, any, St);
 
194
        _ -> add_error({illegal_expr,St#lint.func}, St)
 
195
    end.
 
196
 
 
197
%% body(Expr, Defined, RetCount, State) -> State.
 
198
 
 
199
body(#c_values{es=Es}, Def, Rt, St) ->
 
200
    return_match(Rt, length(Es), expr_list(Es, Def, St));
 
201
body(E, Def, Rt, St0) ->
 
202
    St1 = expr(E, Def, Rt, St0),
 
203
    case core_lib:is_simple_top(E) of
 
204
        true -> return_match(Rt, 1, St1);
 
205
        false -> St1
 
206
    end.
 
207
 
 
208
%% guard(Expr, Defined, State) -> State.
 
209
%%  Guards are boolean expressions with test wrapped in a protected.
 
210
 
 
211
guard(Expr, Def, St) -> gexpr(Expr, Def, 1, St).
 
212
 
 
213
%% guard_list([Expr], Defined, State) -> State.
 
214
 
 
215
%% guard_list(Es, Def, St0) ->
 
216
%%     foldl(fun (E, St) -> guard(E, Def, St) end, St0, Es).
 
217
 
 
218
%% gbody(Expr, Defined, RetCount, State) -> State.
 
219
 
 
220
gbody(#c_values{es=Es}, Def, Rt, St) ->
 
221
    return_match(Rt, length(Es), gexpr_list(Es, Def, St));
 
222
gbody(E, Def, Rt, St0) ->
 
223
    St1 = gexpr(E, Def, Rt, St0),
 
224
    case core_lib:is_simple_top(E) of
 
225
        true -> return_match(Rt, 1, St1);
 
226
        false -> St1
 
227
    end.
 
228
 
 
229
gexpr(#c_var{name=N}, Def, _Rt, St) -> expr_var(N, Def, St);
 
230
gexpr(#c_int{}, _Def, _Rt, St) -> St;
 
231
gexpr(#c_float{}, _Def, _Rt, St) -> St;
 
232
gexpr(#c_atom{}, _Def, _Rt, St) -> St;
 
233
gexpr(#c_char{}, _Def, _Rt, St) -> St;
 
234
gexpr(#c_string{}, _Def, _Rt, St) -> St;
 
235
gexpr(#c_nil{}, _Def, _Rt, St) -> St;
 
236
gexpr(#c_cons{hd=H,tl=T}, Def, _Rt, St) ->
 
237
    gexpr_list([H,T], Def, St);
 
238
gexpr(#c_tuple{es=Es}, Def, _Rt, St) ->
 
239
    gexpr_list(Es, Def, St);
 
240
gexpr(#c_binary{segments=Ss}, Def, _Rt, St) ->
 
241
    gbitstr_list(Ss, Def, St);
 
242
gexpr(#c_seq{arg=Arg,body=B}, Def, Rt, St0) ->
 
243
    St1 = gexpr(Arg, Def, any, St0),            %Ignore values
 
244
    gbody(B, Def, Rt, St1);
 
245
gexpr(#c_let{vars=Vs,arg=Arg,body=B}, Def, Rt, St0) ->
 
246
    St1 = gbody(Arg, Def, let_varcount(Vs), St0), %This is a guard body
 
247
    {Lvs,St2} = variable_list(Vs, St1),
 
248
    gbody(B, union(Lvs, Def), Rt, St2);
 
249
gexpr(#c_call{module=#c_atom{val=erlang},
 
250
              name=#c_atom{},
 
251
              args=As}, Def, 1, St) ->
 
252
    gexpr_list(As, Def, St);
 
253
gexpr(#c_primop{name=N,args=As}, Def, _Rt, St0) when record(N, c_atom) ->
 
254
    gexpr_list(As, Def, St0);
 
255
gexpr(#c_try{arg=E,vars=[#c_var{name=X}],body=#c_var{name=X},
 
256
             evars=[#c_var{},#c_var{},#c_var{}],handler=#c_atom{val=false}},
 
257
      Def, Rt, St) ->
 
258
    gbody(E, Def, Rt, St);
 
259
gexpr(_, _, _, St) ->
 
260
    add_error({illegal_guard,St#lint.func}, St).
 
261
 
 
262
%% gexpr_list([Expr], Defined, State) -> State.
 
263
 
 
264
gexpr_list(Es, Def, St0) ->
 
265
    foldl(fun (E, St) -> gexpr(E, Def, 1, St) end, St0, Es).
 
266
 
 
267
%% gbitstr_list([Elem], Defined, State) -> State.
 
268
 
 
269
gbitstr_list(Es, Def, St0) ->
 
270
    foldl(fun (E, St) -> gbitstr(E, Def, St) end, St0, Es).
 
271
 
 
272
gbitstr(#c_bitstr{val=V,size=S,unit=U,type=T,flags=Fs}, Def, St0) ->
 
273
    St1 = bit_type(U, T, Fs, St0),
 
274
    gexpr_list([V,S], Def, St1).
 
275
 
 
276
%% expr(Expr, Defined, RetCount, State) -> State.
 
277
 
 
278
expr(#c_var{name=N}, Def, _Rt, St) -> expr_var(N, Def, St);
 
279
expr(#c_int{}, _Def, _Rt, St) -> St;
 
280
expr(#c_float{}, _Def, _Rt, St) -> St;
 
281
expr(#c_atom{}, _Def, _Rt, St) -> St;
 
282
expr(#c_char{}, _Def, _Rt, St) -> St;
 
283
expr(#c_string{}, _Def, _Rt, St) -> St;
 
284
expr(#c_nil{}, _Def, _Rt, St) -> St;
 
285
expr(#c_cons{hd=H,tl=T}, Def, _Rt, St) ->
 
286
    expr_list([H,T], Def, St);
 
287
expr(#c_tuple{es=Es}, Def, _Rt, St) ->
 
288
    expr_list(Es, Def, St);
 
289
expr(#c_binary{segments=Ss}, Def, _Rt, St) ->
 
290
    bitstr_list(Ss, Def, St);
 
291
expr(#c_fname{id=I,arity=A}, Def, _Rt, St) ->
 
292
    expr_fname({I,A}, Def, St);
 
293
expr(#c_fun{vars=Vs,body=B}, Def, Rt, St0) ->
 
294
    {Vvs,St1} = variable_list(Vs, St0),
 
295
    return_match(Rt, 1, body(B, union(Vvs, Def), any, St1));
 
296
expr(#c_seq{arg=Arg,body=B}, Def, Rt, St0) ->
 
297
    St1 = expr(Arg, Def, any, St0),             %Ignore values
 
298
    body(B, Def, Rt, St1);
 
299
expr(#c_let{vars=Vs,arg=Arg,body=B}, Def, Rt, St0) ->
 
300
    St1 = body(Arg, Def, let_varcount(Vs), St0), %This is a body
 
301
    {Lvs,St2} = variable_list(Vs, St1),
 
302
    body(B, union(Lvs, Def), Rt, St2);
 
303
expr(#c_letrec{defs=Fs,body=B}, Def0, Rt, St0) ->
 
304
    Def1 = union(defined_funcs(Fs), Def0),      %All defined stuff
 
305
    St1 = functions(Fs, Def1, St0),
 
306
    body(B, Def1, Rt, St1#lint{func=St0#lint.func});
 
307
expr(#c_case{arg=Arg,clauses=Cs}, Def, Rt, St0) ->
 
308
    Pc = case_patcount(Cs),
 
309
    St1 = body(Arg, Def, Pc, St0),
 
310
    clauses(Cs, Def, Pc, Rt, St1);
 
311
expr(#c_receive{clauses=Cs,timeout=T,action=A}, Def, Rt, St0) ->
 
312
    St1 = expr(T, Def, 1, St0),
 
313
    St2 = body(A, Def, Rt, St1),
 
314
    clauses(Cs, Def, 1, Rt, St2);
 
315
expr(#c_apply{op=Op,args=As}, Def, _Rt, St0) ->
 
316
    St1 = apply_op(Op, Def, length(As), St0),
 
317
    expr_list(As, Def, St1);
 
318
expr(#c_call{module=M,name=N,args=As}, Def, _Rt, St0) ->
 
319
    St1 = expr(M, Def, 1, St0),
 
320
    St2 = expr(N, Def, 1, St1),
 
321
    expr_list(As, Def, St2);
 
322
expr(#c_primop{name=N,args=As}, Def, _Rt, St0) when record(N, c_atom) ->
 
323
    expr_list(As, Def, St0);
 
324
expr(#c_catch{body=B}, Def, Rt, St) ->
 
325
    return_match(Rt, 1, body(B, Def, 1, St));
 
326
expr(#c_try{arg=A,vars=Vs,body=B,evars=Evs,handler=H}, Def, Rt, St0) ->
 
327
    St1 = case length(Evs) of
 
328
              2 -> St0;
 
329
              _ -> add_error({illegal_try,St0#lint.func}, St0)
 
330
          end,
 
331
    St2 = body(A, Def, let_varcount(Vs), St1),
 
332
    {Ns,St3} = variable_list(Vs, St2),
 
333
    St4 = body(B, union(Ns, Def), Rt, St3),
 
334
    {Ens,St5} = variable_list(Evs, St4),
 
335
    body(H, union(Ens, Def), Rt, St5);
 
336
expr(_, _, _, St) ->
 
337
    %%io:fwrite("clint: ~p~n", [Other]),
 
338
    add_error({illegal_expr,St#lint.func}, St).
 
339
 
 
340
%% expr_list([Expr], Defined, State) -> State.
 
341
 
 
342
expr_list(Es, Def, St0) ->
 
343
    foldl(fun (E, St) -> expr(E, Def, 1, St) end, St0, Es).
 
344
 
 
345
%% bitstr_list([Elem], Defined, State) -> State.
 
346
 
 
347
bitstr_list(Es, Def, St0) ->
 
348
    foldl(fun (E, St) -> bitstr(E, Def, St) end, St0, Es).
 
349
 
 
350
bitstr(#c_bitstr{val=V,size=S,unit=U,type=T,flags=Fs}, Def, St0) ->
 
351
    St1 = bit_type(U, T, Fs, St0),
 
352
    expr_list([V,S], Def, St1).
 
353
 
 
354
%% apply_op(Op, Defined, ArgCount, State) -> State.
 
355
%%  A apply op is either an fname or an expression.
 
356
 
 
357
apply_op(#c_fname{id=I,arity=A}, Def, Ac, St0) ->
 
358
    St1 = expr_fname({I,A}, Def, St0),
 
359
    arg_match(Ac, A, St1);
 
360
apply_op(E, Def, _, St) -> expr(E, Def, 1, St). %Hard to check
 
361
 
 
362
%% expr_var(VarName, Defined, State) -> State.
 
363
 
 
364
expr_var(N, Def, St) ->
 
365
    case is_element(N, Def) of
 
366
        true -> St;
 
367
        false -> add_error({unbound_var,N,St#lint.func}, St)
 
368
    end.
 
369
 
 
370
%% expr_fname(Fname, Defined, State) -> State.
 
371
 
 
372
expr_fname(Fname, Def, St) ->
 
373
    case is_element(Fname, Def) of
 
374
        true -> St;
 
375
        false -> add_error({undefined_function,Fname,St#lint.func}, St)
 
376
    end.
 
377
 
 
378
%% let_varcount([Var]) -> int().
 
379
 
 
380
let_varcount([]) -> any;                        %Ignore values
 
381
let_varcount(Es) -> length(Es).
 
382
 
 
383
%% case_patcount([Clause]) -> int().
 
384
 
 
385
case_patcount([#c_clause{pats=Ps}|_]) -> length(Ps).
 
386
 
 
387
%% clauses([Clause], Defined, PatCount, RetCount, State) -> State.
 
388
 
 
389
clauses(Cs, Def, Pc, Rt, St0) ->
 
390
    foldl(fun (C, St) -> clause(C, Def, Pc, Rt, St) end, St0, Cs).
 
391
 
 
392
%% clause(Clause, Defined, PatCount, RetCount, State) -> State.
 
393
 
 
394
clause(#c_clause{pats=Ps,guard=G,body=B}, Def0, Pc, Rt, St0) ->
 
395
    St1 = pattern_match(Pc, length(Ps), St0),
 
396
    {Pvs,St2} = pattern_list(Ps, Def0, St1),
 
397
    Def1 = union(Pvs, Def0),
 
398
    St3 = guard(G, Def1, St2),
 
399
    body(B, Def1, Rt, St3).
 
400
 
 
401
%% variable(Var, [PatVar], State) -> {[VarName],State}.
 
402
 
 
403
variable(#c_var{name=N}, Ps, St) ->
 
404
    case is_element(N, Ps) of
 
405
        true -> {[],add_error({duplicate_var,N,St#lint.func}, St)};
 
406
        false -> {[N],St}
 
407
    end;
 
408
variable(_, Def, St) -> {Def,add_error({not_var,St#lint.func}, St)}.
 
409
 
 
410
%% variable_list([Var], State) -> {[Var],State}.
 
411
%% variable_list([Var], [PatVar], State) -> {[Var],State}.
 
412
 
 
413
variable_list(Vs, St) -> variable_list(Vs, [], St).
 
414
 
 
415
variable_list(Vs, Ps, St) ->
 
416
    foldl(fun (V, {Ps0,St0}) ->
 
417
                  {Vvs,St1} = variable(V, Ps0, St0),
 
418
                  {union(Vvs, Ps0),St1}
 
419
          end, {Ps,St}, Vs).
 
420
 
 
421
%% pattern(Pattern, Defined, State) -> {[PatVar],State}.
 
422
%% pattern(Pattern, Defined, [PatVar], State) -> {[PatVar],State}.
 
423
%%  Patterns are complicated by sizes in binaries.  These are pure
 
424
%%  input variables which create no bindings.  We, therefor, need to
 
425
%%  carry around the original defined variables to get the correct
 
426
%%  handling.
 
427
 
 
428
%% pattern(P, Def, St) -> pattern(P, Def, [], St).
 
429
 
 
430
pattern(#c_var{name=N}, Def, Ps, St) ->
 
431
    pat_var(N, Def, Ps, St);
 
432
pattern(#c_int{}, _Def, Ps, St) -> {Ps,St};
 
433
pattern(#c_float{}, _Def, Ps, St) -> {Ps,St};
 
434
pattern(#c_atom{}, _Def, Ps, St) -> {Ps,St};
 
435
pattern(#c_char{}, _Def, Ps, St) -> {Ps,St};
 
436
pattern(#c_string{}, _Def, Ps, St) -> {Ps,St};
 
437
pattern(#c_nil{}, _Def, Ps, St) -> {Ps,St};
 
438
pattern(#c_cons{hd=H,tl=T}, Def, Ps, St) ->
 
439
    pattern_list([H,T], Def, Ps, St);
 
440
pattern(#c_tuple{es=Es}, Def, Ps, St) ->
 
441
    pattern_list(Es, Def, Ps, St);
 
442
pattern(#c_binary{segments=Ss}, Def, Ps, St) ->
 
443
    pat_bin(Ss, Def, Ps, St);
 
444
pattern(#c_alias{var=V,pat=P}, Def, Ps, St0) ->
 
445
    {Vvs,St1} = variable(V, Ps, St0),
 
446
    pattern(P, Def, union(Vvs, Ps), St1);
 
447
pattern(_, _, Ps, St) -> {Ps,add_error({not_pattern,St#lint.func}, St)}.
 
448
 
 
449
pat_var(N, _Def, Ps, St) ->
 
450
    case is_element(N, Ps) of
 
451
        true -> {Ps,add_error({duplicate_var,N,St#lint.func}, St)};
 
452
        false -> {add_element(N, Ps),St}
 
453
    end.
 
454
 
 
455
%% pat_bin_list([Elem], Defined, [PatVar], State) -> {[PatVar],State}.
 
456
 
 
457
pat_bin(Es, Def, Ps0, St0) ->
 
458
    foldl(fun (E, {Ps,St}) -> pat_segment(E, Def, Ps, St) end, {Ps0,St0}, Es).
 
459
 
 
460
pat_segment(#c_bitstr{val=V,size=S,unit=U,type=T,flags=Fs}, Def, Ps, St0) ->
 
461
    St1 = bit_type(U, T, Fs, St0),
 
462
    St2 = pat_bit_expr(S, T, Def, St1),
 
463
    pattern(V, Def, Ps, St2);
 
464
pat_segment(_, _, Ps, St) ->
 
465
    {Ps,add_error({not_bs_pattern,St#lint.func}, St)}.
 
466
 
 
467
%% pat_bit_expr(SizePat, Type, Defined, State) -> State.
 
468
%%  Check the Size pattern, this is an input!  Be a bit tough here.
 
469
 
 
470
pat_bit_expr(#c_int{val=I}, _, _, St) when I >= 0 -> St;
 
471
pat_bit_expr(#c_var{name=N}, _, Def, St) ->
 
472
    expr_var(N, Def, St);
 
473
pat_bit_expr(#c_atom{val=all}, binary, _Def, St) -> St;
 
474
pat_bit_expr(_, _, _, St) ->
 
475
    add_error({illegal_expr,St#lint.func}, St).
 
476
 
 
477
bit_type(Unit, Type, Flags, St) ->
 
478
    U = core_lib:literal_value(Unit),
 
479
    T = core_lib:literal_value(Type),
 
480
    Fs = core_lib:literal_value(Flags),
 
481
    case erl_bits:set_bit_type(default, [T,{unit,U}|Fs]) of
 
482
        {ok,_,_} -> St;
 
483
        {error,E} -> add_error({E,St#lint.func}, St)
 
484
    end.
 
485
 
 
486
%% pattern_list([Var], Defined, State) -> {[PatVar],State}.
 
487
%% pattern_list([Var], Defined, [PatVar], State) -> {[PatVar],State}.
 
488
 
 
489
pattern_list(Pats, Def, St) -> pattern_list(Pats, Def, [], St).
 
490
 
 
491
pattern_list(Pats, Def, Ps0, St0) ->
 
492
    foldl(fun (P, {Ps,St}) -> pattern(P, Def, Ps, St) end, {Ps0,St0}, Pats).
 
493
 
 
494
%% pattern_match(Required, Supplied, State) -> State.
 
495
%%  Check that the required number of patterns match the supplied.
 
496
 
 
497
pattern_match(N, N, St) -> St;
 
498
pattern_match(_Req, _Sup, St) ->
 
499
    add_error({pattern_mismatch,St#lint.func}, St).
 
500
 
 
501
%% return_match(Required, Supplied, State) -> State.
 
502
%%  Check that the required number of return values match the supplied.
 
503
 
 
504
return_match(any, _Sup, St) -> St;
 
505
return_match(_Req, unknown, St) -> St;
 
506
return_match(N, N, St) -> St;
 
507
return_match(_Req, _Sup, St) ->
 
508
    add_error({return_mismatch,St#lint.func}, St).
 
509
 
 
510
%% arg_match(Required, Supplied, State) -> State.
 
511
 
 
512
arg_match(_Req, unknown, St) -> St;
 
513
arg_match(N, N, St) -> St;
 
514
arg_match(_Req, _Sup, St) ->
 
515
    add_error({arg_mismatch,St#lint.func}, St).