~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%-----------------------------------------------------------------------
3
 
%% ``The contents of this file are subject to the Erlang Public License,
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
4
8
%% Version 1.1, (the "License"); you may not use this file except in
5
9
%% compliance with the License. You should have received a copy of the
6
10
%% Erlang Public License along with this software. If not, it can be
7
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
11
%% retrieved online at http://www.erlang.org/.
8
12
%% 
9
13
%% Software distributed under the License is distributed on an "AS IS"
10
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
11
15
%% the License for the specific language governing rights and limitations
12
16
%% under the License.
13
17
%% 
14
 
%% Copyright 2006, 2007 Tobias Lindahl and Kostis Sagonas
15
 
%% 
16
 
%%     $Id$
 
18
%% %CopyrightEnd%
17
19
%%
18
20
 
19
21
%%%-------------------------------------------------------------------
27
29
 
28
30
-module(dialyzer).
29
31
 
30
 
%%%-------------------------------------------------------------------
31
 
%%% NOTE: Only functions exported by this module are available to
32
 
%%%       other applications.
33
 
%%%-------------------------------------------------------------------
 
32
%%--------------------------------------------------------------------
 
33
%% NOTE: Only functions exported by this module are available to
 
34
%%       other applications.
 
35
%%--------------------------------------------------------------------
34
36
-export([plain_cl/0, 
35
37
         run/1, 
36
38
         gui/0,
63
65
      end,
64
66
      case Opts#options.check_plt of
65
67
        true ->
66
 
          case cl_check_init(Opts#options{get_warnings=false}) of
67
 
            {error, _} = Error -> cl_halt(Error, Opts);
68
 
            {ok, _} -> gui_halt(internal_gui(Opts), Opts)
 
68
          case cl_check_init(Opts#options{get_warnings = false}) of
 
69
            {ok, _} -> gui_halt(internal_gui(Opts), Opts);
 
70
            {error, _} = Error -> cl_halt(Error, Opts)
69
71
          end;
70
72
        false ->
71
73
          gui_halt(internal_gui(Opts), Opts)
73
75
    {cl, Opts} -> 
74
76
      case Opts#options.check_plt of
75
77
        true ->
76
 
          case cl_check_init(Opts#options{get_warnings=false}) of
 
78
          case cl_check_init(Opts#options{get_warnings = false}) of
77
79
            {error, _} = Error -> cl_halt(Error, Opts);
78
80
            {ok, _} -> cl_halt(cl(Opts), Opts)
79
81
          end;
91
93
    plt_remove -> {ok, ?RET_NOTHING_SUSPICIOUS};
92
94
    Other when Other =:= succ_typings; Other =:= plt_check ->
93
95
      F = fun() ->
94
 
              dialyzer_cl:start(Opts#options{analysis_type=plt_check})
 
96
              dialyzer_cl:start(Opts#options{analysis_type = plt_check})
95
97
          end,
96
98
      doit(F)
97
99
  end.
102
104
      end,
103
105
  doit(F).
104
106
 
105
 
print_plt_info(Opts) ->
106
 
  Plt = Opts#options.init_plt,
 
107
print_plt_info(#options{init_plt = PLT, output_file = OutputFile}) ->
107
108
  String =
108
 
    case dialyzer_plt:included_files(Plt) of
 
109
    case dialyzer_plt:included_files(PLT) of
109
110
      {ok, Files} ->
110
 
        io_lib:format("The plt ~s includes the following files:\n~p\n",
111
 
                      [Plt, Files]);
 
111
        io_lib:format("The PLT ~s includes the following files:\n~p\n",
 
112
                      [PLT, Files]);
112
113
      {error, read_error} ->
113
 
        Msg = io_lib:format("Could not read the plt file ~p\n", [Plt]),
 
114
        Msg = io_lib:format("Could not read the PLT file ~p\n", [PLT]),
114
115
        throw({dialyzer_error, Msg});
115
116
      {error, no_such_file} ->
116
 
        Msg = io_lib:format("The plt file ~p does not exist\n", [Plt]),
 
117
        Msg = io_lib:format("The PLT file ~p does not exist\n", [PLT]),
117
118
        throw({dialyzer_error, Msg})
118
119
    end,
119
 
  case Opts#options.output_file of
120
 
    none -> 
 
120
  case OutputFile =:= none of
 
121
    true ->
121
122
      io:format("~s", [String]),
122
123
      ?RET_NOTHING_SUSPICIOUS;
123
 
    OutputFile ->
 
124
    false ->
124
125
      case file:open(OutputFile, [write]) of
125
126
        {ok, FileDesc} ->
126
127
          io:format(FileDesc, "~s", [String]),
200
201
      erlang:error({dialyzer_error, lists:flatten(ErrorMsg)})
201
202
  end.
202
203
 
203
 
check_gui_options(#options{analysis_type=succ_typings}) ->
 
204
check_gui_options(#options{analysis_type = succ_typings}) ->
204
205
  ok;
205
 
check_gui_options(#options{analysis_type=Mode}) ->
206
 
  Msg = io_lib:format("Analysis mode ~w is illegal in gui mode", [Mode]),
 
206
check_gui_options(#options{analysis_type = Mode}) ->
 
207
  Msg = io_lib:format("Analysis mode ~w is illegal in GUI mode", [Mode]),
207
208
  throw({dialyzer_error, Msg}).
208
209
 
209
 
-spec plt_info(string()) -> {ok, [{'files', [string()]}]} | {error, atom()}.
 
210
-spec plt_info(filename()) -> {'ok', [{'files', [filename()]}]} | {'error', atom()}.
210
211
 
211
212
plt_info(Plt) ->
212
213
  case dialyzer_plt:included_files(Plt) of
231
232
  cl_halt({error, Msg}, #options{}).
232
233
 
233
234
gui_halt(R, Opts) ->
234
 
  cl_halt(R, Opts#options{report_mode=quiet}).
 
235
  cl_halt(R, Opts#options{report_mode = quiet}).
235
236
 
236
237
-spec cl_halt({'ok',dial_ret()} | {'error',string()}, #options{}) -> no_return().
237
238
 
238
 
cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS},  #options{report_mode=quiet}) -> 
239
 
  halt(R);
240
 
cl_halt({ok, R = ?RET_DISCREPANCIES}, #options{report_mode=quiet}) -> 
241
 
  halt(R);
242
 
cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS},  #options{}) ->
 
239
cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS}, #options{report_mode = quiet}) -> 
 
240
  halt(R);
 
241
cl_halt({ok, R = ?RET_DISCREPANCIES}, #options{report_mode = quiet}) -> 
 
242
  halt(R);
 
243
cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS}, #options{}) ->
243
244
  io:put_chars("done (passed successfully)\n"),
244
245
  halt(R);
245
 
cl_halt({ok, R = ?RET_DISCREPANCIES},  #options{output_file=Output}) ->
 
246
cl_halt({ok, R = ?RET_DISCREPANCIES}, #options{output_file = Output}) ->
246
247
  io:put_chars("done (warnings were emitted)\n"),
247
248
  cl_check_log(Output),
248
249
  halt(R);
249
 
cl_halt({error, Msg1}, #options{output_file=Output}) ->
250
 
  Msg2 = "dialyzer: Internal problems were encountered in the analysis.",
251
 
  io:format("\n~s\n~s\n", [Msg1, Msg2]),
 
250
cl_halt({error, Msg1}, #options{output_file = Output}) ->
 
251
  %% Msg2 = "dialyzer: Internal problems were encountered in the analysis",
 
252
  io:format("\ndialyzer: ~s\n", [Msg1]),
252
253
  cl_check_log(Output),
253
254
  halt(?RET_INTERNAL_ERROR).
254
255
 
255
 
-spec cl_check_log(string()) -> 'ok'.
 
256
-spec cl_check_log('none' | filename()) -> 'ok'.
256
257
 
257
258
cl_check_log(none) ->
258
259
  ok;
267
268
  String = lists:flatten(message_to_string(Msg)),
268
269
  lists:flatten(io_lib:format("~s:~w: ~s", [BaseName, Line, String])).
269
270
 
270
 
message_to_string({binary_construction, [Size, Seg, Type]}) ->
271
 
  io_lib:format("Binary construction will fail since the size field ~s in "
272
 
                "binary segment ~s has type ~s\n",
273
 
                [Size, Seg, Type]);
274
 
message_to_string({fun_app_no_fun, [Op, Type]}) ->
275
 
  io_lib:format("Fun application will fail since ~s :: ~s is not a function\n",
276
 
                [Op, Type]);
277
 
message_to_string({fun_app_args, [Args, Type]}) ->
278
 
  io_lib:format("Fun application with arguments ~s will fail "
279
 
                "since the function has type ~s\n",
280
 
                 [Args, Type]);
 
271
 
 
272
%%-----------------------------------------------------------------------------
 
273
%% Message classification and pretty-printing below. Messages appear in
 
274
%% categories and iin more or less alphabetical ordering within each category.
 
275
%%-----------------------------------------------------------------------------
 
276
 
 
277
%%----- Warnings for general discrepancies ----------------
 
278
message_to_string({apply, [Args, ArgNs, FailReason,
 
279
                           SigArgs, SigRet, Contract]}) ->
 
280
  io_lib:format("Fun application with arguments ~s ", [Args]) ++
 
281
    call_or_apply_to_string(ArgNs, FailReason, SigArgs, SigRet, Contract);
 
282
message_to_string({app_call, [M, F, Args, Culprit, ExpectedType, FoundType]}) ->
 
283
  io_lib:format("The call ~s:~s~s requires that ~s is of type ~s not ~s\n",
 
284
                [M, F, Args, Culprit, ExpectedType, FoundType]);
 
285
message_to_string({bin_construction, [Culprit, Size, Seg, Type]}) ->
 
286
  io_lib:format("Binary construction will fail since the ~s field ~s in"
 
287
                " segment ~s has type ~s\n", [Culprit, Size, Seg, Type]);
281
288
message_to_string({call, [M, F, Args, ArgNs, FailReason, 
282
289
                          SigArgs, SigRet, Contract]}) ->
283
290
  io_lib:format("The call ~w:~w~s ", [M, F, Args]) ++
284
291
    call_or_apply_to_string(ArgNs, FailReason, SigArgs, SigRet, Contract);
285
 
message_to_string({apply, [Args, ArgNs, FailReason,
286
 
                           SigArgs, SigRet, Contract]}) ->
287
 
  io_lib:format("Fun application with arguments ~s ", [Args]) ++
288
 
    call_or_apply_to_string(ArgNs, FailReason, SigArgs, SigRet, Contract);
289
 
message_to_string({exact_eq, [Type1, Type2]}) ->
290
 
  io_lib:format("~s =:= ~s can never evaluate to 'true'\n", [Type1, Type2]);
291
 
message_to_string({improper_list_constr, [TlType]}) ->
292
 
  io_lib:format("Cons will produce an improper list since its "
293
 
                "2nd argument is ~s\n", [TlType]);
294
 
message_to_string({record_matching, [String, Name]}) ->
295
 
  io_lib:format("The ~s violates the "
296
 
                "declared type for #~w{}\n", [String, Name]);
297
 
message_to_string({record_constr, [Types, Name]}) ->
298
 
  io_lib:format("Record construction ~s violates the "
299
 
                "declared type for #~w{}\n", [Types, Name]);
300
 
message_to_string({record_constr, [Name, Field, Type]}) ->
301
 
  io_lib:format("Record construction violates the declared type for #~w{}"
302
 
                " since ~s cannot be of type ~s\n", 
303
 
                [Name, Field, Type]);
304
 
message_to_string({pattern_match_cov, [Pat, Type]}) ->
305
 
  io_lib:format("The ~s can never match since previous"
306
 
                " clauses completely covered the type ~s\n",
307
 
                [Pat, Type]);
308
 
message_to_string({pattern_match, [Pat, Type]}) ->
309
 
  io_lib:format("The ~s can never match the type ~s\n", [Pat, Type]);
 
292
message_to_string({call_to_missing, [M, F, A]}) ->
 
293
  io_lib:format("Call to missing or unexported function ~w:~w/~w\n", [M, F, A]);
 
294
message_to_string({exact_eq, [Type1, Op, Type2]}) ->
 
295
  io_lib:format("The test ~s ~s ~s can never evaluate to 'true'\n",
 
296
                [Type1, Op, Type2]);
 
297
message_to_string({fun_app_args, [Args, Type]}) ->
 
298
  io_lib:format("Fun application with arguments ~s will fail"
 
299
                " since the function has type ~s\n", [Args, Type]);
 
300
message_to_string({fun_app_no_fun, [Op, Type, Arity]}) ->
 
301
  io_lib:format("Fun application will fail since ~s :: ~s"
 
302
                " is not a function of arity ~w\n", [Op, Type, Arity]);
310
303
message_to_string({guard_fail, []}) ->
311
304
  "Clause guard cannot succeed.\n";
312
305
message_to_string({guard_fail, [Arg1, Infix, Arg2]}) ->
313
 
  io_lib:format("Guard test ~s ~s ~s can never succeed\n",
314
 
                [Arg1, Infix, Arg2]);
 
306
  io_lib:format("Guard test ~s ~s ~s can never succeed\n", [Arg1, Infix, Arg2]);
315
307
message_to_string({guard_fail, [Guard, Args]}) ->
316
308
  io_lib:format("Guard test ~w~s can never succeed\n", [Guard, Args]);
317
309
message_to_string({guard_fail_pat, [Pat, Type]}) ->
318
310
  io_lib:format("Clause guard cannot succeed. The ~s was matched"
319
311
                " against the type ~s\n", [Pat, Type]);
320
 
message_to_string({unused_fun, []}) ->
321
 
  io_lib:format("Function will never be called\n", []);
322
 
message_to_string({unused_fun, [F, A]}) ->
323
 
  io_lib:format("Function ~w/~w will never be called\n", [F, A]);
 
312
message_to_string({improper_list_constr, [TlType]}) ->
 
313
  io_lib:format("Cons will produce an improper list"
 
314
                " since its 2nd argument is ~s\n", [TlType]);
324
315
message_to_string({no_return, [Type|Name]}) ->
325
316
  NameString =
326
317
    case Name of
327
 
      [] -> "Function ";
 
318
      [] -> "The created fun ";
328
319
      [F, A] -> io_lib:format("Function ~w/~w ", [F, A])
329
320
    end,
330
321
  case Type of
332
323
    only_normal -> NameString ++ "has no local return\n";
333
324
    both -> NameString ++ "has no local return\n"
334
325
  end;
335
 
message_to_string({spec_missing_fun, [M, F, A]}) ->
336
 
  io_lib:format("Contract for function that does not exist: ~w:~w/~w\n",
337
 
                [M, F, A]);
 
326
message_to_string({record_constr, [Types, Name]}) ->
 
327
  io_lib:format("Record construction ~s violates the"
 
328
                " declared type for #~w{}\n", [Types, Name]);
 
329
message_to_string({record_constr, [Name, Field, Type]}) ->
 
330
  io_lib:format("Record construction violates the declared type for #~w{}"
 
331
                " since ~s cannot be of type ~s\n", [Name, Field, Type]);
 
332
message_to_string({record_matching, [String, Name]}) ->
 
333
  io_lib:format("The ~s violates the"
 
334
                " declared type for #~w{}\n", [String, Name]);
 
335
message_to_string({pattern_match, [Pat, Type]}) ->
 
336
  io_lib:format("The ~s can never match the type ~s\n", [Pat, Type]);
 
337
message_to_string({pattern_match_cov, [Pat, Type]}) ->
 
338
  io_lib:format("The ~s can never match since previous"
 
339
                " clauses completely covered the type ~s\n",
 
340
                [Pat, Type]);
 
341
message_to_string({unmatched_return, [Type]}) ->
 
342
  io_lib:format("Expression produces a value of type ~s,"
 
343
                " but this value is unmatched\n", [Type]);
 
344
message_to_string({unused_fun, []}) ->
 
345
  io_lib:format("Function will never be called\n", []);
 
346
message_to_string({unused_fun, [F, A]}) ->
 
347
  io_lib:format("Function ~w/~w will never be called\n", [F, A]);
 
348
%%----- Warnings for specs and contracts -------------------
 
349
message_to_string({contract_diff, [M, F, _A, Contract, Sig]}) ->
 
350
  io_lib:format("Type specification ~w:~w~s"
 
351
                " is not equal to the success typing: ~w:~w~s\n",
 
352
                [M, F, Contract, M, F, Sig]);
 
353
message_to_string({contract_subtype, [M, F, _A, Contract, Sig]}) ->
 
354
  io_lib:format("Type specification ~w:~w~s"
 
355
                " is a subtype of the success typing: ~w:~w~s\n", 
 
356
                [M, F, Contract, M, F, Sig]);
 
357
message_to_string({contract_supertype, [M, F, _A, Contract, Sig]}) ->
 
358
  io_lib:format("Type specification ~w:~w~s"
 
359
                " is a supertype of the success typing: ~w:~w~s\n",
 
360
                [M, F, Contract, M, F, Sig]);
338
361
message_to_string({invalid_contract, [M, F, A, Sig]}) ->
339
 
  io_lib:format("Invalid type specification for function ~w:~w/~w. "
340
 
                "The success typing is ~s\n", 
341
 
                [M, F, A, Sig]);
 
362
  io_lib:format("Invalid type specification for function ~w:~w/~w."
 
363
                " The success typing is ~s\n", [M, F, A, Sig]);
342
364
message_to_string({overlapping_contract, []}) ->
343
365
  "Overloaded contract has overlapping domains;"
344
366
    " such contracts are currently unsupported and are simply ignored\n";
345
 
message_to_string({contract_subtype, [M, F, A, Contract, Sig]}) ->
346
 
  io_lib:format("Type specification ~w:~w/~w :: ~s "
347
 
                "is a subtype of the success typing: ~s\n", 
348
 
                [M, F, A, Contract, Sig]);
349
 
message_to_string({contract_supertype, [M, F, A, Contract, Sig]}) ->
350
 
  io_lib:format("Type specification ~w:~w/~w :: ~s "
351
 
                "is a supertype of the success typing: ~s\n",
352
 
                [M, F, A, Contract, Sig]);
353
 
message_to_string({contract_diff, [M, F, A, Contract, Sig]}) ->
354
 
  io_lib:format("Type specification ~w:~w/~w :: ~s "
355
 
                "is not equal to the success typing: ~s\n",
356
 
                [M, F, A, Contract, Sig]);
357
 
message_to_string({call_to_missing, [M, F, A]}) ->
358
 
  io_lib:format("Call to missing or unexported function ~w:~w/~w\n", [M, F, A]);
359
 
message_to_string({unmatched_return, [Type]}) ->
360
 
  io_lib:format("Expression produces a value of type ~s, "
361
 
                "but this value is unmatched\n", [Type]).
 
367
message_to_string({spec_missing_fun, [M, F, A]}) ->
 
368
  io_lib:format("Contract for function that does not exist: ~w:~w/~w\n",
 
369
                [M, F, A]);
 
370
%%----- Warnings for opaque type violations -------------------
 
371
message_to_string({call_with_opaque, [M, F, Args, ArgNs, ExpArgs]}) ->
 
372
  io_lib:format("The call ~w:~w~s contains ~s when ~s\n",
 
373
                [M, F, Args, form_positions(ArgNs), form_expected(ExpArgs)]);
 
374
message_to_string({call_without_opaque, [M, F, Args, ExpectedTriples]}) ->
 
375
  io_lib:format("The call ~w:~w~s does not have ~s\n",
 
376
                [M, F, Args, form_expected_without_opaque(ExpectedTriples)]);
 
377
message_to_string({opaque_eq, [Type, _Op, OpaqueType]}) ->
 
378
  io_lib:format("Attempt to test for equality between a term of type ~s"
 
379
                " and a term of opaque type ~s\n", [Type, OpaqueType]);
 
380
message_to_string({opaque_guard, [Guard, Args]}) ->
 
381
  io_lib:format("Guard test ~w~s breaks the opaqueness of its argument\n",
 
382
                [Guard, Args]);
 
383
message_to_string({opaque_match, [Pat, OpaqueType, OpaqueTerm]}) ->
 
384
  Term = if OpaqueType =:= OpaqueTerm -> "the term";
 
385
            true -> OpaqueTerm
 
386
         end,
 
387
  io_lib:format("The attempt to match a term of type ~s against the ~s"
 
388
                " breaks the opaqueness of ~s\n", [OpaqueType, Pat, Term]);
 
389
message_to_string({opaque_neq, [Type, _Op, OpaqueType]}) ->
 
390
  io_lib:format("Attempt to test for inequality between a term of type ~s"
 
391
                " and a term of opaque type ~s\n", [Type, OpaqueType]);
 
392
message_to_string({opaque_type_test, [Fun, Opaque]}) ->
 
393
  io_lib:format("The type test ~s(~s) breaks the opaqueness of the term ~s\n", [Fun, Opaque, Opaque]);
 
394
%%----- Warnings for concurrency errors --------------------
 
395
message_to_string({possible_race, [M, F, Args, Reason]}) ->
 
396
  io_lib:format("The call ~w:~w~s ~s\n", [M, F, Args, Reason]).
 
397
 
 
398
 
 
399
%%-----------------------------------------------------------------------------
 
400
%% Auxiliary functions below
 
401
%%-----------------------------------------------------------------------------
362
402
 
363
403
call_or_apply_to_string(ArgNs, FailReason, SigArgs, SigRet, 
364
404
                        {IsOverloaded, Contract}) ->
365
 
  PositionString =
366
 
    case ArgNs of
367
 
      [] -> [];
368
 
      [N1] -> io_lib:format("position ~w", [N1]);
369
 
      [_|_] -> 
370
 
        " and"++ArgString = lists:flatten([io_lib:format(" and ~w", [N]) 
371
 
                                           || N <- ArgNs]),
372
 
        "positions" ++ ArgString
373
 
    end,
 
405
  PositionString = form_position_string(ArgNs),
374
406
  case FailReason of
375
407
    only_sig ->
376
408
      case ArgNs =:= [] of
377
 
        true -> 
378
 
          %% We do not know which arguments caused the failure. 
 
409
        true ->
 
410
          %% We do not know which argument(s) caused the failure
379
411
          io_lib:format("will never return since the success typing arguments"
380
412
                        " are ~s\n", [SigArgs]);
381
 
        false ->
 
413
        false ->
382
414
          io_lib:format("will never return since it differs in argument" 
383
415
                        " ~s from the success typing arguments: ~s\n", 
384
416
                        [PositionString, SigArgs])
386
418
    only_contract -> 
387
419
      case (ArgNs =:= []) orelse IsOverloaded of
388
420
        true ->
389
 
          %% We do not know which arguments caused the failure. 
 
421
          %% We do not know which arguments caused the failure
390
422
          io_lib:format("breaks the contract ~s\n", [Contract]);
391
423
        false ->
392
424
          io_lib:format("breaks the contract ~s in argument ~s\n",
393
425
                        [Contract, PositionString])
394
426
      end;
395
 
    both  ->
 
427
    both ->
396
428
      io_lib:format("will never return since the success typing is ~s -> ~s"
397
429
                    " and the contract is ~s\n", [SigArgs, SigRet, Contract])
398
430
  end.
 
431
 
 
432
form_positions(ArgNs) ->
 
433
  case ArgNs of
 
434
    [_] -> "an opaque term in ";
 
435
    [_,_|_] -> "opaque terms in "
 
436
 end ++ form_position_string(ArgNs).
 
437
 
 
438
%% We know which positions N are to blame;
 
439
%% the list of triples will never be empty.
 
440
form_expected_without_opaque([{N, T, TStr}]) ->
 
441
  case erl_types:t_is_opaque(T) of
 
442
    true  ->
 
443
      io_lib:format("an opaque term of type ~s in ", [TStr]);
 
444
    false ->
 
445
      io_lib:format("a term of type ~s (with opaque subterms) in ", [TStr])
 
446
  end ++ form_position_string([N]);
 
447
form_expected_without_opaque(ExpectedTriples) -> %% TODO: can do much better here
 
448
  {ArgNs, _Ts, _TStrs} = lists:unzip3(ExpectedTriples),
 
449
  "opaque terms in " ++ form_position_string(ArgNs).
 
450
 
 
451
form_expected(ExpectedArgs) ->
 
452
  case ExpectedArgs of
 
453
    [T] ->
 
454
      TS = erl_types:t_to_string(T),
 
455
      case erl_types:t_is_opaque(T) of
 
456
        true  -> io_lib:format("an opaque term of type ~s is expected", [TS]);
 
457
        false -> io_lib:format("a structured term of type ~s is expected", [TS])
 
458
      end;
 
459
    [_,_|_] -> "terms of different types are expected in these positions"
 
460
  end.
 
461
 
 
462
form_position_string(ArgNs) ->
 
463
  case ArgNs of
 
464
    [] -> "";
 
465
    [N1] -> io_lib:format("position ~w", [N1]);
 
466
    [_,_|_] -> 
 
467
      " and"++ArgString = lists:flatten([io_lib:format(" and ~w", [N]) 
 
468
                                         || N <- ArgNs]),
 
469
        "positions" ++ ArgString
 
470
  end.