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

« back to all changes in this revision

Viewing changes to lib/stdlib/test/epp_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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
 
19
19
-module(epp_SUITE).
20
 
-export([all/1]).
 
20
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
21
         init_per_group/2,end_per_group/2]).
21
22
 
22
 
-export([rec_1/1, predef_mac/1, 
23
 
         upcase_mac/1, upcase_mac_1/1, upcase_mac_2/1,
24
 
         variable/1, variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
 
23
-export([rec_1/1, predef_mac/1,
 
24
         upcase_mac_1/1, upcase_mac_2/1,
 
25
         variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
25
26
         pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
26
 
         otp_8130/1]).
 
27
         otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
 
28
         otp_8562/1, otp_8665/1, otp_8911/1]).
27
29
 
28
30
-export([epp_parse_erl_form/2]).
29
31
 
38
40
-define(config(A,B),config(A,B)).
39
41
%% -define(t, test_server).
40
42
-define(t, io).
41
 
config(priv_dir, _) ->    
 
43
config(priv_dir, _) ->
42
44
    filename:absname("./epp_SUITE_priv");
43
45
config(data_dir, _) ->
44
46
    filename:absname("./epp_SUITE_data").
45
47
-else.
46
 
-include("test_server.hrl").
47
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
48
-include_lib("test_server/include/test_server.hrl").
 
49
-export([init_per_testcase/2, end_per_testcase/2]).
48
50
 
49
51
% Default timetrap timeout (set in init_per_testcase).
50
52
-define(default_timeout, ?t:minutes(1)).
52
54
init_per_testcase(_, Config) ->
53
55
    ?line Dog = ?t:timetrap(?default_timeout),
54
56
    [{watchdog, Dog} | Config].
55
 
fin_per_testcase(_, Config) ->
 
57
end_per_testcase(_, Config) ->
56
58
    Dog = ?config(watchdog, Config),
57
59
    test_server:timetrap_cancel(Dog),
58
60
    ok.
59
61
-endif.
60
62
 
61
 
all(doc) ->
62
 
    ["Test cases for epp."];
63
 
all(suite) ->
64
 
    [rec_1, upcase_mac, predef_mac, variable, otp_4870, otp_4871, otp_5362, 
65
 
     pmod, not_circular, skip_header, otp_6277, otp_7702, otp_8130].
 
63
suite() -> [{ct_hooks,[ts_install_cth]}].
 
64
 
 
65
all() -> 
 
66
    [rec_1, {group, upcase_mac}, predef_mac,
 
67
     {group, variable}, otp_4870, otp_4871, otp_5362, pmod,
 
68
     not_circular, skip_header, otp_6277, otp_7702, otp_8130,
 
69
     overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
 
70
     otp_8665, otp_8911].
 
71
 
 
72
groups() -> 
 
73
    [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
 
74
     {variable, [], [variable_1]}].
 
75
 
 
76
init_per_suite(Config) ->
 
77
    Config.
 
78
 
 
79
end_per_suite(_Config) ->
 
80
    ok.
 
81
 
 
82
init_per_group(_GroupName, Config) ->
 
83
    Config.
 
84
 
 
85
end_per_group(_GroupName, Config) ->
 
86
    Config.
66
87
 
67
88
rec_1(doc) ->
68
89
    ["Recursive macros hang or crash epp (OTP-1398)."];
125
146
check_errors([_ | Rest]) ->
126
147
    check_errors(Rest).
127
148
 
128
 
upcase_mac(doc) ->
129
 
    ["Check that uppercase macro names are implicitly quoted (OTP-2608)"];
130
 
upcase_mac(suite) ->
131
 
    [upcase_mac_1, upcase_mac_2].
132
149
 
133
150
upcase_mac_1(doc) ->
134
151
    [];
174
191
          end,
175
192
    ok.
176
193
 
177
 
variable(doc) ->
178
 
    ["Check variable as first file component of the include directives."];
179
 
variable(suite) ->
180
 
    [variable_1].
181
194
 
182
195
variable_1(doc) ->
183
196
    [];
190
203
    %% variable_1.erl includes variable_1_include.hrl and
191
204
    %% variable_1_include_dir.hrl.
192
205
    ?line {ok, List} = epp:parse_file(File, [], []),
193
 
    ?line {value, {attribute,_,a,{value1,value2}}} = 
 
206
    ?line {value, {attribute,_,a,{value1,value2}}} =
194
207
        lists:keysearch(a,3,List),
195
208
    ok.
196
209
 
217
230
    %% Testing crash in erl_scan. Unfortunately there currently is
218
231
    %% no known way to crash erl_scan so it is emulated by killing the
219
232
    %% file io server. This assumes lots of things about how
220
 
    %% the processes are started and how monitors are set up, 
 
233
    %% the processes are started and how monitors are set up,
221
234
    %% so there are some sanity checks before killing.
222
235
    ?line {ok,Epp} = epp:open(File, []),
223
236
    timer:sleep(1),
224
237
    ?line {current_function,{epp,_,_}} = process_info(Epp, current_function),
225
238
    ?line {monitored_by,[Io]} = process_info(Epp, monitored_by),
226
 
    ?line {current_function,{file_io_server,_,_}} = 
 
239
    ?line {current_function,{file_io_server,_,_}} =
227
240
        process_info(Io, current_function),
228
241
    ?line exit(Io, emulate_crash),
229
242
    timer:sleep(1),
300
313
    Back_hrl = [<<"
301
314
                  -file(\"">>,File_Back,<<"\", 2).
302
315
                 ">>],
303
 
    
 
316
 
304
317
    ?line ok = file:write_file(File_Back, Back),
305
318
    ?line ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)),
306
319
 
331
344
 
332
345
    ?line ok = file:write_file(File_Change, list_to_binary(Change)),
333
346
 
334
 
    ?line {ok, change_5362, ChangeWarnings} = 
 
347
    ?line {ok, change_5362, ChangeWarnings} =
335
348
        compile:file(File_Change, Copts),
336
349
    ?line true = message_compare(
337
350
                   [{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]},
439
452
                                  that should be skipped
440
453
                                  -module(epp_test_skip_header).
441
454
                                  -export([main/1]).
442
 
                               
 
455
 
443
456
                                  main(_) -> ?MODULE.
444
 
                               
 
457
 
445
458
                                  ">>),
446
459
    ?line {ok, Fd} = file:open(File, [read]),
447
460
    ?line io:get_line(Fd, ''),
466
479
              -define(ASSERT, ?MODULE).
467
480
 
468
481
              ?ASSERT().">>,
469
 
           [{error,{{4,16},epp,{undefined,'MODULE'}}}]}],
 
482
           [{error,{{4,16},epp,{undefined,'MODULE', none}}}]}],
470
483
    ?line [] = check(Config, Ts),
471
484
    ok.
472
485
 
492
505
                   t() ->
493
506
                       ?RECEIVE(foo, bar).">>,
494
507
    ?line ok = file:write_file(File, Contents),
495
 
    ?line {ok, file_7702, []} = 
 
508
    ?line {ok, file_7702, []} =
496
509
        compile:file(File, [debug_info,return,{outdir,Dir}]),
497
 
    
 
510
 
498
511
    BeamFile = filename:join(Dir, "file_7702.beam"),
499
512
    {ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]),
500
513
 
504
517
                  L
505
518
          end,
506
519
    Forms2 = [erl_lint:modify_line(Form, Fun) || Form <- Forms],
507
 
    ?line 
 
520
    ?line
508
521
        [{attribute,1,file,_},
509
522
         _,
510
523
         _,
615
628
             "t() -> 14 = (#file_info{size = 14})#file_info.size, ok.\n">>,
616
629
           ok},
617
630
 
618
 
          {otp_8130_7,
 
631
          {otp_8130_7_new,
619
632
           <<"-record(b, {b}).\n"
620
 
             "-define(A, {{a,#b.b.\n"
 
633
             "-define(A, {{a,#b.b).\n"
621
634
             "t() -> {{a,2}} = ?A}}, ok.">>,
622
635
           ok},
623
636
 
635
648
 
636
649
         ],
637
650
    ?line [] = run(Config, Ts),
638
 
          
 
651
 
639
652
    Cs = [{otp_8130_c1,
640
653
           <<"-define(M1(A), if\n"
641
654
             "A =:= 1 -> B;\n"
673
686
 
674
687
          {otp_8130_c7,
675
688
           <<"\nt() -> ?A.\n">>,
676
 
           {errors,[{{2,9},epp,{undefined,'A'}}],[]}},
 
689
           {errors,[{{2,9},epp,{undefined,'A', none}}],[]}},
677
690
 
678
691
          {otp_8130_c8,
679
692
           <<"\n-include_lib(\"$apa/foo.hrl\").\n">>,
680
693
           {errors,[{{2,2},epp,{include,lib,"$apa/foo.hrl"}}],[]}},
681
694
 
682
 
          
 
695
 
683
696
          {otp_8130_c9,
684
697
           <<"-define(S, ?S).\n"
685
698
             "t() -> ?S.\n">>,
686
 
           {errors,[{{2,9},epp,{circular,'S'}}],[]}},
 
699
           {errors,[{{2,9},epp,{circular,'S', none}}],[]}},
687
700
 
688
701
          {otp_8130_c10,
689
702
           <<"\n-file.">>,
718
731
          {otp_8130_c17,
719
732
           <<"\n-define(A(B), B).\n"
720
733
            "-define(A, 1).\n">>,
721
 
           {errors,[{{3,9},epp,{redefine,'A'}}],[]}},
 
734
           []},
722
735
 
723
736
          {otp_8130_c18,
724
737
           <<"\n-define(A, 1).\n"
725
738
            "-define(A(B), B).\n">>,
726
 
           {errors,[{{3,9},epp,{redefine,'A'}}],[]}},
 
739
           []},
727
740
 
728
741
          {otp_8130_c19,
729
742
           <<"\n-define(a(B), B).\n"
730
743
            "-define(a, 1).\n">>,
731
 
           {errors,[{{3,9},epp,{redefine,a}}],[]}},
 
744
           []},
732
745
 
733
746
          {otp_8130_c20,
734
747
           <<"\n-define(a, 1).\n"
735
748
            "-define(a(B), B).\n">>,
736
 
           {errors,[{{3,9},epp,{redefine,a}}],[]}},
 
749
           []},
737
750
 
738
751
          {otp_8130_c21,
739
752
           <<"\n-define(A(B, B), B).\n">>,
745
758
 
746
759
          {otp_8130_c23,
747
760
           <<"\n-file(?b, 3).\n">>,
748
 
           {errors,[{{2,8},epp,{undefined,b}}],[]}},
 
761
           {errors,[{{2,8},epp,{undefined,b, none}}],[]}},
749
762
 
750
763
          {otp_8130_c24,
751
764
           <<"\n-include(\"no such file.erl\").\n">>,
752
 
           {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}}
 
765
           {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}},
 
766
 
 
767
          {otp_8130_7,
 
768
           <<"-record(b, {b}).\n"
 
769
             "-define(A, {{a,#b.b.\n"
 
770
             "t() -> {{a,2}} = ?A}}, ok.">>,
 
771
           {errors,[{{2,20},epp,missing_parenthesis},
 
772
                    {{3,19},epp,{undefined,'A',none}}],[]}}
753
773
 
754
774
          ],
755
775
    ?line [] = compile(Config, Cs),
766
786
 
767
787
    ?line Dir = ?config(priv_dir, Config),
768
788
    ?line File = filename:join(Dir, "otp_8130.erl"),
769
 
    ?line ok = file:write_file(File, 
 
789
    ?line ok = file:write_file(File,
770
790
                               "-module(otp_8130).\n"
771
791
                               "-define(a, 3.14).\n"
772
792
                               "t() -> ?a.\n"),
779
799
    ?line {eof,_} = epp:scan_erl_form(Epp),
780
800
    ?line ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE',
781
801
           'MACHINE','MODULE','MODULE_STRING',a] = macs(Epp),
782
 
    ?line epp:close(Epp),    
 
802
    ?line epp:close(Epp),
783
803
 
784
804
    %% escript
785
805
    ModuleStr = "any_name",
806
826
            PreDefMacros = [{a,1},a],
807
827
            ?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
808
828
    end(),
809
 
            
 
829
 
810
830
    ?line {error,enoent} = epp:open("no such file", []),
811
831
    ?line {error,enoent} = epp:parse_file("no such file", [], []),
812
832
 
821
841
macro(Epp, N) ->
822
842
    case lists:keyfind({atom,N}, 1, epp:macro_defs(Epp)) of
823
843
        false -> false;
824
 
        {{atom,N},{_,V}} -> V
 
844
        {{atom,N},{_,V}} -> V;
 
845
        {{atom,N},Defs} -> lists:append([V || {_,{_,V}} <- Defs])
825
846
    end.
826
847
 
827
848
ifdef(Config) ->
931
952
           <<"\n-if.\n"
932
953
             "-endif.\n">>,
933
954
           {errors,[{{2,2},epp,{'NYI','if'}}],[]}},
934
 
          
 
955
 
935
956
          {define_c7,
936
957
           <<"-ifndef(a).\n"
937
958
             "-elif.\n"
1030
1051
           ],
1031
1052
    ?line [] = run(Config, Ts).
1032
1053
 
 
1054
 
 
1055
 
 
1056
overload_mac(doc) ->
 
1057
    ["Advanced test on overloading macros."];
 
1058
overload_mac(suite) ->
 
1059
    [];
 
1060
overload_mac(Config) when is_list(Config) ->
 
1061
    Cs = [
 
1062
          %% '-undef' removes all definitions of a macro
 
1063
          {overload_mac_c1,
 
1064
           <<"-define(A, a).\n"
 
1065
            "-define(A(X), X).\n"
 
1066
            "-undef(A).\n"
 
1067
            "t1() -> ?A.\n",
 
1068
            "t2() -> ?A(1).">>,
 
1069
           {errors,[{{4,10},epp,{undefined,'A', none}},
 
1070
                    {{5,10},epp,{undefined,'A', 1}}],[]}},
 
1071
 
 
1072
          %% cannot overload predefined macros
 
1073
          {overload_mac_c2,
 
1074
           <<"-define(MODULE(X), X).">>,
 
1075
           {errors,[{{1,50},epp,{redefine_predef,'MODULE'}}],[]}},
 
1076
 
 
1077
          %% cannot overload macros with same arity
 
1078
          {overload_mac_c3,
 
1079
           <<"-define(A(X), X).\n"
 
1080
            "-define(A(Y), Y).">>,
 
1081
           {errors,[{{2,9},epp,{redefine,'A'}}],[]}},
 
1082
 
 
1083
          {overload_mac_c4,
 
1084
           <<"-define(A, a).\n"
 
1085
            "-define(A(X,Y), {X,Y}).\n"
 
1086
            "a(X) -> X.\n"
 
1087
            "t() -> ?A(1).">>,
 
1088
           {errors,[{{4,9},epp,{mismatch,'A'}}],[]}}
 
1089
         ],
 
1090
    ?line [] = compile(Config, Cs),
 
1091
 
 
1092
    Ts = [
 
1093
          {overload_mac_r1,
 
1094
           <<"-define(A, 1).\n"
 
1095
            "-define(A(X), X).\n"
 
1096
            "-define(A(X, Y), {X, Y}).\n"
 
1097
            "t() -> {?A, ?A(2), ?A(3, 4)}.">>,
 
1098
           {1, 2, {3, 4}}},
 
1099
 
 
1100
          {overload_mac_r2,
 
1101
           <<"-define(A, 1).\n"
 
1102
            "-define(A(X), X).\n"
 
1103
            "t() -> ?A(?A).">>,
 
1104
           1},
 
1105
 
 
1106
          {overload_mac_r3,
 
1107
           <<"-define(A, ?B).\n"
 
1108
            "-define(B, a).\n"
 
1109
            "-define(B(X), {b,X}).\n"
 
1110
            "a(X) -> X.\n"
 
1111
            "t() -> ?A(1).">>,
 
1112
           1}
 
1113
          ],
 
1114
    ?line [] = run(Config, Ts).
 
1115
 
 
1116
 
 
1117
otp_8388(doc) ->
 
1118
    ["OTP-8388. More tests on overloaded macros."];
 
1119
otp_8388(suite) ->
 
1120
    [];
 
1121
otp_8388(Config) when is_list(Config) ->
 
1122
    Dir = ?config(priv_dir, Config),
 
1123
    ?line File = filename:join(Dir, "otp_8388.erl"),
 
1124
    ?line ok = file:write_file(File, <<"-module(otp_8388)."
 
1125
                                       "-define(LINE, a).">>),
 
1126
    fun() ->
 
1127
            PreDefMacros = [{'LINE', a}],
 
1128
            ?line {error,{redefine_predef,'LINE'}} =
 
1129
                epp:open(File, [], PreDefMacros)
 
1130
    end(),
 
1131
 
 
1132
    fun() ->
 
1133
            PreDefMacros = ['LINE'],
 
1134
            ?line {error,{redefine_predef,'LINE'}} =
 
1135
                epp:open(File, [], PreDefMacros)
 
1136
    end(),
 
1137
 
 
1138
    Ts = [
 
1139
          {macro_1,
 
1140
           <<"-define(m(A), A).\n"
 
1141
             "t() -> ?m(,).\n">>,
 
1142
           {errors,[{{2,9},epp,{arg_error,m}}],[]}},
 
1143
          {macro_2,
 
1144
           <<"-define(m(A), A).\n"
 
1145
             "t() -> ?m(a,).\n">>,
 
1146
           {errors,[{{2,9},epp,{arg_error,m}}],[]}},
 
1147
          {macro_3,
 
1148
           <<"-define(LINE, a).\n">>,
 
1149
           {errors,[{{1,50},epp,{redefine_predef,'LINE'}}],[]}},
 
1150
          {macro_4,
 
1151
           <<"-define(A(B, C, D), {B,C,D}).\n"
 
1152
             "t() -> ?A(a,,3).\n">>,
 
1153
           {errors,[{{2,9},epp,{mismatch,'A'}}],[]}},
 
1154
          {macro_5,
 
1155
           <<"-define(Q, {?F0(), ?F1(,,4)}).\n">>,
 
1156
           {errors,[{{1,62},epp,{arg_error,'F1'}}],[]}},
 
1157
          {macro_6,
 
1158
           <<"-define(FOO(X), ?BAR(X)).\n"
 
1159
             "-define(BAR(X), ?FOO(X)).\n"
 
1160
             "-undef(FOO).\n"
 
1161
             "test() -> ?BAR(1).\n">>,
 
1162
           {errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}}
 
1163
         ],
 
1164
    ?line [] = compile(Config, Ts),
 
1165
    ok.
 
1166
 
 
1167
otp_8470(doc) ->
 
1168
    ["OTP-8470. Bugfix (one request - two replies)."];
 
1169
otp_8470(suite) ->
 
1170
    [];
 
1171
otp_8470(Config) when is_list(Config) ->
 
1172
    Dir = ?config(priv_dir, Config),
 
1173
    C = <<"-file(\"erl_parse.yrl\", 486).\n"
 
1174
          "-file(\"erl_parse.yrl\", 488).\n">>,
 
1175
    ?line File = filename:join(Dir, "otp_8470.erl"),
 
1176
    ?line ok = file:write_file(File, C),
 
1177
    ?line {ok, _List} = epp:parse_file(File, [], []),
 
1178
    file:delete(File),
 
1179
    ?line receive _ -> fail() after 0 -> ok end,
 
1180
    ok.
 
1181
 
 
1182
otp_8503(doc) ->
 
1183
    ["OTP-8503. Record with no fields is considered typed."];
 
1184
otp_8503(suite) ->
 
1185
    [];
 
1186
otp_8503(Config) when is_list(Config) ->
 
1187
    Dir = ?config(priv_dir, Config),
 
1188
    C = <<"-record(r, {}).">>,
 
1189
    ?line File = filename:join(Dir, "otp_8503.erl"),
 
1190
    ?line ok = file:write_file(File, C),
 
1191
    ?line {ok, List} = epp:parse_file(File, [], []),
 
1192
    ?line [_] = [F || {attribute,_,type,{{record,r},[],[]}}=F <- List],
 
1193
    file:delete(File),
 
1194
    ?line receive _ -> fail() after 0 -> ok end,
 
1195
    ok.
 
1196
 
 
1197
otp_8562(doc) ->
 
1198
    ["OTP-8503. Record with no fields is considered typed."];
 
1199
otp_8562(suite) ->
 
1200
    [];
 
1201
otp_8562(Config) when is_list(Config) ->
 
1202
    Cs = [{otp_8562,
 
1203
           <<"-define(P(), {a,b}.\n"
 
1204
             "-define(P3, .\n">>,
 
1205
           {errors,[{{1,60},epp,missing_parenthesis},
 
1206
                    {{2,13},epp,missing_parenthesis}], []}}
 
1207
         ],
 
1208
    ?line [] = compile(Config, Cs),
 
1209
    ok.
 
1210
 
 
1211
otp_8911(doc) ->
 
1212
    ["OTP-8911. -file and file inclusion bug"];
 
1213
otp_8911(suite) ->
 
1214
    [];
 
1215
otp_8911(Config) when is_list(Config) ->
 
1216
    ?line {ok, CWD} = file:get_cwd(),
 
1217
    ?line ok = file:set_cwd(?config(priv_dir, Config)),
 
1218
 
 
1219
    File = "i.erl",
 
1220
    Cont = <<"-module(i).
 
1221
              -compile(export_all).
 
1222
              -file(\"fil1\", 100).
 
1223
              -include(\"i1.erl\").
 
1224
              t() ->
 
1225
                  a.
 
1226
           ">>,
 
1227
    ?line ok = file:write_file(File, Cont),
 
1228
    Incl = <<"-file(\"fil2\", 35).
 
1229
              t1() ->
 
1230
                  b.
 
1231
           ">>,
 
1232
    File1 = "i1.erl",
 
1233
    ?line ok = file:write_file(File1, Incl),
 
1234
 
 
1235
    ?line {ok, i} = cover:compile(File),
 
1236
    ?line a = i:t(),
 
1237
    ?line {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
 
1238
    ?line cover:stop(),
 
1239
 
 
1240
    file:delete(File),
 
1241
    file:delete(File1),
 
1242
    ?line file:set_cwd(CWD),
 
1243
    ok.
 
1244
 
 
1245
otp_8665(doc) ->
 
1246
    ["OTP-8665. Bugfix premature end."];
 
1247
otp_8665(suite) ->
 
1248
    [];
 
1249
otp_8665(Config) when is_list(Config) ->
 
1250
    Cs = [{otp_8562,
 
1251
           <<"-define(A, a)\n">>,
 
1252
           {errors,[{{1,54},epp,premature_end}],[]}}
 
1253
         ],
 
1254
    ?line [] = compile(Config, Cs),
 
1255
    ok.
 
1256
 
1033
1257
check(Config, Tests) ->
1034
1258
    eval_tests(Config, fun check_test/2, Tests).
1035
1259
 
1046
1270
                case message_compare(E, Return) of
1047
1271
                    true ->
1048
1272
                        BadL;
1049
 
                    false -> 
 
1273
                    false ->
1050
1274
                        ?t:format("~nTest ~p failed. Expected~n  ~p~n"
1051
1275
                                  "but got~n  ~p~n", [N, E, Return]),
1052
1276
                        fail()
1061
1285
    ?line File = filename:join(PrivDir, Filename),
1062
1286
    ?line ok = file:write_file(File, Test),
1063
1287
    ?line case epp:parse_file(File, [PrivDir], []) of
1064
 
              {ok,Forms} -> 
 
1288
              {ok,Forms} ->
1065
1289
                  [E || E={error,_} <- Forms];
1066
 
              {error,Error} -> 
 
1290
              {error,Error} ->
1067
1291
                  Error
1068
1292
          end.
1069
1293
 
1078
1302
        {ok, Ws} -> warnings(File, Ws);
1079
1303
        Else -> Else
1080
1304
    end.
1081
 
            
 
1305
 
1082
1306
warnings(File, Ws) ->
1083
1307
    case lists:append([W || {F, W} <- Ws, F =:= File]) of
1084
1308
        [] -> [];
1122
1346
message_compare(T1, T2) ->
1123
1347
    ln(T1) =:= T2.
1124
1348
 
1125
 
%% Replaces locations like {Line,Column} with Line. 
 
1349
%% Replaces locations like {Line,Column} with Line.
1126
1350
ln({warnings,L}) ->
1127
1351
    {warnings,ln0(L)};
1128
1352
ln({errors,EL,WL}) ->