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

« back to all changes in this revision

Viewing changes to lib/ic/test/ic_pp_SUITE.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
%%----------------------------------------------------------------------
 
21
%% Purpose : Test suite for the IDL preprocessor
 
22
%%----------------------------------------------------------------------
 
23
 
 
24
-module(ic_pp_SUITE).
 
25
-include_lib("test_server/include/test_server.hrl").
 
26
 
 
27
 
 
28
 
 
29
%% Standard options to the ic compiler, NOTE unholy use of OutDir
 
30
 
 
31
-define(OUT(X), filename:join([?config(priv_dir, Config), gen, to_list(X)])).
 
32
-define(GCC, "g++").
 
33
-define(GCC_VER, "2.95.3").
 
34
 
 
35
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
 
36
-export([arg_norm/1]).
 
37
-export([cascade_norm/1]).
 
38
-export([comment_norm/1]).
 
39
-export([concat_norm/1]).
 
40
-export([define_norm/1]).
 
41
-export([if_norm/1]).
 
42
-export([if_zero/1]).
 
43
-export([misc_norm/1]).
 
44
-export([improp_nest_constr_norm/1]).
 
45
-export([inc_norm/1]).
 
46
-export([line_norm/1]).
 
47
-export([nopara_norm/1]).
 
48
-export([predef_norm/1]).
 
49
-export([predef_time_norm/1]).
 
50
-export([self_ref_norm/1]).
 
51
-export([separate_norm/1]).
 
52
-export([swallow_sc_norm/1]).
 
53
-export([unintended_grp_norm/1]).
 
54
-export([cases/0, init_per_suite/1, end_per_suite/1]).
 
55
 
 
56
 
 
57
suite() -> [{ct_hooks,[ts_install_cth]}].
 
58
 
 
59
all() -> 
 
60
    cases().
 
61
 
 
62
groups() -> 
 
63
    [{arg, [], [arg_norm]}, {cascade, [], [cascade_norm]},
 
64
     {comment, [], [comment_norm]},
 
65
     {concat, [], [concat_norm]},
 
66
     {define, [], [define_norm]}, {inc, [], [inc_norm]},
 
67
     {improp_nest_constr, [], [improp_nest_constr_norm]},
 
68
     {misc, [], [misc_norm]}, {line, [], [line_norm]},
 
69
     {nopara, [], [nopara_norm]},
 
70
     {predef, [], [predef_norm]},
 
71
     {predef_time, [], [predef_time_norm]},
 
72
     {self_ref, [], [self_ref_norm]},
 
73
     {separate, [], [separate_norm]},
 
74
     {swallow_sc, [], [swallow_sc_norm]},
 
75
     {unintended_grp, [], [unintended_grp_norm]},
 
76
     {'if', [],[if_norm, if_zero]}].
 
77
 
 
78
init_per_group(_GroupName, Config) ->
 
79
        Config.
 
80
 
 
81
end_per_group(_GroupName, Config) ->
 
82
        Config.
 
83
 
 
84
 
 
85
init_per_suite(Config) ->
 
86
    if
 
87
        is_list(Config) ->
 
88
            case os:type() of
 
89
                {win32, _} ->
 
90
                    {skipped, "Very unplesent to run on windows"};
 
91
                _ ->
 
92
                    check_gcc(Config)
 
93
            end;
 
94
        true ->
 
95
            exit("Config not a list")
 
96
    end.
 
97
 
 
98
check_gcc(Config) ->
 
99
    case os:find_executable(?GCC) of
 
100
        false ->
 
101
            {skipped, 
 
102
             lists:flatten(io_lib:format("Can not run without ~s in path", 
 
103
                                         [?GCC]))};
 
104
        _ ->
 
105
            case trim(os:cmd(?GCC++" --version")) of
 
106
                ?GCC_VER++[] -> 
 
107
                    Config;
 
108
                ?GCC_VER++[D|_] when is_integer(D), D>=$0, D=<$9 -> 
 
109
                    fail_gcc(?GCC_VER++[D]);
 
110
                ?GCC_VER++_ ->
 
111
                    Config;
 
112
                Ver ->
 
113
                    fail_gcc(Ver)
 
114
            end
 
115
    end.
 
116
 
 
117
fail_gcc(Ver) ->
 
118
    {skipped, lists:flatten(io_lib:format("Need ~s v~s, not ~s", 
 
119
                                          [?GCC, ?GCC_VER, Ver]))}.
 
120
 
 
121
trim(S) -> lists:reverse(skip_white(lists:reverse(skip_white(S)))).
 
122
 
 
123
skip_white([$\s|T]) -> skip_white(T);
 
124
skip_white([$\n|T]) -> skip_white(T);
 
125
skip_white([$\r|T]) -> skip_white(T);
 
126
skip_white([$\t|T]) -> skip_white(T);
 
127
skip_white(L) -> L.
 
128
    
 
129
 
 
130
end_per_suite(Config) ->
 
131
    Config.
 
132
 
 
133
 
 
134
cases() -> 
 
135
    [{group, arg}, {group, cascade}, {group, comment},
 
136
     {group, concat}, {group, define}, {group, misc}, {group, 'if'},
 
137
     {group, improp_nest_constr}, {group, inc},
 
138
     {group, line}, {group, nopara}, {group, predef},
 
139
     {group, predef_time}, {group, self_ref},
 
140
     {group, separate}, {group, swallow_sc},
 
141
     {group, unintended_grp}].
 
142
    
 
143
 
 
144
 
 
145
%%--------------------------------------------------------------------
 
146
%% arg
 
147
%%--------------------------------------------------------------------
 
148
 
 
149
 
 
150
arg_norm(doc) -> ["Checks arguments for #define."];
 
151
arg_norm(suite) -> [];
 
152
arg_norm(Config) when is_list(Config) ->
 
153
    DataDir = ?config(data_dir, Config),
 
154
    _OutDir = ?OUT(arg_norm),
 
155
    File = filename:join(DataDir, arg),
 
156
    
 
157
    ?line ok = test_file(File, DataDir),
 
158
    ok.
 
159
 
 
160
 
 
161
%%--------------------------------------------------------------------
 
162
%% cascade
 
163
%%--------------------------------------------------------------------
 
164
 
 
165
 
 
166
cascade_norm(doc) -> ["Check cascade #define."];
 
167
cascade_norm(suite) -> [];
 
168
cascade_norm(Config) when is_list(Config) ->
 
169
    DataDir = ?config(data_dir, Config),
 
170
    _OutDir = ?OUT(cascade_norm),
 
171
    File = filename:join(DataDir, cascade),
 
172
    
 
173
    ?line ok = test_file(File, DataDir),
 
174
    ok.
 
175
 
 
176
 
 
177
%%--------------------------------------------------------------------
 
178
%% comment
 
179
%%--------------------------------------------------------------------
 
180
 
 
181
 
 
182
comment_norm(doc) -> ["Check comments."];
 
183
comment_norm(suite) -> [];
 
184
comment_norm(Config) when is_list(Config) ->
 
185
    DataDir = ?config(data_dir, Config),
 
186
    _OutDir = ?OUT(comment_norm),
 
187
    File = filename:join(DataDir, comment),
 
188
    
 
189
    ?line ok = test_file(File, DataDir),
 
190
    ok.
 
191
 
 
192
 
 
193
%%--------------------------------------------------------------------
 
194
%% concat
 
195
%%--------------------------------------------------------------------
 
196
 
 
197
 
 
198
concat_norm(doc) -> ["Check concatinations, i.e ## ."];
 
199
concat_norm(suite) -> [];
 
200
concat_norm(Config) when is_list(Config) ->
 
201
    DataDir = ?config(data_dir, Config),
 
202
    _OutDir = ?OUT(concat_norm),
 
203
    File = filename:join(DataDir, concat),
 
204
    
 
205
    ?line ok = test_file(File, DataDir),
 
206
    ok.
 
207
 
 
208
 
 
209
%%--------------------------------------------------------------------
 
210
%% define
 
211
%%--------------------------------------------------------------------
 
212
 
 
213
 
 
214
define_norm(doc) -> ["Check misceleaneous #define."];
 
215
define_norm(suite) -> [];
 
216
define_norm(Config) when is_list(Config) ->
 
217
    DataDir = ?config(data_dir, Config),
 
218
    _OutDir = ?OUT(define_norm),
 
219
    File = filename:join(DataDir, define),
 
220
    
 
221
    ?line ok = test_file(File, DataDir),
 
222
    ok.
 
223
 
 
224
 
 
225
%%--------------------------------------------------------------------
 
226
%% if
 
227
%%--------------------------------------------------------------------
 
228
 
 
229
if_norm(doc) -> ["Check #if, #elif, and #endif. ."];
 
230
if_norm(suite) -> [];
 
231
if_norm(Config) when is_list(Config) ->
 
232
    DataDir = ?config(data_dir, Config),
 
233
    _OutDir = ?OUT(if_norm),
 
234
    File = filename:join(DataDir, 'if'),
 
235
    
 
236
    ?line ok = test_file(File, DataDir),
 
237
    ok.
 
238
 
 
239
if_zero(doc) -> ["Check #if 0"];
 
240
if_zero(suite) -> [];
 
241
if_zero(Config) when is_list(Config) ->
 
242
    DataDir = ?config(data_dir, Config),
 
243
    _OutDir = ?OUT(if_zero),
 
244
    File = filename:join(DataDir, if_zero),
 
245
    
 
246
    ?line ok = test_file(File, DataDir),
 
247
    ok.
 
248
 
 
249
 
 
250
%%--------------------------------------------------------------------
 
251
%% inc
 
252
%%--------------------------------------------------------------------
 
253
 
 
254
 
 
255
inc_norm(doc) -> ["Check #include."];
 
256
inc_norm(suite) -> [];
 
257
inc_norm(Config) when is_list(Config) ->
 
258
    DataDir = ?config(data_dir, Config),
 
259
    _OutDir = ?OUT(inc_norm),
 
260
    File = filename:join(DataDir, inc),
 
261
    
 
262
    ?line ok = test_file(File, DataDir),
 
263
    ok.
 
264
 
 
265
 
 
266
 
 
267
%%--------------------------------------------------------------------
 
268
%% improp_nest_constr
 
269
%%--------------------------------------------------------------------
 
270
 
 
271
 
 
272
improp_nest_constr_norm(doc) -> ["Check improperly nested constructs."];
 
273
improp_nest_constr_norm(suite) -> [];
 
274
improp_nest_constr_norm(Config) when is_list(Config) ->
 
275
    DataDir = ?config(data_dir, Config),
 
276
    _OutDir = ?OUT(improp_nest_constr_norm),
 
277
    File = filename:join(DataDir, improp_nest_constr),
 
278
    
 
279
    ?line ok = test_file(File, DataDir),
 
280
    ok.
 
281
 
 
282
 
 
283
%%--------------------------------------------------------------------
 
284
%% misc
 
285
%%--------------------------------------------------------------------
 
286
 
 
287
 
 
288
misc_norm(doc) -> ["Misceleaneous checks."];
 
289
misc_norm(suite) -> [];
 
290
misc_norm(Config) when is_list(Config) ->
 
291
    DataDir = ?config(data_dir, Config),
 
292
    _OutDir = ?OUT(misc_norm),
 
293
    File = filename:join(DataDir, misc),
 
294
    
 
295
    ?line ok = test_file(File, DataDir),
 
296
    ok.
 
297
 
 
298
 
 
299
%%--------------------------------------------------------------------
 
300
%% line
 
301
%%--------------------------------------------------------------------
 
302
 
 
303
 
 
304
line_norm(doc) -> ["Checks #line."];
 
305
line_norm(suite) -> [];
 
306
line_norm(Config) when is_list(Config) ->
 
307
    DataDir = ?config(data_dir, Config),
 
308
    _OutDir = ?OUT(line_norm),
 
309
    File = filename:join(DataDir, line),
 
310
    
 
311
    ?line ok = test_file(File, DataDir),
 
312
    ok.
 
313
 
 
314
 
 
315
%%--------------------------------------------------------------------
 
316
%% nopara
 
317
%%--------------------------------------------------------------------
 
318
 
 
319
 
 
320
nopara_norm(doc) -> ["Checks #define with no parameters."];
 
321
nopara_norm(suite) -> [];
 
322
nopara_norm(Config) when is_list(Config) ->
 
323
    DataDir = ?config(data_dir, Config),
 
324
    _OutDir = ?OUT(nopara_norm),
 
325
    File = filename:join(DataDir, nopara),
 
326
    
 
327
    ?line ok = test_file(File, DataDir),
 
328
    ok.
 
329
 
 
330
 
 
331
%%--------------------------------------------------------------------
 
332
%% predef
 
333
%%--------------------------------------------------------------------
 
334
 
 
335
 
 
336
predef_norm(doc) -> ["Checks predefined macros. Note: not __TIME__ and __DATE__."];
 
337
predef_norm(suite) -> [];
 
338
predef_norm(Config) when is_list(Config) ->
 
339
    DataDir = ?config(data_dir, Config),
 
340
    _OutDir = ?OUT(predef_norm),
 
341
    File = filename:join(DataDir, predef),
 
342
    
 
343
    ?line ok = test_file(File, DataDir),
 
344
    ok.
 
345
 
 
346
 
 
347
%%--------------------------------------------------------------------
 
348
%% predef_time
 
349
%%--------------------------------------------------------------------
 
350
 
 
351
 
 
352
predef_time_norm(doc) -> ["Checks the predefined macros __TIME__ and __DATE__."];
 
353
predef_time_norm(suite) -> [];
 
354
predef_time_norm(Config) when is_list(Config) ->
 
355
    DataDir = ?config(data_dir, Config),
 
356
    _OutDir = ?OUT(predef_time_norm),
 
357
    File = filename:join(DataDir, predef_time),
 
358
    
 
359
    ?line ok = test_file(File, DataDir),
 
360
    ok.
 
361
 
 
362
 
 
363
%%--------------------------------------------------------------------
 
364
%% self_ref
 
365
%%--------------------------------------------------------------------
 
366
 
 
367
 
 
368
self_ref_norm(doc) -> ["Checks self referring macros."];
 
369
self_ref_norm(suite) -> [];
 
370
self_ref_norm(Config) when is_list(Config) ->
 
371
    DataDir = ?config(data_dir, Config),
 
372
    _OutDir = ?OUT(self_ref_norm),
 
373
    File = filename:join(DataDir, self_ref),
 
374
    
 
375
    ?line ok = test_file(File, DataDir),
 
376
    ok.
 
377
 
 
378
 
 
379
%%--------------------------------------------------------------------
 
380
%% separate
 
381
%%--------------------------------------------------------------------
 
382
 
 
383
 
 
384
separate_norm(doc) -> ["Checks separete expansion of macro arguments."];
 
385
separate_norm(suite) -> [];
 
386
separate_norm(Config) when is_list(Config) ->
 
387
    DataDir = ?config(data_dir, Config),
 
388
    _OutDir = ?OUT(separate_norm),
 
389
    File = filename:join(DataDir, separate),
 
390
    
 
391
    ?line ok = test_file(File, DataDir),
 
392
    ok.
 
393
 
 
394
 
 
395
%%--------------------------------------------------------------------
 
396
%% swallow_sc
 
397
%%--------------------------------------------------------------------
 
398
 
 
399
 
 
400
swallow_sc_norm(doc) -> ["Checks swallowing an undesirable semicolon."];
 
401
swallow_sc_norm(suite) -> [];
 
402
swallow_sc_norm(Config) when is_list(Config) ->
 
403
    DataDir = ?config(data_dir, Config),
 
404
    _OutDir = ?OUT(swallow_sc_norm),
 
405
    File = filename:join(DataDir, swallow_sc),
 
406
    
 
407
    ?line ok = test_file(File, DataDir),
 
408
    ok.
 
409
 
 
410
 
 
411
%%--------------------------------------------------------------------
 
412
%% unintended_grp
 
413
%%--------------------------------------------------------------------
 
414
 
 
415
 
 
416
unintended_grp_norm(doc) -> ["Checks unintended grouping of arithmetic."];
 
417
unintended_grp_norm(suite) -> [];
 
418
unintended_grp_norm(Config) when is_list(Config) ->
 
419
    DataDir = ?config(data_dir, Config),
 
420
    _OutDir = ?OUT(unintended_grp_norm),
 
421
    File = filename:join(DataDir, unintended_grp),
 
422
    
 
423
    ?line ok = test_file(File, DataDir),
 
424
    ok.
 
425
 
 
426
 
 
427
 
 
428
 
 
429
 
 
430
test_file(FileT, DataDir) ->
 
431
    case test_file_1(FileT, DataDir) of
 
432
        ok -> ok;
 
433
        Chars ->
 
434
            io:put_chars(Chars),
 
435
            {error,{FileT,DataDir}}
 
436
    end.
 
437
 
 
438
test_file_1(FileT, DataDir) ->
 
439
    Tok = string:tokens(FileT, "/"),
 
440
    FileName = lists:last(Tok),
 
441
    File = FileT++".idl",
 
442
 
 
443
    ?line test_server:format("File  ~p~n",[File]),
 
444
    ?line test_server:format("FileName  ~p~n",[FileName]),
 
445
 
 
446
    Flags = "-I"++DataDir,
 
447
 
 
448
    ?line test_server:format("Flags  ~p~n",[Flags]),
 
449
 
 
450
    ?line Erl = pp_erl(File, Flags),
 
451
    ?line Gcc = pp_gcc(File, Flags),
 
452
 
 
453
    ?line case Erl of
 
454
        {error,_ErlError} ->
 
455
            ?line test_server:format("Internal_pp Result ~n==================~n~p~n~n",[Erl]);
 
456
        {warning, _ErlWar} ->
 
457
            ?line test_server:format("Internal_pp Result ~n==================~n~p~n~n",[Erl]);
 
458
        _ ->
 
459
            ?line test_server:format("Internal_pp Result ~n==================~n~s~n~n",[Erl])
 
460
    end,
 
461
    
 
462
    ?line case Gcc of
 
463
        {error,GccError} ->
 
464
            Error = string:tokens(GccError, "\n"),
 
465
            ?line test_server:format(?GCC" Result ~n==========~n~p~n~n",
 
466
                                     [Error]);
 
467
        _ ->
 
468
            ?line test_server:format(?GCC" Result ~n==========~n~s~n~n",[Gcc])
 
469
    end,
 
470
 
 
471
 
 
472
 
 
473
    ?line case {Erl,Gcc} of
 
474
        {{warning,W}, {error,X}} ->
 
475
            ?line case is_ok(W,X) of
 
476
                yes ->
 
477
                    ok;
 
478
                no ->
 
479
                    io_lib:format("Internal_pp found Warning = ~p ~n"
 
480
                                  ?GCC" found Error = ~p~n",[W,X])
 
481
            end;
 
482
           
 
483
 
 
484
        {{warning,W}, _} ->
 
485
            io_lib:format(?GCC" did not find warnings while ~n"
 
486
                          "Internal_pp found the following Warning = ~p~n",[W]);
 
487
 
 
488
        {{error,E}, {error,X}} ->
 
489
            ?line case is_ok(E,X) of
 
490
                yes ->
 
491
                    ok;
 
492
                no ->
 
493
                    io_lib:format("Internal_pp found Error = ~p ~n"
 
494
                                  ?GCC" found Error = ~p~n",[E,X])
 
495
            end;
 
496
 
 
497
        {{error,E}, _} ->
 
498
            ?line case FileName of
 
499
                "if" ->
 
500
                    ?line case if_res(E) of
 
501
                        ok ->
 
502
                            ok;
 
503
                        _ ->
 
504
                            io_lib:format(?GCC" did not find errors while ~n"
 
505
                                          "Internal_pp found the following Error = ~p~n",[E])
 
506
                    end;
 
507
                _ ->
 
508
                    io_lib:format(?GCC" did not find errors while ~n"
 
509
                                  "Internal_pp found the following Error = ~p~n",[lists:flatten(E)])
 
510
            end;
 
511
 
 
512
        {_, {error,X}} ->
 
513
            io_lib:format("Internal_pp did not find errors while ~n"
 
514
                          ?GCC" found the following Error = ~p~n",[X]);
 
515
 
 
516
        _ ->
 
517
 
 
518
            ?line file:write_file("/tmp/Erl.pp",list_to_binary(Erl)),
 
519
            ?line file:write_file("/tmp/Gcc.pp",list_to_binary(Gcc)),
 
520
            
 
521
            ?line Res = os:cmd("diff -b -w /tmp/Erl.pp /tmp/Gcc.pp"),
 
522
            ?line test_server:format("///////////{error,E} E ~p  FileName~p~n",[Res,FileName]),
 
523
            ?line case {Res, FileName} of
 
524
                {[], _} ->
 
525
                    ?line test_server:format("Diff = []   OK!!!!!!~n"),
 
526
                    ok;
 
527
                {_, "predef_time"} ->
 
528
                    Tokens = string:tokens(Res,"\n"),
 
529
                    ?line test_server:format("///////////{error,E} Tokens~p~n",[Tokens]),
 
530
                    case Tokens of
 
531
                        ["3c3",_,"---",_,"5c5",_,"---",_,"9c9",_,"---",_] ->
 
532
                            ok;
 
533
                        _ ->
 
534
                            io_lib:format("Diff Result = ~p~n",[Res])
 
535
                    end;
 
536
                _ ->
 
537
                    io_lib:format("Diff Result = ~p~n",[Res])
 
538
            end
 
539
    end.
 
540
 
 
541
 
 
542
 
 
543
 
 
544
 
 
545
pp_erl(File, Flags) ->
 
546
    case ic_pp:run(File,Flags) of
 
547
        {ok, [$#, $ , $1 | Rest], []} ->
 
548
            [$#, $ , $1 | Rest];
 
549
        {ok, [$#, $ , $1 | _Rest], Warning} ->
 
550
            {warning,Warning};
 
551
        {error,Error} ->
 
552
            {error,Error}
 
553
    end.
 
554
 
 
555
pp_gcc(File, Flags) ->
 
556
    Cmd = ?GCC" -x c++ -E",
 
557
    Line        = Cmd++" "++Flags++" "++File,
 
558
 
 
559
    case os:cmd(Line) of
 
560
        [$#, $ , $1 | Rest] ->                  
 
561
            [$#, $ , $1 | Rest];
 
562
        Res ->
 
563
 
 
564
            case string:str(Res,"# 1 \"") of
 
565
                0 ->
 
566
                    {error,Res};
 
567
                X ->
 
568
                    {error, string:sub_string(Res, 1, X-1)}
 
569
            end
 
570
    end.
 
571
 
 
572
 
 
573
is_ok([],_Gcc) ->
 
574
    yes;
 
575
is_ok([{FileName,Line,Text}|T],Gcc) ->
 
576
    Str = FileName++":"++integer_to_list(Line)++": "++Text,
 
577
    case string:str(Gcc,Str) of
 
578
        0 ->
 
579
            io:format("~n is_ok Internal_pp missed Error = ~s~n",[Str]),
 
580
            no;
 
581
        _X ->
 
582
            is_ok(T,Gcc)
 
583
    end;
 
584
is_ok([Str|T],Gcc) ->
 
585
    case string:str(Gcc,Str) of
 
586
        0 ->
 
587
            io:format("~n is_ok Internal_pp missed Error = ~s~n",[Str]),
 
588
            no;
 
589
        _X ->
 
590
            is_ok(T,Gcc)
 
591
    end.
 
592
 
 
593
 
 
594
to_list(X) when is_atom(X) -> atom_to_list(X);
 
595
to_list(X) -> X.
 
596
 
 
597
 
 
598
 
 
599
if_res(E) ->
 
600
    if_res(E,1).
 
601
 
 
602
if_res([H|T],Nr) ->
 
603
    %% Dir = "/clearcase/otp/libraries/ic/test/ic_pp_SUITE_data/if.idl",
 
604
    case {Nr, H} of
 
605
        {1, {_Dir, 2, "only '#if 0' is implemented at present"}} ->
 
606
            if_res(T,Nr+1);
 
607
        {2, {_Dir, 3, "only '#if 0' is implemented at present"}} ->
 
608
            if_res(T,Nr+1);
 
609
        {3, {_Dir, 5, "`else' command is not implemented at present"}} ->
 
610
            if_res(T,Nr+1);
 
611
        {4, {_Dir, 9, "`elif' command is not implemented at present"}} ->
 
612
            if_res(T,Nr+1);
 
613
        {5, {_Dir, 11, "`else' command is not implemented at present"}} ->
 
614
            ok;
 
615
        _ ->
 
616
            error
 
617
    end;
 
618
if_res(_, _) ->
 
619
    error.
 
620
 
 
621
 
 
622