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

« back to all changes in this revision

Viewing changes to lib/parsetools/test/leex_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 2010-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
-module(leex_SUITE).
 
20
 
 
21
%-define(debug, true).
 
22
 
 
23
-include_lib("stdlib/include/erl_compile.hrl").
 
24
-include_lib("kernel/include/file.hrl").
 
25
 
 
26
-ifdef(debug).
 
27
-define(line, put(line, ?LINE), ).
 
28
-define(config(X,Y), foo).
 
29
-define(datadir, "leex_SUITE_data").
 
30
-define(privdir, "leex_SUITE_priv").
 
31
-define(t, test_server).
 
32
-else.
 
33
-include_lib("test_server/include/test_server.hrl").
 
34
-define(datadir, ?config(data_dir, Config)).
 
35
-define(privdir, ?config(priv_dir, Config)).
 
36
-endif.
 
37
 
 
38
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
39
         init_per_group/2,end_per_group/2, 
 
40
         init_per_testcase/2, end_per_testcase/2]).
 
41
 
 
42
-export([
 
43
         file/1, compile/1, syntax/1,
 
44
         
 
45
         pt/1, man/1, ex/1, ex2/1, not_yet/1]).
 
46
 
 
47
% Default timetrap timeout (set in init_per_testcase).
 
48
-define(default_timeout, ?t:minutes(1)).
 
49
 
 
50
init_per_testcase(_Case, Config) ->
 
51
    ?line Dog = ?t:timetrap(?default_timeout),
 
52
    [{watchdog, Dog} | Config].
 
53
 
 
54
end_per_testcase(_Case, Config) ->
 
55
    Dog = ?config(watchdog, Config),
 
56
    test_server:timetrap_cancel(Dog),
 
57
    ok.
 
58
 
 
59
suite() -> [{ct_hooks,[ts_install_cth]}].
 
60
 
 
61
all() -> 
 
62
    [{group, checks}, {group, examples}].
 
63
 
 
64
groups() -> 
 
65
    [{checks, [], [file, compile, syntax]},
 
66
     {examples, [], [pt, man, ex, ex2, not_yet]}].
 
67
 
 
68
init_per_suite(Config) ->
 
69
    Config.
 
70
 
 
71
end_per_suite(_Config) ->
 
72
    ok.
 
73
 
 
74
init_per_group(_GroupName, Config) ->
 
75
    Config.
 
76
 
 
77
end_per_group(_GroupName, Config) ->
 
78
    Config.
 
79
 
 
80
 
 
81
 
 
82
file(doc) ->
 
83
    "Bad files and options.";
 
84
file(suite) -> [];
 
85
file(Config) when is_list(Config) ->
 
86
    Dir = ?privdir,
 
87
    Ret = [return, {report, false}],
 
88
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
89
        leex:file("not_a_file", Ret),
 
90
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
91
        leex:file("not_a_file", [{return,true}]),
 
92
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
93
        leex:file("not_a_file", [{report,false},return_errors]),
 
94
    ?line error = leex:file("not_a_file"),
 
95
    ?line error = leex:file("not_a_file", [{return,false},report]),
 
96
    ?line error = leex:file("not_a_file", [return_warnings,{report,false}]),
 
97
 
 
98
    Filename = filename:join(Dir, "file.xrl"),
 
99
    file:delete(Filename),
 
100
 
 
101
    ?line {'EXIT', {badarg, _}} = (catch leex:file({foo})),
 
102
    ?line {'EXIT', {badarg, _}} = 
 
103
        (catch leex:file(Filename, {parserfile,{foo}})),
 
104
    ?line {'EXIT', {badarg, _}} = 
 
105
        (catch leex:file(Filename, {includefile,{foo}})),
 
106
 
 
107
    ?line {'EXIT', {badarg, _}} = (catch leex:file(Filename, no_option)),
 
108
    ?line {'EXIT', {badarg, _}} = 
 
109
        (catch leex:file(Filename, [return | report])),
 
110
    ?line {'EXIT', {badarg, _}} = 
 
111
        (catch leex:file(Filename, {return,foo})),
 
112
    ?line {'EXIT', {badarg, _}} = 
 
113
        (catch leex:file(Filename, includefile)),
 
114
 
 
115
    Mini = <<"Definitions.\n"
 
116
             "D  = [0-9]\n"
 
117
             "Rules.\n"
 
118
             "{L}+  : {token,{word,TokenLine,TokenChars}}.\n"
 
119
             "Erlang code.\n">>,
 
120
    ?line ok = file:write_file(Filename, Mini),
 
121
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
122
        leex:file(Filename, [{scannerfile,"//"} | Ret]),
 
123
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
124
        leex:file(Filename, [{includefile,"//"} | Ret]),
 
125
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
126
        leex:file(Filename, [{includefile,"/ /"} | Ret]),
 
127
 
 
128
    LeexPre = filename:join(Dir, "leexinc.hrl"),
 
129
    ?line ok = file:write_file(LeexPre, <<"syntax error.\n">>),
 
130
    PreErrors = run_test(Config, Mini, LeexPre),
 
131
    ?line {errors,
 
132
           [{1,_,["syntax error before: ","error"]},
 
133
            {3,_,undefined_module}],
 
134
           []} =
 
135
        extract(LeexPre, PreErrors),
 
136
    file:delete(LeexPre),
 
137
 
 
138
    Ret2 = [return, report_errors, report_warnings, verbose],
 
139
    Scannerfile = filename:join(Dir, "file.erl"),
 
140
    ?line ok = file:write_file(Scannerfile, <<"nothing">>),
 
141
    ?line unwritable(Scannerfile),
 
142
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
143
        leex:file(Filename, Ret2),
 
144
    ?line writable(Scannerfile),
 
145
    file:delete(Scannerfile),
 
146
 
 
147
    Dotfile = filename:join(Dir, "file.dot"),
 
148
    ?line ok = file:write_file(Dotfile, <<"nothing">>),
 
149
    ?line unwritable(Dotfile),
 
150
    ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} = 
 
151
        leex:file(Filename, [dfa_graph | Ret2]),
 
152
    ?line writable(Dotfile),
 
153
    file:delete(Dotfile),
 
154
 
 
155
    file:delete(Filename),
 
156
    ok.
 
157
 
 
158
compile(doc) ->
 
159
    "Check of compile/3.";
 
160
compile(suite) -> [];
 
161
compile(Config) when is_list(Config) ->
 
162
    Dir = ?privdir,
 
163
    Filename = filename:join(Dir, "file.xrl"),
 
164
    Scannerfile = filename:join(Dir, "file.erl"),
 
165
    Mini = <<"Definitions.\n"
 
166
             "D  = [0-9]\n"
 
167
             "Rules.\n"
 
168
             "{L}+  : {token,{word,TokenLine,TokenChars}}.\n"
 
169
             "Erlang code.\n">>,
 
170
    ?line ok = file:write_file(Filename, Mini),
 
171
    ?line error = leex:compile(Filename, "//", #options{}),
 
172
    ?line ok = leex:compile(Filename, Scannerfile, #options{}),
 
173
    file:delete(Scannerfile),
 
174
    file:delete(Filename),
 
175
    ok.
 
176
 
 
177
syntax(doc) ->
 
178
    "Syntax checks.";
 
179
syntax(suite) -> [];
 
180
syntax(Config) when is_list(Config) ->
 
181
    Dir = ?privdir,
 
182
    Filename = filename:join(Dir, "file.xrl"),
 
183
    Ret = [return, {report, true}],
 
184
    ?line ok = file:write_file(Filename, 
 
185
                               <<"Definitions.\n"
 
186
                                 "D  = [0-9]\n"
 
187
                                 "%% comment\n"
 
188
                                 "Rules.\n"
 
189
                                 "{L}+  : {token,{word,TokenLine,TokenChars}}.\n
 
190
                                 ">>),
 
191
    ?line {error,[{_,[{7,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
 
192
    ?line ok = file:write_file(Filename, 
 
193
                               <<"Definitions.\n"
 
194
                                 "D  = [0-9]\n"
 
195
                                 "Rules.\n"
 
196
                                 "{L}+  : \n">>),
 
197
    ?line {error,[{_,[{5,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
 
198
    ?line ok = file:write_file(Filename, 
 
199
                               <<"Definitions.\n"
 
200
                                 "D  = [0-9]\n"
 
201
                                 "Rules.\n"
 
202
                                 "[] :">>),
 
203
    ?line {error,[{_,[{4,leex,{regexp,_}}]}],[]} = 
 
204
        leex:file(Filename, Ret),
 
205
    ?line ok = file:write_file(Filename, 
 
206
                               <<"Definitions.\n"
 
207
                                 "D  = [0-9]\n"
 
208
                                 "Rules.\n"
 
209
                                 "{L}+ : .\n"
 
210
                                 "[] : ">>),
 
211
    ?line {error,[{_,[{5,leex,{regexp,_}}]}],[]} = 
 
212
        leex:file(Filename, Ret),
 
213
    ?line ok = file:write_file(Filename, 
 
214
                               <<"Definitions.\n"
 
215
                                 "D  = [0-9]\n"
 
216
                                 "Rules.\n"
 
217
                                 "[] : .\n">>),
 
218
    ?line {error,[{_,[{4,leex,{regexp,_}}]}],[]} = 
 
219
        leex:file(Filename, Ret),
 
220
    ?line ok = file:write_file(Filename, 
 
221
                               <<"Definitions.\n"
 
222
                                 "D  = [0-9]\n"
 
223
                                 "Rules.\n"
 
224
                                 "{L}+ ">>),
 
225
    ?line {error,[{_,[{5,leex,bad_rule}]}],[]} = 
 
226
        leex:file(Filename, Ret),
 
227
    ?line ok = file:write_file(Filename, 
 
228
                               <<"Definitions.\n"
 
229
                                 "D  = [0-9]\n"
 
230
                                 "Rules.\n"
 
231
                                 "{L}+ ; ">>),
 
232
    ?line {error,[{_,[{4,leex,bad_rule}]}],[]} = 
 
233
        leex:file(Filename, Ret),
 
234
    ?line ok = file:write_file(Filename, 
 
235
                               <<"Definitions.\n"
 
236
                                 "D  = [0-9]\n"
 
237
                                 "Rules.\n"
 
238
                                 "[] : '99\n">>),
 
239
    ?line {error,[{_,[{4,erl_scan,_}]}],[]} = leex:file(Filename, Ret),
 
240
    ?line ok = file:write_file(Filename, 
 
241
                               <<"Definitions.\n"
 
242
                                 "D  = [0-9]\n"
 
243
                                 "Rules.\n">>),
 
244
    ?line {error,[{_,[{3,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
 
245
    ?line ok = file:write_file(Filename, 
 
246
                               <<"Definitions.\n"
 
247
                                 "D  = [0-9]\n"
 
248
                                 "Rules.\n"
 
249
                                 "Erlang code.\n">>),
 
250
    ?line {error,[{_,[{4,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
 
251
    ?line ok = file:write_file(Filename, 
 
252
                               <<"Definitions.\n"
 
253
                                 "D  = [0-9]\n">>),
 
254
    ?line {error,[{_,[{2,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
 
255
    ?line ok = file:write_file(Filename, 
 
256
                               <<"Definitions.\n"
 
257
                                 "D  = [0-9]\n"
 
258
                                 "Erlang code.\n">>),
 
259
    ?line {error,[{_,[{3,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
 
260
    ?line ok = file:write_file(Filename, 
 
261
                               <<"">>),
 
262
    %% This is a weird line:
 
263
    ?line {error,[{_,[{0,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
 
264
    ?line ok = file:write_file(Filename, 
 
265
                               <<"Rules.\n">>),
 
266
    ?line {error,[{_,[{1,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
 
267
 
 
268
    %% Check that correct line number is used in messages.
 
269
    ErlFile = filename:join(Dir, "file.erl"),
 
270
    Ret1 = [{scannerfile,ErlFile}|Ret],
 
271
    ?line ok = file:write_file(Filename,
 
272
                               <<"Definitions.\n"
 
273
                                 "D  = [0-9]\n"
 
274
                                 "Rules.\n"
 
275
                                 "{L}+  : {token,\n"
 
276
                                 "         {word,TokenLine,TokenChars,\n"
 
277
                                 "          DDDD}}.\n" % unbound
 
278
                                 "Erlang code.\n"
 
279
                                 "an error.\n">>),     % syntax error
 
280
    ?line {ok, _, []} = leex:file(Filename, Ret1),
 
281
    ?line {error, 
 
282
           [{_,[{8,_,["syntax error before: ","error"]}]},
 
283
            {_,[{6,_,{unbound_var,'DDDD'}}]}],
 
284
           []} =
 
285
        compile:file(ErlFile, [basic_validation, return]),
 
286
 
 
287
    %% Ignored characters
 
288
    ?line ok = file:write_file(Filename,
 
289
                               <<"Definitions. D = [0-9]\n"
 
290
                                 "Rules. [a-z] : .\n"
 
291
                                 "1 : skip_token.\n"
 
292
                                 "Erlang code. f() -> a.\n">>),
 
293
    ?line {ok,_,[{_,
 
294
                  [{1,leex,ignored_characters},
 
295
                   {2,leex,ignored_characters},
 
296
                   {4,leex,ignored_characters}]}]} = 
 
297
        leex:file(Filename, Ret),
 
298
 
 
299
    ?line ok = file:write_file(Filename,
 
300
                               <<"Definitions.\n"
 
301
                                 "D  = [0-9]\n"
 
302
                                 "Rules.\n"
 
303
                                 "{L}+\\  : token.\n">>),
 
304
    ?line {error,[{_,[{4,leex,{regexp,{unterminated,"\\"}}}]}],[]} =
 
305
        leex:file(Filename, Ret),
 
306
    ?line ok = file:write_file(Filename,
 
307
                               <<"Definitions.\n"
 
308
                                 "D  = [0-9]\n"
 
309
                                 "Rules.\n"
 
310
                                 "{L}+\\x  : token.\n">>),
 
311
    ?line {error,[{_,[{4,leex,{regexp,{illegal_char,"\\x"}}}]}],[]} =
 
312
        leex:file(Filename, Ret),
 
313
    ?line ok = file:write_file(Filename,
 
314
                               <<"Definitions.\n"
 
315
                                 "D  = [0-9]\n"
 
316
                                 "Rules.\n"
 
317
                                 "{L}+\\x{  : token.\n">>),
 
318
    ?line {error,[{_,[{4,leex,{regexp,{unterminated,"\\x{"}}}]}],[]} =
 
319
        leex:file(Filename, Ret),
 
320
    ?line ok = file:write_file(Filename,
 
321
                               <<"Definitions.\n"
 
322
                                 "D  = [0-9]\n"
 
323
                                 "Rules.\n"
 
324
                                 "[^ab : token.\n">>),
 
325
    ?line {error,[{_,[{4,leex,{regexp,{unterminated,"["}}}]}],[]} =
 
326
        leex:file(Filename, Ret),
 
327
    ?line ok = file:write_file(Filename,
 
328
                               <<"Definitions.\n"
 
329
                                 "D  = [0-9]\n"
 
330
                                 "Rules.\n"
 
331
                                 "(a : token.\n">>),
 
332
    ?line {error,[{_,[{4,leex,{regexp,{unterminated,"("}}}]}],[]} =
 
333
        leex:file(Filename, Ret),
 
334
    ?line ok = file:write_file(Filename,
 
335
                               <<"Definitions.\n"
 
336
                                 "D  = [0-9]\n"
 
337
                                 "Rules.\n"
 
338
                                 "[b-a] : token.\n">>),
 
339
    ?line {error,[{_,[{4,leex,{regexp,{char_class,"b-a"}}}]}],[]} =
 
340
        leex:file(Filename, Ret),
 
341
 
 
342
    ?line ok = file:write_file(Filename,
 
343
                               <<"Definitions.\n"
 
344
                                 "D  = [0-9]\n"
 
345
                                 "Rules.\n"
 
346
                                 "\\x{333333333333333333333333} : token.\n">>),
 
347
    ?line {error,[{_,[{4,leex,{regexp,
 
348
                                {illegal_char,
 
349
                                 "\\x{333333333333333333333333}"}}}]}],[]} =
 
350
        leex:file(Filename, Ret),
 
351
    ok.
 
352
 
 
353
 
 
354
pt(doc) ->
 
355
    "Pushing back characters.";
 
356
pt(suite) -> [];
 
357
pt(Config) when is_list(Config) ->
 
358
    %% Needs more testing...
 
359
    Ts = [{pt_1, 
 
360
         <<"Definitions.\n"
 
361
            "D  = [0-9]\n"
 
362
            "L  = [a-z]\n"
 
363
 
 
364
            "Rules.\n"
 
365
            "{L}+  : {token,{word,TokenLine,TokenChars}}.\n"
 
366
            "abc{D}+  : {skip_token,\"sture\" ++ string:substr(TokenChars, 4)}.\n"
 
367
            "{D}+  : {token,{integer,TokenLine,list_to_integer(TokenChars)}}.\n"
 
368
            "\\s  : .\n"
 
369
            "\\r\\n  : {end_token,{crlf,TokenLine}}.\n"
 
370
 
 
371
            "Erlang code.\n"
 
372
            "-export([t/0]).\n"
 
373
            "t() ->
 
374
                 {ok,[{word,1,\"sture\"},{integer,1,123}],1} =
 
375
                     string(\"abc123\"), ok. ">>,
 
376
           default,
 
377
           ok}],
 
378
 
 
379
    ?line run(Config, Ts),
 
380
    ok.
 
381
 
 
382
man(doc) ->
 
383
    "Examples from the manpage.";
 
384
man(suite) -> [];
 
385
man(Config) when is_list(Config) ->
 
386
    Ts = [{man_1, 
 
387
     <<"Definitions.\n"
 
388
       "Rules.\n"
 
389
       "[a-z][0-9a-zA-Z_]* :\n"
 
390
       "    {token,{atom,TokenLine,list_to_atom(TokenChars)}}.\n"
 
391
       "[A-Z_][0-9a-zA-Z_]* :\n"
 
392
       "    {token,{var,TokenLine,list_to_atom(TokenChars)}}.\n"
 
393
       "(\\+|-)?[0-9]+\\.[0-9]+((E|e)(\\+|-)?[0-9]+)? : \n"
 
394
       "   {token,{float,TokenLine,list_to_float(TokenChars)}}.\n"
 
395
       "\\s : skip_token.\n"
 
396
       "Erlang code.\n"
 
397
       "-export([t/0]).\n"
 
398
       "t() ->\n"
 
399
       "    {ok,[{float,1,3.14},{atom,1,atom},{var,1,'V314'}],1} =\n"
 
400
       "        string(\"3.14atom V314\"),\n"
 
401
       "    ok.\n">>,
 
402
           default,
 
403
           ok},
 
404
 
 
405
          {man_2,
 
406
     <<"Definitions.\n"
 
407
       "D = [0-9]\n"
 
408
       "Rules.\n"
 
409
       "{D}+ :\n"
 
410
       "  {token,{integer,TokenLine,list_to_integer(TokenChars)}}.\n"
 
411
       "{D}+\\.{D}+((E|e)(\\+|\\-)?{D}+)? :\n"
 
412
       "  {token,{float,TokenLine,list_to_float(TokenChars)}}.\n"
 
413
       "\\s : skip_token.\n"
 
414
       "Erlang code.\n"
 
415
       "-export([t/0]).\n"
 
416
       "t() ->\n"
 
417
       "    {ok,[{float,1,3.14},{integer,1,314}],1} = \n"
 
418
       "        string(\"3.14 314\"),\n"
 
419
       "    ok.\n">>,
 
420
           default,
 
421
           ok}],
 
422
    
 
423
    ?line run(Config, Ts),
 
424
    ok.
 
425
 
 
426
ex(doc) ->
 
427
    "Examples.";
 
428
ex(suite) -> [];
 
429
ex(Config) when is_list(Config) ->
 
430
    Ts = [{ex_1,
 
431
      <<"Definitions.\n"
 
432
        "D = [0-543-705-982]\n"
 
433
        "Rules.\n"
 
434
        "{D}+ :\n"
 
435
        "  {token,{integer,TokenLine,list_to_integer(TokenChars)}}.\n"
 
436
        "[^235]+ :\n"
 
437
        "  {token,{list_to_atom(TokenChars),TokenLine}}.\n"
 
438
        "Erlang code.\n"
 
439
        "-export([t/0]).\n"
 
440
        "t() ->\n"
 
441
        "    {ok,[{integer,1,12},{' c\\na',1},{integer,2,34},{b789a,2}],2} =\n"
 
442
        "        string(\"12 c\\na34b789a\"),\n"
 
443
        "    ok.\n">>,
 
444
           default,
 
445
           ok},
 
446
 
 
447
          {ex_2,
 
448
      <<"Definitions.\n"
 
449
        "L = [a-z]\n"
 
450
        "D = [0-9]\n"
 
451
        "Rules.\n"
 
452
        "{L}+ : {token,chars}.\n"
 
453
        "zyx{D}+ : {token,zyx}.\n"
 
454
        "\\s : skip_token.\n"
 
455
        "Erlang code.\n"
 
456
        "-export([t/0]).\n"
 
457
        "t() ->\n"
 
458
        "    {ok,[chars,zyx],1} = string(\"abcdef zyx123\"),\n"
 
459
        "    ok.\n">>,
 
460
           default,
 
461
           ok},
 
462
 
 
463
          {ex_3,
 
464
      <<"Definitions.\n"
 
465
        "NL = [\\n]\n"
 
466
        "Rules.\n"
 
467
        "{NL}* : {token,newlines}.\n"
 
468
        "Erlang code.\n"
 
469
        "-export([t/0]).\n"
 
470
        "t() ->\n"
 
471
        "     {ok,[],1} = string(\"\"), ok.\n">>, % string("a") would loop...
 
472
           default,
 
473
           ok},
 
474
 
 
475
          {ex_4,
 
476
      <<"Definitions.\n"
 
477
        "SP1 = [\\n-\\s]\n"
 
478
        "SP0 = [\\000-\\n]\n"
 
479
        "Rules.\n"
 
480
        "{SP0}+ : {token,{small,TokenChars}}.\n"
 
481
        "{SP1}+ : {token,{big,TokenChars}}.\n"
 
482
        "Erlang code.\n"
 
483
        "-export([t/0]).\n"
 
484
        "t() ->\n"
 
485
        "     string(\"\\x00\\n\\s\\n\\n\"),\n"
 
486
        "     ok.\n">>,
 
487
          default,
 
488
          ok},
 
489
 
 
490
          {ex_5, 
 
491
      <<"Definitions.\n"
 
492
        "L = [a-z]\n"
 
493
        "W = [\\s\\b\\n\\r\\t\\e\\v\\d\\f]\n"
 
494
        "Rules.\n"
 
495
        "\\[{L}+(,{L}+)*\\] : {token,{list,TokenChars}}.\n"
 
496
        "\"{L}+\" : {token,{string,TokenChars}}.\n"
 
497
        "\\$. : {token,{char,TokenChars}}.\n"
 
498
        "{W}+ : {token,{white,TokenChars}}.\n"
 
499
        "ff\\f+ : {token,{form,TokenChars}}.\n"
 
500
        "\\$\\^+\\\\+ : {token,{other,TokenChars}}.\n"
 
501
        "Erlang code.\n"
 
502
        "-export([t/0]).\n"
 
503
        "t() ->\n"
 
504
        "    {ok,[{white,\"\\b\\f\"}],1} = string(\"\\b\\f\"),\n"
 
505
        "    {ok,[{form,\"ff\\f\"}],1} = string(\"ff\\f\"),\n"
 
506
        "    {ok,[{string,\"\\\"foo\\\"\"}],1} = string(\"\\\"foo\\\"\"),\n"
 
507
        "    {ok,[{char,\"$.\"}],1} = string(\"$\\.\"),\n"
 
508
        "    {ok,[{list,\"[a,b,c]\"}],1} = string(\"[a,b,c]\"),\n"
 
509
        "    {ok,[{other,\"$^\\\\\"}],1} = string(\"$^\\\\\"),\n"
 
510
        "    ok.\n">>,
 
511
           default,
 
512
           ok},
 
513
 
 
514
         {ex_6,
 
515
      <<"Definitions.\n"
 
516
        "L = [a-z]\n"
 
517
        "Rules.\n"
 
518
        "L}+ : {token,{TokenChars,#r.f}}.\n"
 
519
        "Erlang code.\n"
 
520
        "-record(r, {f}).\n"
 
521
        "-export([t/0]).\n"
 
522
        "t() ->\n"
 
523
        "    string(\"abc\"),\n"
 
524
        "    ok.\n">>,
 
525
          default,
 
526
          ok},
 
527
 
 
528
         {ex_7, %% Assumes regexp can handle \x
 
529
      <<"Definitions.\n"
 
530
        "H1 = \\x11\\x{ab}\n"
 
531
        "H2 = [\\x{30}\\x{ac}]\n"
 
532
        "Rules.\n"
 
533
        "{H1}{H2}+ : {token,{hex,TokenChars}}.\n"
 
534
        "Erlang code.\n"
 
535
        "-export([t/0]).\n"
 
536
        "t() ->\n"
 
537
        "    {ok,[{hex,[17,171,48,172]}],1} =\n"
 
538
        "        string(\"\\x{11}\\xab0\\xac\"),\n"
 
539
        "    ok.\n">>,
 
540
          default,
 
541
          ok}],
 
542
    
 
543
    ?line run(Config, Ts),
 
544
    ok.
 
545
 
 
546
ex2(doc) ->
 
547
    "More examples.";
 
548
ex2(suite) -> [];
 
549
ex2(Config) when is_list(Config) ->
 
550
    Xrl = 
 
551
     <<"
 
552
%%% File : erlang_scan.xrl
 
553
%%% Author : Robert Virding
 
554
%%% Purpose : Tkoen definitions for Erlang.
 
555
 
 
556
Definitions.
 
557
O  = [0-7]
 
558
D  = [0-9]
 
559
H  = [0-9a-fA-F]
 
560
U  = [A-Z]
 
561
L  = [a-z]
 
562
A  = ({U}|{L}|{D}|_|@)
 
563
WS  = ([\\000-\\s]|%.*)
 
564
 
 
565
Rules.
 
566
{D}+\\.{D}+((E|e)(\\+|\\-)?{D}+)? :
 
567
      {token,{float,TokenLine,list_to_float(TokenChars)}}.
 
568
{D}+#{H}+  :  base(TokenLine, TokenChars).
 
569
{D}+    :  {token,{integer,TokenLine,list_to_integer(TokenChars)}}.
 
570
{L}{A}*    :  Atom = list_to_atom(TokenChars),
 
571
      {token,case reserved_word(Atom) of
 
572
         true -> {Atom,TokenLine};
 
573
         false -> {atom,TokenLine,Atom}
 
574
       end}.
 
575
'(\\\\\\^.|\\\\.|[^'])*' :
 
576
      %% Strip quotes.
 
577
      S = lists:sublist(TokenChars, 2, TokenLen - 2),
 
578
      case catch list_to_atom(string_gen(S)) of
 
579
       {'EXIT',_} -> {error,\"illegal atom \" ++ TokenChars};
 
580
       Atom -> {token,{atom,TokenLine,Atom}}
 
581
      end.
 
582
({U}|_){A}*  :  {token,{var,TokenLine,list_to_atom(TokenChars)}}.
 
583
\"(\\\\\\^.|\\\\.|[^\"])*\" :
 
584
      %% Strip quotes.
 
585
      S = lists:sublist(TokenChars, 2, TokenLen - 2),
 
586
      {token,{string,TokenLine,string_gen(S)}}.
 
587
\\$(\\\\{O}{O}{O}|\\\\\\^.|\\\\.|.) :
 
588
      {token,{char,TokenLine,cc_convert(TokenChars)}}.
 
589
->    :  {token,{'->',TokenLine}}.
 
590
:-    :  {token,{':-',TokenLine}}.
 
591
\\|\\|    :  {token,{'||',TokenLine}}.
 
592
<-    :  {token,{'<-',TokenLine}}.
 
593
\\+\\+    :  {token,{'++',TokenLine}}.
 
594
--    :  {token,{'--',TokenLine}}.
 
595
=/=    :  {token,{'=/=',TokenLine}}.
 
596
==    :  {token,{'==',TokenLine}}.
 
597
=:=    :  {token,{'=:=',TokenLine}}.
 
598
/=    :  {token,{'/=',TokenLine}}.
 
599
>=    :  {token,{'>=',TokenLine}}.
 
600
=<    :  {token,{'=<',TokenLine}}.
 
601
<=    :  {token,{'<=',TokenLine}}.
 
602
<<    :  {token,{'<<',TokenLine}}.
 
603
>>    :  {token,{'>>',TokenLine}}.
 
604
::    :  {token,{'::',TokenLine}}.
 
605
[]()[}{|!?/;:,.*+#<>=-] :
 
606
      {token,{list_to_atom(TokenChars),TokenLine}}.
 
607
\\.{WS}    :  {end_token,{dot,TokenLine}}.
 
608
{WS}+    :  skip_token.
 
609
 
 
610
Erlang code.
 
611
 
 
612
-export([reserved_word/1]).
 
613
 
 
614
%% reserved_word(Atom) -> Bool
 
615
%% return 'true' if Atom is an Erlang reserved word, else 'false'.
 
616
 
 
617
reserved_word('after') -> true;
 
618
reserved_word('begin') -> true;
 
619
reserved_word('case') -> true;
 
620
reserved_word('try') -> true;
 
621
reserved_word('cond') -> true;
 
622
reserved_word('catch') -> true;
 
623
reserved_word('andalso') -> true;
 
624
reserved_word('orelse') -> true;
 
625
reserved_word('end') -> true;
 
626
reserved_word('fun') -> true;
 
627
reserved_word('if') -> true;
 
628
reserved_word('let') -> true;
 
629
reserved_word('of') -> true;
 
630
reserved_word('query') -> true;
 
631
reserved_word('receive') -> true;
 
632
reserved_word('when') -> true;
 
633
reserved_word('bnot') -> true;
 
634
reserved_word('not') -> true;
 
635
reserved_word('div') -> true;
 
636
reserved_word('rem') -> true;
 
637
reserved_word('band') -> true;
 
638
reserved_word('and') -> true;
 
639
reserved_word('bor') -> true;
 
640
reserved_word('bxor') -> true;
 
641
reserved_word('bsl') -> true;
 
642
reserved_word('bsr') -> true;
 
643
reserved_word('or') -> true;
 
644
reserved_word('xor') -> true;
 
645
reserved_word('spec') -> true;
 
646
reserved_word(_) -> false.
 
647
 
 
648
base(L, Cs) ->
 
649
    H = string:chr(Cs, $#),
 
650
    case list_to_integer(string:substr(Cs, 1, H-1)) of
 
651
        B when B > 16 -> {error,\"illegal base\"};
 
652
        B ->
 
653
            case base(string:substr(Cs, H+1), B, 0) of
 
654
                error -> {error,\"illegal based number\"};
 
655
                N -> {token,{integer,L,N}}
 
656
            end
 
657
    end.
 
658
 
 
659
base([C|Cs], Base, SoFar) when C >= $0, C =< $9, C < Base + $0 ->
 
660
    Next = SoFar * Base + (C - $0),
 
661
    base(Cs, Base, Next);
 
662
base([C|Cs], Base, SoFar) when C >= $a, C =< $f, C < Base + $a - 10 ->
 
663
    Next = SoFar * Base + (C - $a + 10),
 
664
    base(Cs, Base, Next);
 
665
base([C|Cs], Base, SoFar) when C >= $A, C =< $F, C < Base + $A - 10 ->
 
666
    Next = SoFar * Base + (C - $A + 10),
 
667
    base(Cs, Base, Next);
 
668
base([_|_], _, _) -> error;      %Unknown character
 
669
base([], _, N) -> N.
 
670
 
 
671
cc_convert([$$,$\\\\|Cs]) ->
 
672
    hd(string_escape(Cs));
 
673
cc_convert([$$,C]) -> C.
 
674
 
 
675
string_gen([$\\\\|Cs]) ->
 
676
    string_escape(Cs);
 
677
string_gen([C|Cs]) ->
 
678
    [C|string_gen(Cs)];
 
679
string_gen([]) -> [].
 
680
 
 
681
string_escape([O1,O2,O3|S]) when
 
682
        O1 >= $0, O1 =< $7, O2 >= $0, O2 =< $7, O3 >= $0, O3 =< $7 ->
 
683
    [(O1*8 + O2)*8 + O3 - 73*$0|string_gen(S)];
 
684
string_escape([$^,C|Cs]) ->
 
685
    [C band 31|string_gen(Cs)];
 
686
string_escape([C|Cs]) when C >= $\\000, C =< $\\s ->
 
687
    string_gen(Cs);
 
688
string_escape([C|Cs]) ->
 
689
    [escape_char(C)|string_gen(Cs)].
 
690
 
 
691
escape_char($n) -> $\\n;        %\\n = LF
 
692
escape_char($r) -> $\\r;        %\\r = CR
 
693
escape_char($t) -> $\\t;        %\\t = TAB
 
694
escape_char($v) -> $\\v;        %\\v = VT
 
695
escape_char($b) -> $\\b;        %\\b = BS
 
696
escape_char($f) -> $\\f;        %\\f = FF
 
697
escape_char($e) -> $\\e;        %\\e = ESC
 
698
escape_char($s) -> $\\s;        %\\s = SPC
 
699
escape_char($d) -> $\\d;        %\\d = DEL
 
700
escape_char(C) -> C.
 
701
      ">>,
 
702
    Dir = ?privdir,
 
703
    XrlFile = filename:join(Dir, "erlang_scan.xrl"),
 
704
    ?line ok = file:write_file(XrlFile, Xrl),
 
705
    ErlFile = filename:join(Dir, "erlang_scan.erl"),
 
706
    ?line {ok, _} = leex:file(XrlFile, []),
 
707
    ?line {ok, _} = compile:file(ErlFile, [{outdir,Dir}]),
 
708
    code:purge(erlang_scan),
 
709
    AbsFile = filename:rootname(ErlFile, ".erl"),
 
710
    code:load_abs(AbsFile, erlang_scan),
 
711
 
 
712
    F = fun(Cont, Chars, Location) ->
 
713
                erlang_scan:tokens(Cont, Chars, Location)
 
714
        end,
 
715
    F1 = fun(Cont, Chars, Location) ->
 
716
                 erlang_scan:token(Cont, Chars, Location)
 
717
         end,
 
718
    fun() ->
 
719
            S = "ab cd. ",
 
720
            {ok, Ts, 1} = scan_tokens_1(S, F, 1),
 
721
            {ok, Ts, 1} = scan_token_1(S, F1, 1),
 
722
            {ok, Ts, 1} = scan_tokens(S, F, 1),
 
723
            {ok, Ts, 1} = erlang_scan:string(S, 1)
 
724
    end(),
 
725
    fun() ->
 
726
            S = "'ab\n cd'. ",
 
727
            {ok, Ts, 2} = scan_tokens_1(S, F, 1),
 
728
            {ok, Ts, 2} = scan_token_1(S, F1, 1),
 
729
            {ok, Ts, 2} = scan_tokens(S, F, 1),
 
730
            {ok, Ts, 2} = erlang_scan:string(S, 1)
 
731
    end(),
 
732
    fun() ->
 
733
            S = "99. ",
 
734
            {ok, Ts, 1} = scan_tokens_1(S, F, 1),
 
735
            {ok, Ts, 1} = scan_token_1(S, F1, 1),
 
736
            {ok, Ts, 1} = scan_tokens(S, F, 1),
 
737
            {ok, Ts, 1} = erlang_scan:string(S, 1)
 
738
    end(),
 
739
    {ok,[{integer,1,99},{dot,1}],1} = erlang_scan:string("99. "),
 
740
    fun() ->
 
741
            Atom = "'" ++ lists:duplicate(1000,$a) ++ "'",
 
742
            S = Atom ++ ". ",
 
743
            Reason = "illegal atom " ++ Atom,
 
744
            Err = {error,{1,erlang_scan,{user,Reason}},1},
 
745
            {done,Err,[]} = scan_tokens_1(S, F, 1),
 
746
            {done,Err,[]} = scan_token_1(S, F1, 1),
 
747
            {done,Err,[]} = scan_tokens(S, F, 1),
 
748
            Err = erlang_scan:string(S, 1)
 
749
    end(),
 
750
    fun() ->
 
751
            S = "\x{aaa}. ",
 
752
            Err = {error,{1,erlang_scan,{illegal,[2730]}},1},
 
753
            {done,Err,[]} = scan_tokens_1(S, F, 1),
 
754
            {done,Err,[_]} = scan_token_1(S, F1, 1), % Note: Rest non-empty
 
755
            {done,Err,[]} = scan_tokens(S, F, 1),
 
756
            Err = erlang_scan:string(S, 1)
 
757
    end(),
 
758
    fun() ->
 
759
            S = "\x{aaa} + 1. 34",
 
760
            Err = {error,{1,erlang_scan,{illegal,[2730]}},1},
 
761
            {done,Err,[]} = scan_tokens_1(S, F, 1),
 
762
            {done,Err,[_]} = scan_token_1(S, F1, 1), % Note: Rest non-empty
 
763
            {done,Err,"34"} = scan_tokens(S, F, 1),
 
764
            Err = erlang_scan:string(S, 1)
 
765
    end(),
 
766
    fun() ->
 
767
            S = "\x{aaa} \x{bbb}. 34",
 
768
            Err = {error,{1,erlang_scan,{illegal,[2730]}},1},
 
769
            {done,Err,[]} = scan_tokens_1(S, F, 1),
 
770
            {done,Err,[_]} = scan_token_1(S, F1, 1), % Note: Rest non-empty
 
771
            {done,Err,"34"} = scan_tokens(S, F, 1),
 
772
            Err = erlang_scan:string(S, 1)
 
773
    end(),
 
774
    fun() ->
 
775
            S = "\x{aaa} 18#34. 34",
 
776
            Err = {error,{1,erlang_scan,{illegal,[2730]}},1},
 
777
            {done,Err,[]} = scan_tokens_1(S, F, 1),
 
778
            {done,Err,[_]} = scan_token_1(S, F1, 1), % Note: Rest non-empty
 
779
            {done,Err,"34"} = scan_tokens(S, F, 1),
 
780
            Err = erlang_scan:string(S, 1)
 
781
    end(),
 
782
    fun() ->
 
783
            S = "\x{aaa}"++eof,
 
784
            Err = {error,{1,erlang_scan,{illegal,[2730]}},1},
 
785
            {done,Err,eof} = scan_tokens_1(S, F, 1),
 
786
            {done,Err,[_]} = scan_token_1(S, F1, 1), % Note: Rest non-empty
 
787
            {done,Err,eof} = scan_tokens(S, F, 1),
 
788
            Err = erlang_scan:string(S, 1)
 
789
    end(),
 
790
    ok.
 
791
 
 
792
scan_tokens(String, Fun, Location) ->
 
793
    scan_tokens(String, Fun, Location, []).
 
794
 
 
795
scan_tokens(String, Fun, Location, Rs) ->
 
796
    case Fun([], String, Location) of
 
797
        {done, {error,_,_}, _} = Error ->
 
798
            Error;
 
799
        {done, {ok,Ts,End}, ""} ->
 
800
            {ok, lists:append(lists:reverse([Ts|Rs])), End};
 
801
        {done, {ok,Ts,End}, Rest} ->
 
802
            scan_tokens(Rest, Fun, End, [Ts|Rs])
 
803
    end.
 
804
 
 
805
scan_tokens_1(String, Fun, Location) ->
 
806
    scan_tokens_1({more, []}, String, Fun, Location, []).
 
807
 
 
808
scan_tokens_1({done, {error, _, _}, _}=Error, _Cs, _Fun, _Location, _Rs) ->
 
809
    Error;
 
810
scan_tokens_1({done, {ok,Ts,End}, ""}, "", _Fun, _Location, Rs) ->
 
811
    {ok,lists:append(lists:reverse([Ts|Rs])),End};
 
812
scan_tokens_1({done, {ok,Ts,End}, Rest}, Cs, Fun, _Location, Rs) ->
 
813
    scan_tokens_1({more,[]}, Rest++Cs, Fun, End, [Ts|Rs]);
 
814
scan_tokens_1({more, Cont}, [C | Cs], Fun, Loc, Rs) ->
 
815
    R = Fun(Cont, [C], Loc),
 
816
    scan_tokens_1(R, Cs, Fun, Loc, Rs);
 
817
scan_tokens_1({more, Cont}, eof, Fun, Loc, Rs) ->
 
818
    R = Fun(Cont, eof, Loc),
 
819
    scan_tokens_1(R, eof, Fun, Loc, Rs).
 
820
 
 
821
scan_token_1(String, Fun, Location) ->
 
822
    scan_token_1({more, []}, String, Fun, Location, []).
 
823
 
 
824
scan_token_1({done, {error, _, _}, _}=Error, _Cs, _Fun, _Location, _Rs) ->
 
825
    Error;
 
826
scan_token_1({done, {ok,Ts,End}, ""}, "", _Fun, _Location, Rs) ->
 
827
    {ok,lists:reverse([Ts|Rs]),End};
 
828
scan_token_1({done, {ok,Ts,End}, Rest}, Cs, Fun, _Location, Rs) ->
 
829
    scan_token_1({more,[]}, Rest++Cs, Fun, End, [Ts|Rs]);
 
830
scan_token_1({more, Cont}, [C | Cs], Fun, Loc, Rs) ->
 
831
    R = Fun(Cont, [C], Loc),
 
832
    scan_token_1(R, Cs, Fun, Loc, Rs).
 
833
 
 
834
%% End of ex2
 
835
 
 
836
not_yet(doc) ->
 
837
    "Not yet implemented.";
 
838
not_yet(suite) -> [];
 
839
not_yet(Config) when is_list(Config) ->
 
840
    Dir = ?privdir,
 
841
    Filename = filename:join(Dir, "file.xrl"),
 
842
    Ret = [return, {report, true}],
 
843
    ?line ok = file:write_file(Filename,
 
844
                               <<"Definitions.\n"
 
845
                                 "Rules.\n"
 
846
                                 "$ : .\n"
 
847
                                 "Erlang code.\n">>),
 
848
    ?line {error,[{_,[{3,leex,{regexp,_}}]}],[]} = 
 
849
        leex:file(Filename, Ret),
 
850
    ?line ok = file:write_file(Filename,
 
851
                               <<"Definitions.\n"
 
852
                                 "Rules.\n"
 
853
                                 "^ : .\n"
 
854
                                 "Erlang code.\n">>),
 
855
    ?line {error,[{_,[{3,leex,{regexp,_}}]}],[]} = 
 
856
        leex:file(Filename, Ret),
 
857
 
 
858
    ok.
 
859
 
 
860
unwritable(Fname) ->
 
861
    {ok, Info} = file:read_file_info(Fname),
 
862
    Mode = Info#file_info.mode - 8#00200,
 
863
    ok = file:write_file_info(Fname, Info#file_info{mode = Mode}).
 
864
 
 
865
writable(Fname) ->
 
866
    {ok, Info} = file:read_file_info(Fname),
 
867
    Mode = Info#file_info.mode bor 8#00200,
 
868
    ok = file:write_file_info(Fname, Info#file_info{mode = Mode}).
 
869
 
 
870
run(Config, Tests) ->
 
871
    F = fun({N,P,Pre,E}) ->
 
872
                case catch run_test(Config, P, Pre) of
 
873
                    E -> 
 
874
                        ok;
 
875
                    Bad -> 
 
876
                        ?t:format("~nTest ~p failed. Expected~n  ~p~n"
 
877
                                  "but got~n  ~p~n", [N, E, Bad]),
 
878
                        fail()
 
879
                end
 
880
        end,
 
881
    lists:foreach(F, Tests).
 
882
 
 
883
run_test(Config, Def, Pre) ->
 
884
    %% io:format("testing ~s~n", [binary_to_list(Def)]),
 
885
    DefFile = 'leex_test.xrl',
 
886
    Filename = 'leex_test.erl',
 
887
    DataDir = ?privdir,
 
888
    XrlFile = filename:join(DataDir, DefFile),
 
889
    ErlFile = filename:join(DataDir, Filename),
 
890
    Opts = [return, warn_unused_vars,{outdir,DataDir}],
 
891
    ok = file:write_file(XrlFile, Def),
 
892
    LOpts = [return, {report, false} | 
 
893
             case Pre of
 
894
                 default ->
 
895
                     [];
 
896
                 _ ->
 
897
                     [{includefile,Pre}]
 
898
             end],
 
899
    XOpts = [verbose, dfa_graph], % just to get some code coverage...
 
900
    LRet = leex:file(XrlFile, XOpts ++ LOpts),
 
901
    case LRet of
 
902
        {ok, _Outfile, _LWs} ->
 
903
                 CRet = compile:file(ErlFile, Opts),
 
904
                 case CRet of
 
905
                     {ok, _M, _Ws} -> 
 
906
                         AbsFile = filename:rootname(ErlFile, ".erl"),
 
907
                         Mod = leex_test,
 
908
                         code:purge(Mod),
 
909
                         code:load_abs(AbsFile, Mod),
 
910
                         Mod:t();
 
911
                         %% warnings(ErlFile, Ws);
 
912
                     {error, [{ErlFile,Es}], []} -> {error, Es, []};
 
913
                     {error, [{ErlFile,Es}], [{ErlFile,Ws}]} -> {error, Es, Ws};
 
914
                     Error  -> Error
 
915
                 end;
 
916
        {error, [{XrlFile,LEs}], []} -> {error, LEs, []};
 
917
        {error, [{XrlFile,LEs}], [{XrlFile,LWs}]} -> {error, LEs, LWs};
 
918
        LError -> LError
 
919
    end.
 
920
 
 
921
extract(File, {error, Es, Ws}) ->
 
922
    {errors, extract(File, Es), extract(File, Ws)};    
 
923
extract(File, Ts) ->
 
924
    lists:append([T || {F, T} <- Ts,  F =:= File]).
 
925
 
 
926
fail() ->
 
927
    ?t:fail().