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

« back to all changes in this revision

Viewing changes to lib/kernel/test/file_name_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
-module(file_name_SUITE).
 
2
%%
 
3
%% %CopyrightBegin%
 
4
%%
 
5
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
6
%%
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%%
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%%
 
18
%% %CopyrightEnd%
 
19
%%
 
20
 
 
21
-include_lib("test_server/include/test_server.hrl").
 
22
-include_lib("kernel/include/file.hrl").
 
23
 
 
24
%%
 
25
%% File operations that take filenames as parameters (* not prim_file operation) (** a drive):
 
26
%% altname
 
27
%% copy (*)
 
28
%% del_dir
 
29
%% delete
 
30
%% get_cwd (**)
 
31
%% list_dir
 
32
%% make_dir
 
33
%% make_link
 
34
%% make_symlink
 
35
%% open
 
36
%% read_file
 
37
%% read_file_info
 
38
%% read_link
 
39
%% read_link_info
 
40
%% rename
 
41
%% set_cwd
 
42
%% write_file
 
43
%% write_file_info
 
44
%%
 
45
%% File operations that opens/uses separate driver port (not connected to file)
 
46
%% altname
 
47
%% del_dir
 
48
%% delete
 
49
%% get_cwd
 
50
%% list_dir
 
51
%% make_dir
 
52
%% make_link
 
53
%% make_symlink
 
54
%% read_file_info
 
55
%% read_link
 
56
%% read_link_info
 
57
%% rename
 
58
%% set_cwd
 
59
%% write_file_info
 
60
%% 
 
61
%% Operations that use ?FD_DRV in prim_file
 
62
%% open
 
63
%% read_file
 
64
%% write_file
 
65
%%
 
66
%%
 
67
%% Operations that return a filename/path
 
68
%% altname
 
69
%% get_cwd
 
70
%% list_dir
 
71
%% read_link
 
72
 
 
73
-export([all/0,groups/0,suite/0,
 
74
         init_per_suite/1,end_per_suite/1,
 
75
         init_per_group/2,end_per_group/2,
 
76
         init_per_testcase/2, end_per_testcase/2]).
 
77
-export([normal/1,icky/1,very_icky/1,normalize/1]).
 
78
 
 
79
 
 
80
init_per_testcase(_Func, Config) ->
 
81
    Dog = test_server:timetrap(test_server:seconds(60)),
 
82
    [{watchdog,Dog}|Config].
 
83
 
 
84
end_per_testcase(_Func, Config) ->
 
85
    Dog = ?config(watchdog, Config),
 
86
    test_server:timetrap_cancel(Dog).
 
87
 
 
88
suite() -> [{ct_hooks,[ts_install_cth]}].
 
89
 
 
90
all() -> 
 
91
    [normal, icky, very_icky, normalize].
 
92
 
 
93
groups() -> 
 
94
    [].
 
95
 
 
96
init_per_suite(Config) ->
 
97
    Config.
 
98
 
 
99
end_per_suite(_Config) ->
 
100
    ok.
 
101
 
 
102
init_per_group(_GroupName, Config) ->
 
103
        Config.
 
104
 
 
105
end_per_group(_GroupName, Config) ->
 
106
        Config.
 
107
 
 
108
normalize(suite) ->
 
109
    [];
 
110
normalize(doc) ->
 
111
    ["Check that filename normalization works"];
 
112
normalize(Config) when is_list(Config) ->
 
113
    random:seed({1290,431421,830412}),
 
114
    try
 
115
        ?line UniMode = file:native_name_encoding() =/= latin1,
 
116
        if 
 
117
            not UniMode ->
 
118
                throw(need_unicode_mode);
 
119
            true ->
 
120
                ok
 
121
        end,
 
122
        ?line Pairs = [rand_comp_decomp(200) || _ <- lists:seq(1,1000)],
 
123
        case os:type() of
 
124
            {unix,darwin} ->
 
125
                ?line [ true = (A =:= prim_file:internal_native2name(B)) ||
 
126
                    {A,B} <- Pairs ];
 
127
            _ ->
 
128
                ok
 
129
        end,
 
130
        ?line [ true = (A =:= prim_file:internal_normalize_utf8(B)) ||
 
131
                  {A,B} <- Pairs ]
 
132
        
 
133
    catch
 
134
        throw:need_unicode_mode ->
 
135
            io:format("Sorry, can only run in unicode mode.~n"),
 
136
            {skipped,"VM needs to be started in Unicode filename mode"}
 
137
    end.
 
138
    
 
139
normal(suite) ->
 
140
    [];
 
141
normal(doc) ->
 
142
    "Check file operations on normal file names regardless of unicode mode";
 
143
normal(Config) when is_list(Config) ->
 
144
    {ok,Dir} = file:get_cwd(),
 
145
    try
 
146
        Priv = ?config(priv_dir, Config),
 
147
        file:set_cwd(Priv),
 
148
        put(file_module,prim_file),
 
149
        ok = check_normal(prim_file),
 
150
        put(file_module,file),
 
151
        ok = check_normal(file)
 
152
    after
 
153
        file:set_cwd(Dir)
 
154
    end.
 
155
    
 
156
 
 
157
icky(suite) ->
 
158
    [];
 
159
icky(doc) ->
 
160
    "Check file operations on normal file names regardless of unicode mode";
 
161
icky(Config) when is_list(Config) ->
 
162
    case hopeless_darwin() of
 
163
        true ->
 
164
            {skipped,"This version of darwin does not support icky names at all."};
 
165
        false ->
 
166
            {ok,Dir} = file:get_cwd(),
 
167
            try
 
168
                Priv = ?config(priv_dir, Config),
 
169
                file:set_cwd(Priv),
 
170
                put(file_module,prim_file),
 
171
                ok = check_icky(prim_file),
 
172
                put(file_module,file),
 
173
                ok = check_icky(file)
 
174
            after
 
175
                file:set_cwd(Dir)
 
176
            end
 
177
    end.
 
178
very_icky(suite) ->
 
179
    [];
 
180
very_icky(doc) ->
 
181
    "Check file operations on normal file names regardless of unicode mode";
 
182
very_icky(Config) when is_list(Config) ->
 
183
    case hopeless_darwin() of
 
184
        true ->
 
185
            {skipped,"This version of darwin does not support icky names at all."};
 
186
        false ->
 
187
            {ok,Dir} = file:get_cwd(),
 
188
            try
 
189
                Priv = ?config(priv_dir, Config),
 
190
                file:set_cwd(Priv),
 
191
                put(file_module,prim_file),
 
192
                case check_very_icky(prim_file) of
 
193
                    need_unicode_mode ->
 
194
                        {skipped,"VM needs to be started in Unicode filename mode"};
 
195
                    ok ->
 
196
                        put(file_module,file),
 
197
                        ok = check_very_icky(file)
 
198
                end
 
199
            after
 
200
                file:set_cwd(Dir)
 
201
            end
 
202
    end.
 
203
    
 
204
 
 
205
check_normal(Mod) -> 
 
206
    {ok,Dir} = Mod:get_cwd(),
 
207
    try
 
208
        ?line make_normal_dir(Mod),
 
209
        ?line {ok, L0} = Mod:list_dir("."),
 
210
        ?line L1 = lists:sort(L0),
 
211
        %erlang:display(L1),
 
212
        ?line L1 = lists:sort(list(normal_dir())),
 
213
        ?line {ok,D2} = Mod:get_cwd(),
 
214
        ?line true = is_list(D2),
 
215
        ?line case Mod:altname("fil1") of
 
216
            {error,enotsup} ->
 
217
                ok;
 
218
            {ok,LLL} when is_list(LLL) ->
 
219
                ok
 
220
        end,
 
221
        ?line [ true = is_list(El) || El <- L1],
 
222
        ?line Syms = [ {S,Targ,list_to_binary(get_data(Targ,normal_dir()))} 
 
223
                 || {T,S,Targ} <- normal_dir(), T =:= symlink ],
 
224
        ?line [ {ok, Cont} = Mod:read_file(SymL) || {SymL,_,Cont} <- Syms ],
 
225
        ?line [ {ok, Targ} = fixlink(Mod:read_link(SymL)) || {SymL,Targ,_} <- Syms ],
 
226
        ?line chk_cre_dir(Mod,[{directory,"temp_dir",normal_dir()}]),
 
227
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
228
        ?line true = is_list(BeginAt),
 
229
        ?line {error,enoent} = Mod:set_cwd("tmp_dir"),
 
230
        ?line ok = Mod:set_cwd("temp_dir"),
 
231
        ?line {ok, NowAt} = Mod:get_cwd(),
 
232
        ?line true = BeginAt =/= NowAt,
 
233
        ?line ok = Mod:set_cwd(".."),
 
234
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
235
        ?line rm_r(Mod,"temp_dir"),
 
236
        ?line true = is_list(Dir),
 
237
        ?line [ true = is_list(FN) || FN <- L0 ],
 
238
        case has_links() of
 
239
            true ->
 
240
                ?line ok = Mod:make_link("fil1","nisse"),
 
241
                ?line {ok, <<"fil1">>} = Mod:read_file("nisse"),
 
242
                ?line {ok, #file_info{type = regular}} = Mod:read_link_info("nisse"),
 
243
                ?line ok = Mod:delete("nisse"),
 
244
                ?line {ok, <<"fil1">>} = Mod:read_file("fil1"),
 
245
                ?line {error,enoent} = Mod:read_file("nisse"),
 
246
                ?line {error,enoent} = Mod:read_link_info("nisse");
 
247
            false ->
 
248
                ok
 
249
        end,
 
250
        ?line [ begin
 
251
              ?line {ok, FD} = Mod:open(Name,[read]),
 
252
              ?line {ok, Content} = Mod:read(FD,1024),
 
253
              ?line ok = file:close(FD)
 
254
          end || {regular,Name,Content} <- normal_dir() ],
 
255
        ?line [ begin
 
256
              ?line {ok, FD} = Mod:open(Name,[read,binary]),
 
257
              ?line BC = list_to_binary(Content),
 
258
              ?line {ok, BC} = Mod:read(FD,1024),
 
259
              ?line ok = file:close(FD)
 
260
          end || {regular,Name,Content} <- normal_dir() ],
 
261
        ?line Mod:rename("fil1","tmp_fil1"),
 
262
        ?line {ok, <<"fil1">>} = Mod:read_file("tmp_fil1"),
 
263
        ?line {error,enoent} = Mod:read_file("fil1"),
 
264
        ?line Mod:rename("tmp_fil1","fil1"),
 
265
        ?line {ok, <<"fil1">>} = Mod:read_file("fil1"),
 
266
        ?line {error,enoent} = Mod:read_file("tmp_fil1"),
 
267
        ?line {ok,FI} = Mod:read_file_info("fil1"),
 
268
        ?line NewMode = FI#file_info.mode band (bnot 8#333),
 
269
        ?line NewMode2 = NewMode bor 8#222,
 
270
        ?line true = NewMode2 =/= NewMode,
 
271
        ?line ok = Mod:write_file_info("fil1",FI#file_info{mode = NewMode}),
 
272
        ?line {ok,#file_info{mode = NewMode}} = Mod:read_file_info("fil1"),
 
273
        ?line ok = Mod:write_file_info("fil1",FI#file_info{mode = NewMode2}),
 
274
        ?line {ok,#file_info{mode = NewMode2}} = Mod:read_file_info("fil1"),
 
275
        ok
 
276
    after
 
277
        case Mod:read_file_info("fil1") of
 
278
            {ok,FII} ->
 
279
                NewModeI = FII#file_info.mode bor 8#777,
 
280
                Mod:write_file_info("fil1",FII#file_info{mode = NewModeI});
 
281
            _ ->
 
282
                ok
 
283
        end,
 
284
        Mod:set_cwd(Dir),
 
285
        io:format("Wd now: ~s~n",[Dir])
 
286
    end.
 
287
 
 
288
check_icky(Mod) -> 
 
289
    {ok,Dir} = Mod:get_cwd(),
 
290
    try
 
291
        ?line true=(length("���") =:= 3),
 
292
        ?line UniMode = file:native_name_encoding() =/= latin1,
 
293
        ?line make_icky_dir(Mod),
 
294
        ?line {ok, L0} = Mod:list_dir("."),
 
295
        ?line L1 = lists:sort(L0),
 
296
        io:format("~p ~p~n",[L1,list(icky_dir())]),
 
297
        ?line L1 = lists:sort(convlist(list(icky_dir()))),
 
298
        ?line {ok,D2} = Mod:get_cwd(),
 
299
        ?line true = is_list(D2),
 
300
%% Altname only on windows, and there are no non native filenames there
 
301
%%      ?line case Mod:altname("fil1") of
 
302
%%          {error,enotsup} ->
 
303
%%              ok;
 
304
%%          {ok,LLL} when is_list(LLL) ->
 
305
%%              ok
 
306
%%      end,
 
307
        ?line [ true = ((is_list(El) or (UniMode and is_binary(El))))  || El <- L1],
 
308
        ?line Syms = [ {S,conv(Targ),list_to_binary(get_data(Targ,icky_dir()))} 
 
309
                 || {T,S,Targ} <- icky_dir(), T =:= symlink ],
 
310
        ?line [ {ok, Cont} = Mod:read_file(SymL) || {SymL,_,Cont} <- Syms ],
 
311
        ?line [ {ok, Targ} = fixlink(Mod:read_link(SymL)) || {SymL,Targ,_} <- Syms ],
 
312
        ?line chk_cre_dir(Mod,[{directory,"���_dir",icky_dir()}]),
 
313
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
314
        ?line true = is_list(BeginAt),
 
315
        ?line {error,enoent} = Mod:set_cwd("��_dir"),
 
316
        ?line ok = Mod:set_cwd("���_dir"),
 
317
        ?line {ok, NowAt} = Mod:get_cwd(),
 
318
        ?line true = is_list(NowAt),
 
319
        ?line true = BeginAt =/= NowAt,
 
320
        ?line ok = Mod:set_cwd(".."),
 
321
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
322
        ?line rm_r2(Mod,"���_dir"),
 
323
        {OS,TYPE} = os:type(),
 
324
        % Check that treat_icky really converts to the same as the OS
 
325
        case UniMode of
 
326
            true ->
 
327
                ?line chk_cre_dir(Mod,[{directory,"���_dir",[]}]),
 
328
                ?line ok = Mod:set_cwd("���_dir"),
 
329
                ?line ok = Mod:write_file(<<"���">>,<<"hello">>),
 
330
                ?line Treated = treat_icky(<<"���">>),
 
331
                ?line {ok,[Treated]} = Mod:list_dir("."),
 
332
                ?line ok = Mod:delete(<<"���">>),
 
333
                ?line {ok,[]} = Mod:list_dir("."),
 
334
                ?line ok = Mod:set_cwd(".."),
 
335
                ?line rm_r2(Mod,"���_dir");
 
336
            false ->
 
337
                ok
 
338
        end,
 
339
 
 
340
        ?line chk_cre_dir(Mod,[{directory,treat_icky(<<"���_dir">>),icky_dir()}]),
 
341
        if 
 
342
            UniMode and (OS =/= win32) ->
 
343
                ?line {error,enoent} = Mod:set_cwd("���_dir");
 
344
            true ->
 
345
                ok
 
346
        end,
 
347
        ?line ok = Mod:set_cwd(treat_icky(<<"���_dir">>)),
 
348
        ?line {ok, NowAt2} = Mod:get_cwd(),
 
349
        io:format("~p~n",[NowAt2]),
 
350
        % Cannot create raw unicode-breaking filenames on windows or macos
 
351
        ?line true = ((((not UniMode) or (OS =:= win32) or (TYPE=:=darwin)) and is_list(NowAt2)) orelse ((UniMode) and is_binary(NowAt2))),
 
352
        ?line true = BeginAt =/= NowAt2,
 
353
        ?line ok = Mod:set_cwd(".."),
 
354
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
355
        ?line rm_r2(Mod,conv(treat_icky(<<"���_dir">>))),
 
356
        case has_links() of
 
357
            true ->
 
358
                ?line ok = Mod:make_link("fil1","nisse�"),
 
359
                ?line {ok, <<"fil1">>} = Mod:read_file("nisse�"),
 
360
                ?line {ok, #file_info{type = regular}} = Mod:read_link_info("nisse�"),
 
361
                ?line ok = Mod:delete("nisse�"),
 
362
                ?line ok = Mod:make_link("fil1",treat_icky(<<"nisse�">>)),
 
363
                ?line {ok, <<"fil1">>} = Mod:read_file(treat_icky(<<"nisse�">>)),
 
364
                ?line {ok, #file_info{type = regular}} = Mod:read_link_info(treat_icky(<<"nisse�">>)),
 
365
                ?line ok = Mod:delete(treat_icky(<<"nisse�">>)),
 
366
                ?line {ok, <<"fil1">>} = Mod:read_file("fil1"),
 
367
                ?line {error,enoent} = Mod:read_file("nisse�"),
 
368
                ?line {error,enoent} = Mod:read_link_info("nisse�"),
 
369
                ?line {error,enoent} = Mod:read_file(treat_icky(<<"nisse�">>)),
 
370
                ?line {error,enoent} = Mod:read_link_info(treat_icky(<<"nisse�">>));
 
371
            false ->
 
372
                ok
 
373
        end,
 
374
        ?line [ begin
 
375
              ?line {ok, FD} = Mod:open(Name,[read]),
 
376
              ?line {ok, Content} = Mod:read(FD,1024),
 
377
              ?line ok = file:close(FD)
 
378
          end || {regular,Name,Content} <- icky_dir() ],
 
379
        ?line [ begin
 
380
              ?line {ok, FD} = Mod:open(Name,[read,binary]),
 
381
              ?line BC = list_to_binary([Content]),
 
382
              ?line {ok, BC} = Mod:read(FD,1024),
 
383
              ?line ok = file:close(FD)
 
384
          end || {regular,Name,Content} <- icky_dir() ],
 
385
        ?line Mod:rename("���2","���_fil1"),
 
386
        ?line {ok, <<"���2">>} = Mod:read_file("���_fil1"),
 
387
        ?line {error,enoent} = Mod:read_file("���2"),
 
388
        ?line Mod:rename("���_fil1","���2"),
 
389
        ?line {ok, <<"���2">>} = Mod:read_file("���2"),
 
390
        ?line {error,enoent} = Mod:read_file("���_fil1"),
 
391
 
 
392
        ?line Mod:rename("���2",treat_icky(<<"���_fil1">>)),
 
393
        ?line {ok, <<"���2">>} = Mod:read_file(treat_icky(<<"���_fil1">>)),
 
394
        if
 
395
            UniMode and (OS =/= win32) ->
 
396
                {error,enoent} = Mod:read_file("���_fil1");
 
397
            true ->
 
398
                ok
 
399
        end,
 
400
        ?line {error,enoent} = Mod:read_file("���2"),
 
401
        ?line Mod:rename(treat_icky(<<"���_fil1">>),"���2"),
 
402
        ?line {ok, <<"���2">>} = Mod:read_file("���2"),
 
403
        ?line {error,enoent} = Mod:read_file("���_fil1"),
 
404
        ?line {error,enoent} = Mod:read_file(treat_icky(<<"���_fil1">>)),
 
405
 
 
406
        ?line {ok,FI} = Mod:read_file_info("���2"),
 
407
        ?line NewMode = FI#file_info.mode band (bnot 8#333),
 
408
        ?line NewMode2 = NewMode bor 8#222,
 
409
        ?line true = NewMode2 =/= NewMode,
 
410
        ?line ok = Mod:write_file_info("���2",FI#file_info{mode = NewMode}),
 
411
        ?line {ok,#file_info{mode = NewMode}} = Mod:read_file_info("���2"),
 
412
        ?line ok = Mod:write_file_info("���2",FI#file_info{mode = NewMode2}),
 
413
        ?line {ok,#file_info{mode = NewMode2}} = Mod:read_file_info("���2"),
 
414
 
 
415
        ?line {ok,FII} = Mod:read_file_info(treat_icky(<<"���5">>)),
 
416
        ?line true = NewMode2 =/= NewMode,
 
417
        ?line ok = Mod:write_file_info(treat_icky(<<"���5">>),FII#file_info{mode = NewMode}),
 
418
        ?line {ok,#file_info{mode = NewMode}} = Mod:read_file_info(treat_icky(<<"���5">>)),
 
419
        ?line ok = Mod:write_file_info(<<"���5">>,FII#file_info{mode = NewMode2}),
 
420
        ?line {ok,#file_info{mode = NewMode2}} = Mod:read_file_info(treat_icky(<<"���5">>)),
 
421
        ok
 
422
    after
 
423
        Mod:set_cwd(Dir),
 
424
        io:format("Wd now: ~s~n",[Dir])
 
425
    end.
 
426
 
 
427
check_very_icky(Mod) -> 
 
428
    {ok,Dir} = Mod:get_cwd(),
 
429
    try
 
430
        ?line true=(length("���") =:= 3),
 
431
        ?line UniMode = file:native_name_encoding() =/= latin1,
 
432
        if
 
433
            not UniMode ->
 
434
                throw(need_unicode_mode);
 
435
            true ->
 
436
                ok
 
437
        end,
 
438
        ?line make_very_icky_dir(Mod),
 
439
        ?line {ok, L0} = Mod:list_dir("."),
 
440
        ?line L1 = lists:sort(L0),
 
441
        ?line L1 = lists:sort(convlist(list(very_icky_dir()))),
 
442
        ?line {ok,D2} = Mod:get_cwd(),
 
443
        ?line true = is_list(D2),
 
444
        ?line [ true = ((is_list(El) or is_binary(El)))  || El <- L1],
 
445
        ?line Syms = [ {S,conv(Targ),list_to_binary(get_data(Targ,very_icky_dir()))} 
 
446
                 || {T,S,Targ} <- very_icky_dir(), T =:= symlink ],
 
447
        ?line [ {ok, Cont} = Mod:read_file(SymL) || {SymL,_,Cont} <- Syms ],
 
448
        ?line [ {ok, Targ} = fixlink(Mod:read_link(SymL)) || {SymL,Targ,_} <- Syms ],
 
449
        ?line chk_cre_dir(Mod,[{directory,[1088,1079,1091]++"_dir",very_icky_dir()}]),
 
450
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
451
        ?line true = is_list(BeginAt),
 
452
        ?line {error,enoent} = Mod:set_cwd("��_dir"),
 
453
        ?line ok = Mod:set_cwd([1088,1079,1091]++"_dir"),
 
454
        ?line {ok, NowAt} = Mod:get_cwd(),
 
455
        ?line true = is_list(NowAt),
 
456
        ?line true = BeginAt =/= NowAt,
 
457
        ?line ok = Mod:set_cwd(".."),
 
458
        ?line {ok,BeginAt} = Mod:get_cwd(),
 
459
        ?line rm_r2(Mod,[1088,1079,1091]++"_dir"),
 
460
 
 
461
        case has_links() of
 
462
            true ->
 
463
                ?line ok = Mod:make_link("fil1","nisse"++[1088,1079,1091]),
 
464
                ?line {ok, <<"fil1">>} = 
 
465
                    Mod:read_file("nisse"++[1088,1079,1091]),
 
466
                ?line {ok, #file_info{type = regular}} = 
 
467
                    Mod:read_link_info("nisse"++[1088,1079,1091]),
 
468
                ?line ok = Mod:delete("nisse"++[1088,1079,1091]),
 
469
                ?line ok = Mod:make_link("fil1",<<"nisse�">>),
 
470
                ?line {ok, <<"fil1">>} = Mod:read_file(<<"nisse�">>),
 
471
                ?line {ok, #file_info{type = regular}} = 
 
472
                    Mod:read_link_info(<<"nisse�">>),
 
473
                ?line ok = Mod:delete(<<"nisse�">>),
 
474
                ?line {ok, <<"fil1">>} = Mod:read_file("fil1"),
 
475
                ?line {error,enoent} = Mod:read_file("nisse"++[1088,1079,1091]),
 
476
                ?line {error,enoent} = Mod:read_link_info("nisse"++[1088,1079,1091]),
 
477
                ?line {error,enoent} = Mod:read_file(<<"nisse�">>),
 
478
                ?line {error,enoent} = Mod:read_link_info(<<"nisse�">>);
 
479
            false ->
 
480
                ok
 
481
        end,
 
482
        ?line [ begin
 
483
              ?line {ok, FD} = Mod:open(Name,[read]),
 
484
              ?line {ok, Content} = Mod:read(FD,1024),
 
485
              ?line ok = file:close(FD)
 
486
          end || {regular,Name,Content} <- very_icky_dir() ],
 
487
        ?line [ begin
 
488
              ?line {ok, FD} = Mod:open(Name,[read,binary]),
 
489
              ?line BC = list_to_binary([Content]),
 
490
              ?line {ok, BC} = Mod:read(FD,1024),
 
491
              ?line ok = file:close(FD)
 
492
          end || {regular,Name,Content} <- very_icky_dir() ],
 
493
        ?line Mod:rename([956,965,963,954,959,49],
 
494
                         [956,965,963,954,959]++"_fil1"),
 
495
        ?line {ok, <<"���2">>} = Mod:read_file([956,965,963,954,959]++"_fil1"),
 
496
        ?line {error,enoent} = Mod:read_file([956,965,963,954,959,49]),
 
497
        ?line Mod:rename([956,965,963,954,959]++"_fil1",[956,965,963,954,959,49]),
 
498
        ?line {ok, <<"���2">>} = Mod:read_file([956,965,963,954,959,49]),
 
499
        ?line {error,enoent} = Mod:read_file([956,965,963,954,959]++"_fil1"),
 
500
 
 
501
        ?line {ok,FI} = Mod:read_file_info([956,965,963,954,959,49]),
 
502
        ?line NewMode = FI#file_info.mode band (bnot 8#333),
 
503
        ?line NewMode2 = NewMode bor 8#222,
 
504
        ?line true = NewMode2 =/= NewMode,
 
505
        ?line ok = Mod:write_file_info([956,965,963,954,959,49],
 
506
                                       FI#file_info{mode = NewMode}),
 
507
        ?line {ok,#file_info{mode = NewMode}} = 
 
508
                   Mod:read_file_info([956,965,963,954,959,49]),
 
509
        ?line ok = Mod:write_file_info([956,965,963,954,959,49],
 
510
                                       FI#file_info{mode = NewMode2}),
 
511
        ?line {ok,#file_info{mode = NewMode2}} = 
 
512
                  Mod:read_file_info([956,965,963,954,959,49]),
 
513
        ?line NumOK0 = case has_links() of
 
514
                          true -> 5;
 
515
                          false -> 3
 
516
                      end,
 
517
        ?line NumNOK0 = case has_links() of
 
518
                           true -> 4;
 
519
                           false -> 3
 
520
                       end,
 
521
        ?line {NumOK,NumNOK} = case is_binary(treat_icky(<<"foo">>)) of
 
522
                                   false ->
 
523
                                       {NumOK0+NumNOK0,0};
 
524
                                   true ->
 
525
                                       {NumOK0,NumNOK0}
 
526
                               end,
 
527
        ?line {NumOK,NumNOK} = filelib:fold_files(".",".*",true,fun(_F,{N,M}) when is_list(_F) ->  io:format("~ts~n",[_F]),{N+1,M}; (_F,{N,M}) ->  io:format("~p~n",[_F]),{N,M+1} end,{0,0}),
 
528
        ?line ok = filelib:fold_files(".",[1076,1089,1072,124,46,42],true,fun(_F,_) -> ok end,false),
 
529
        ?line SF3 = unicode:characters_to_binary("���subfil3",
 
530
                                                 file:native_name_encoding()),
 
531
        ?line SF2 = case treat_icky(<<"���subfil2">>) of
 
532
                        LF2 when is_list(LF2) ->
 
533
                            unicode:characters_to_binary(LF2,
 
534
                                              file:native_name_encoding());
 
535
                        BF2 ->
 
536
                            BF2
 
537
                    end,                      
 
538
        ?line Sorted = lists:sort([SF3,SF2]),
 
539
        ?line Sorted = lists:sort(filelib:wildcard("*",<<"���subdir2">>)),
 
540
        ok
 
541
    catch
 
542
        throw:need_unicode_mode ->
 
543
            io:format("Sorry, can only run in unicode mode.~n"),
 
544
            need_unicode_mode
 
545
    after
 
546
        Mod:set_cwd(Dir),
 
547
        io:format("Wd now: ~s~n",[Dir])
 
548
    end.
 
549
 
 
550
%%
 
551
%% Utilities
 
552
%%
 
553
 
 
554
 
 
555
rm_rf(Mod,Dir) ->
 
556
    case  Mod:read_link_info(Dir) of
 
557
        {ok, #file_info{type = directory}} ->
 
558
            {ok, Content} = Mod:list_dir(Dir),
 
559
            [ rm_rf(Mod,filename:join(Dir,C)) || C <- Content ],
 
560
            Mod:del_dir(Dir),
 
561
            ok;
 
562
        {ok, #file_info{}} ->
 
563
            Mod:delete(Dir);
 
564
        _ ->
 
565
            ok
 
566
    end.
 
567
 
 
568
rm_r(Mod,Dir) ->
 
569
    %erlang:display({rm_r,Dir}),
 
570
    case  Mod:read_link_info(Dir) of
 
571
        {ok, #file_info{type = directory}} ->
 
572
            {ok,#file_info{type = directory}} =  Mod:read_file_info(Dir),
 
573
            {ok, Content} = Mod:list_dir(Dir),
 
574
            [ true = is_list(Part) || Part <- Content ],
 
575
            [ true = is_list(filename:join(Dir,Part)) || Part <- Content ],
 
576
            [ rm_r(Mod,filename:join(Dir,C)) || C <- Content ],
 
577
            ok = Mod:del_dir(Dir),
 
578
            ok;
 
579
        {ok, #file_info{type = regular}} ->
 
580
            {ok,#file_info{type = regular}} =  Mod:read_file_info(Dir),
 
581
            ok = Mod:delete(Dir);
 
582
        {ok, #file_info{type = symlink}} ->
 
583
            ok = Mod:delete(Dir)
 
584
    end.
 
585
%% For icky test, allow binaries sometimes
 
586
rm_r2(Mod,Dir) ->
 
587
    %erlang:display({rm_r2,Dir}),
 
588
    case  Mod:read_link_info(Dir) of
 
589
        {ok, #file_info{type = directory}} ->
 
590
            {ok,#file_info{type = directory}} =  Mod:read_file_info(Dir),
 
591
            {ok, Content} = Mod:list_dir(Dir),
 
592
            UniMode = file:native_name_encoding() =/= latin1,
 
593
            [ true = (is_list(Part) orelse UniMode) || Part <- Content ],
 
594
            [ true = (is_list(filename:join(Dir,Part)) orelse UniMode) || Part <- Content ],
 
595
            [ rm_r2(Mod,filename:join(Dir,C)) || C <- Content ],
 
596
            ok = Mod:del_dir(Dir),
 
597
            ok;
 
598
        {ok, #file_info{type = regular}} ->
 
599
            {ok,#file_info{type = regular}} =  Mod:read_file_info(Dir),
 
600
            ok = Mod:delete(Dir);
 
601
        {ok, #file_info{type = symlink}} ->
 
602
            ok = Mod:delete(Dir)
 
603
    end.
 
604
chk_cre_dir(_,[]) ->
 
605
    ok;
 
606
chk_cre_dir(Mod,[{regular,Name,Content}|T]) ->
 
607
    %io:format("~p~n",[Name]),
 
608
    ok = Mod:write_file(Name,Content),
 
609
    chk_cre_dir(Mod,T);
 
610
chk_cre_dir(Mod,[{link,Name,Target}|T]) ->
 
611
    ok = Mod:make_link(Target,Name),
 
612
    chk_cre_dir(Mod,T);
 
613
chk_cre_dir(Mod,[{symlink,Name,Target}|T]) ->
 
614
    ok = Mod:make_symlink(Target,Name),
 
615
    chk_cre_dir(Mod,T);
 
616
chk_cre_dir(Mod,[{directory,Name,Content}|T]) ->
 
617
    ok = Mod:make_dir(Name),
 
618
    %io:format("Content = ~p~n",[Content]),
 
619
    Content2 = [{Ty,filename:join(Name,N),case Ty of link -> filename:join(Name,C); _ -> C end} || {Ty,N,C} <- Content ],
 
620
    %io:format("Content2 = ~p~n",[Content2]),
 
621
    chk_cre_dir(Mod,Content2),
 
622
    chk_cre_dir(Mod,T).
 
623
 
 
624
has_links() ->   
 
625
    case os:type() of
 
626
        {win32,_} ->
 
627
            case os:version() of
 
628
                {N,NN,_} when (N > 5) andalso (NN >= 1) ->
 
629
                    true;
 
630
                _ ->
 
631
                    false
 
632
            end;
 
633
        _ ->
 
634
            true
 
635
    end.
 
636
 
 
637
make_normal_dir(Mod) ->
 
638
    rm_rf(Mod,"normal_dir"),
 
639
    Mod:make_dir("normal_dir"),
 
640
    Mod:set_cwd("normal_dir"),
 
641
    Mod:write_file("fil1","fil1"),
 
642
    Mod:write_file("fil2","fil2"),
 
643
    case has_links() of
 
644
        true ->
 
645
            Mod:make_link("fil2","fil3"),
 
646
            Mod:make_symlink("fil2","fil4");
 
647
        _ ->
 
648
            ok
 
649
    end,
 
650
    Mod:make_dir("subdir"),
 
651
    Mod:write_file(filename:join("subdir","subfil1"),"subfil1"),
 
652
    ok.
 
653
    
 
654
normal_dir() ->
 
655
    [{regular,"fil1","fil1"},
 
656
     {regular,"fil2","fil2"}] ++
 
657
        case has_links() of
 
658
            true ->
 
659
                [{regular,"fil3","fil2"},
 
660
                 {symlink,"fil4","fil2"}];
 
661
            false ->
 
662
                []
 
663
        end ++
 
664
        [{directory,"subdir",
 
665
          [{regular,"subfil1","subfil1"}]}].
 
666
 
 
667
make_icky_dir(Mod) ->
 
668
    rm_rf(Mod,"icky_dir"),
 
669
    Icky=icky_dir(),
 
670
    chk_cre_dir(Mod,[{directory,"icky_dir",linkify([],Icky)}]),
 
671
    Mod:set_cwd("icky_dir"),
 
672
    ok.
 
673
 
 
674
linkify(_Passed,[]) ->
 
675
    [];
 
676
linkify(Passed,[{regular,Name,Content}|T]) ->
 
677
    Regulars = [ {N,C} || {regular,N,C} <- Passed, N =/= Name ],
 
678
    case lists:keysearch(Content,2,Regulars) of
 
679
        {value, {Linkto, Content}} ->
 
680
            [{link,Name,Linkto} | linkify(Passed,T)];
 
681
        _ ->
 
682
            [{regular,Name,Content} | linkify([{regular,Name,Content}|Passed],T)]
 
683
    end;
 
684
linkify(Passed,[{directory, Name, Content}|T]) ->
 
685
    [{directory,Name, linkify(Content,Content)}|linkify(Passed,T)];
 
686
linkify(Passed,[H|T]) ->
 
687
    [H|linkify([H|Passed],T)].
 
688
 
 
689
hopeless_darwin() ->
 
690
    case {os:type(),os:version()} of
 
691
        {{unix,darwin},{Major,_,_}} when Major < 9 ->
 
692
            true;
 
693
        _ ->
 
694
            false
 
695
    end.
 
696
 
 
697
icky_dir() ->
 
698
    [{regular,"fil1","fil1"},
 
699
     {regular,"���2","���2"}] ++
 
700
        case has_links() of
 
701
            true ->
 
702
                [{regular,"���3","���2"},
 
703
                 {symlink,"���4","���2"}];
 
704
            false ->
 
705
                []
 
706
        end ++
 
707
        [{regular,treat_icky(<<"���5">>),"���5"}] ++
 
708
         case has_links() of
 
709
             true -> 
 
710
                 [{symlink,treat_icky(<<"���6">>),treat_icky(<<"���5">>)}];
 
711
             false -> 
 
712
                 []
 
713
         end ++
 
714
        [{directory,treat_icky(<<"���subdir2">>),
 
715
          [{regular,treat_icky(<<"���subfil2">>),"���subfil12"},
 
716
           {regular,"���subfil3","���subfil13"}]},
 
717
         {directory,"���subdir",
 
718
          [{regular,"���subfil1","���subfil1"}]}].
 
719
 
 
720
make_very_icky_dir(Mod) ->
 
721
    rm_rf(Mod,"very_icky_dir"),
 
722
    Icky=very_icky_dir(),
 
723
    chk_cre_dir(Mod,[{directory,"very_icky_dir",linkify([],Icky)}]),
 
724
    Mod:set_cwd("very_icky_dir"),
 
725
    ok.
 
726
 
 
727
very_icky_dir() ->
 
728
    [{regular,"fil1","fil1"},
 
729
     {regular,[956,965,963,954,959,49],"���2"}] ++
 
730
        case has_links() of
 
731
            true ->
 
732
                [{regular,[956,965,963,954,959,50],"���2"},
 
733
                 {symlink,[956,965,963,954,959,51],[956,965,963,954,959,49]}];
 
734
            false ->
 
735
                []
 
736
        end ++
 
737
     [{regular,treat_icky(<<"���5">>),"���5"}] ++
 
738
        case has_links() of
 
739
            true ->
 
740
                [{symlink,treat_icky(<<"���6">>),treat_icky(<<"���5">>)}];
 
741
            false -> 
 
742
                []
 
743
        end ++
 
744
      [{directory,treat_icky(<<"���subdir2">>),
 
745
      [{regular,treat_icky(<<"���subfil2">>),"���subfil12"},
 
746
       {regular,"���subfil3","���subfil13"}]},
 
747
      {directory,[956,965,963,954,959]++"subdir1",
 
748
       [{regular,[956,965,963,954,959]++"subfil1","���subfil1"}]}].
 
749
 
 
750
%% Some OS'es simply do not allow non UTF8 filenames
 
751
treat_icky(Bin) ->
 
752
    case os:type() of
 
753
        {unix,darwin} ->
 
754
            binary_to_list(procentify(Bin));
 
755
        {win32,_} ->
 
756
            binary_to_list(Bin);
 
757
        _ ->
 
758
            Bin
 
759
    end.
 
760
 
 
761
% Handle windows having absolute soft link targets.
 
762
fixlink({ok,Link}) ->
 
763
    case os:type() of
 
764
        {win32,_} ->
 
765
            {ok,filename:basename(Link)};
 
766
        _ ->
 
767
            {ok,Link}
 
768
    end;
 
769
fixlink(X) ->
 
770
    X.
 
771
 
 
772
procentify(<<>>) ->
 
773
    <<>>;
 
774
procentify(<<X:8,Rst/binary>>) when X > 127 ->
 
775
    T=procentify(Rst),
 
776
    Y = list_to_binary([$% 
 
777
                        | io_lib:format("~2.16B",[X])]),
 
778
    <<Y/binary,T/binary>>;
 
779
procentify(<<X:8,Rst/binary>>) ->
 
780
    T=procentify(Rst),
 
781
    <<X:8,T/binary>>.
 
782
 
 
783
 
 
784
list([]) ->
 
785
    [];
 
786
list([{_,Name,_} | T]) ->
 
787
    [Name | list(T)].
 
788
    
 
789
 
 
790
get_data(FN,List) ->
 
791
    case lists:keysearch(FN,2,List) of
 
792
        {value,{regular,FN,C}} ->
 
793
            C;
 
794
        {value,{symlink,FN,NewFN}} ->
 
795
            get_data(NewFN,List);
 
796
        _->
 
797
            []
 
798
    end.
 
799
 
 
800
 
 
801
convlist(L) ->
 
802
    convlist(file:native_name_encoding(),L).
 
803
convlist(latin1,[Bin|T]) when is_binary(Bin) ->
 
804
    %erlang:display('Convert...'),
 
805
    [binary_to_list(Bin)| convlist(latin1,T)];
 
806
convlist(Any,[H|T]) ->
 
807
    [H|convlist(Any,T)];
 
808
convlist(_,[]) ->
 
809
    [].
 
810
 
 
811
conv(L) ->
 
812
    NoUniMode = file:native_name_encoding() =:= latin1,
 
813
    if 
 
814
        NoUniMode, is_binary(L) ->
 
815
            binary_to_list(L);
 
816
        true ->
 
817
            L
 
818
    end.
 
819
 
 
820
 
 
821
rand_comp_decomp(Max) ->
 
822
    N = random:uniform(Max),
 
823
    L = [ rand_decomp() || _ <- lists:seq(1,N) ],
 
824
    LC = [ A || {A,_} <- L],
 
825
    LD = lists:flatten([B || {_,B} <- L]),
 
826
    LB = unicode:characters_to_binary(LD,unicode,utf8),
 
827
    {LC,LB}.
 
828
    
 
829
rand_decomp() ->
 
830
    BT = bigtup(),
 
831
    SZ = tuple_size(BT),
 
832
    element(random:uniform(SZ),BT).
 
833
bigtup() ->
 
834
    {{192,[65,768]},
 
835
     {200,[69,768]},
 
836
     {204,[73,768]},
 
837
     {210,[79,768]},
 
838
     {217,[85,768]},
 
839
     {7808,[87,768]},
 
840
     {7922,[89,768]},
 
841
     {224,[97,768]},
 
842
     {232,[101,768]},
 
843
     {236,[105,768]},
 
844
     {242,[111,768]},
 
845
     {249,[117,768]},
 
846
     {7809,[119,768]},
 
847
     {7923,[121,768]},
 
848
     {8173,[168,768]},
 
849
     {7846,[65,770,768]},
 
850
     {7872,[69,770,768]},
 
851
     {7890,[79,770,768]},
 
852
     {7847,[97,770,768]},
 
853
     {7873,[101,770,768]},
 
854
     {7891,[111,770,768]},
 
855
     {7700,[69,772,768]},
 
856
     {7760,[79,772,768]},
 
857
     {7701,[101,772,768]},
 
858
     {7761,[111,772,768]},
 
859
     {7856,[65,774,768]},
 
860
     {7857,[97,774,768]},
 
861
     {475,[85,776,768]},
 
862
     {476,[117,776,768]},
 
863
     {8146,[953,776,768]},
 
864
     {8162,[965,776,768]},
 
865
     {8074,[913,837,787,768]},
 
866
     {8090,[919,837,787,768]},
 
867
     {8106,[937,837,787,768]},
 
868
     {8066,[945,837,787,768]},
 
869
     {8082,[951,837,787,768]},
 
870
     {8098,[969,837,787,768]},
 
871
     {7946,[913,787,768]},
 
872
     {7962,[917,787,768]},
 
873
     {7978,[919,787,768]},
 
874
     {7994,[921,787,768]},
 
875
     {8010,[927,787,768]},
 
876
     {8042,[937,787,768]},
 
877
     {7938,[945,787,768]},
 
878
     {7954,[949,787,768]},
 
879
     {7970,[951,787,768]},
 
880
     {7986,[953,787,768]},
 
881
     {8002,[959,787,768]},
 
882
     {8018,[965,787,768]},
 
883
     {8034,[969,787,768]},
 
884
     {8075,[913,837,788,768]},
 
885
     {8091,[919,837,788,768]},
 
886
     {8107,[937,837,788,768]},
 
887
     {8067,[945,837,788,768]},
 
888
     {8083,[951,837,788,768]},
 
889
     {8099,[969,837,788,768]},
 
890
     {7947,[913,788,768]},
 
891
     {7963,[917,788,768]},
 
892
     {7979,[919,788,768]},
 
893
     {7995,[921,788,768]},
 
894
     {8011,[927,788,768]},
 
895
     {8027,[933,788,768]},
 
896
     {8043,[937,788,768]},
 
897
     {7939,[945,788,768]},
 
898
     {7955,[949,788,768]},
 
899
     {7971,[951,788,768]},
 
900
     {7987,[953,788,768]},
 
901
     {8003,[959,788,768]},
 
902
     {8019,[965,788,768]},
 
903
     {8035,[969,788,768]},
 
904
     {7900,[79,795,768]},
 
905
     {7914,[85,795,768]},
 
906
     {7901,[111,795,768]},
 
907
     {7915,[117,795,768]},
 
908
     {8114,[945,837,768]},
 
909
     {8130,[951,837,768]},
 
910
     {8178,[969,837,768]},
 
911
     {8122,[913,768]},
 
912
     {8136,[917,768]},
 
913
     {8138,[919,768]},
 
914
     {8154,[921,768]},
 
915
     {8184,[927,768]},
 
916
     {8170,[933,768]},
 
917
     {8186,[937,768]},
 
918
     {8048,[945,768]},
 
919
     {8050,[949,768]},
 
920
     {8052,[951,768]},
 
921
     {8054,[953,768]},
 
922
     {8056,[959,768]},
 
923
     {8058,[965,768]},
 
924
     {8060,[969,768]},
 
925
     {8141,[8127,768]},
 
926
     {8157,[8190,768]},
 
927
     {193,[65,769]},
 
928
     {262,[67,769]},
 
929
     {201,[69,769]},
 
930
     {500,[71,769]},
 
931
     {205,[73,769]},
 
932
     {7728,[75,769]},
 
933
     {313,[76,769]},
 
934
     {7742,[77,769]},
 
935
     {323,[78,769]},
 
936
     {211,[79,769]},
 
937
     {7764,[80,769]},
 
938
     {340,[82,769]},
 
939
     {346,[83,769]},
 
940
     {218,[85,769]},
 
941
     {7810,[87,769]},
 
942
     {221,[89,769]},
 
943
     {377,[90,769]},
 
944
     {225,[97,769]},
 
945
     {263,[99,769]},
 
946
     {233,[101,769]},
 
947
     {501,[103,769]},
 
948
     {237,[105,769]},
 
949
     {7729,[107,769]},
 
950
     {314,[108,769]},
 
951
     {7743,[109,769]},
 
952
     {324,[110,769]},
 
953
     {243,[111,769]},
 
954
     {7765,[112,769]},
 
955
     {341,[114,769]},
 
956
     {347,[115,769]},
 
957
     {250,[117,769]},
 
958
     {7811,[119,769]},
 
959
     {253,[121,769]},
 
960
     {378,[122,769]},
 
961
     {8174,[168,769]},
 
962
     {508,[198,769]},
 
963
     {510,[216,769]},
 
964
     {509,[230,769]},
 
965
     {511,[248,769]},
 
966
     {7844,[65,770,769]},
 
967
     {7870,[69,770,769]},
 
968
     {7888,[79,770,769]},
 
969
     {7845,[97,770,769]},
 
970
     {7871,[101,770,769]},
 
971
     {7889,[111,770,769]},
 
972
     {7756,[79,771,769]},
 
973
     {7800,[85,771,769]},
 
974
     {7757,[111,771,769]},
 
975
     {7801,[117,771,769]},
 
976
     {7702,[69,772,769]},
 
977
     {7762,[79,772,769]},
 
978
     {7703,[101,772,769]},
 
979
     {7763,[111,772,769]},
 
980
     {7854,[65,774,769]},
 
981
     {7855,[97,774,769]},
 
982
     {7726,[73,776,769]},
 
983
     {471,[85,776,769]},
 
984
     {7727,[105,776,769]},
 
985
     {472,[117,776,769]},
 
986
     {8147,[953,776,769]},
 
987
     {8163,[965,776,769]},
 
988
     {506,[65,778,769]},
 
989
     {507,[97,778,769]},
 
990
     {8076,[913,837,787,769]},
 
991
     {8092,[919,837,787,769]},
 
992
     {8108,[937,837,787,769]},
 
993
     {8068,[945,837,787,769]},
 
994
     {8084,[951,837,787,769]},
 
995
     {8100,[969,837,787,769]},
 
996
     {7948,[913,787,769]},
 
997
     {7964,[917,787,769]},
 
998
     {7980,[919,787,769]},
 
999
     {7996,[921,787,769]},
 
1000
     {8012,[927,787,769]},
 
1001
     {8044,[937,787,769]},
 
1002
     {7940,[945,787,769]},
 
1003
     {7956,[949,787,769]},
 
1004
     {7972,[951,787,769]},
 
1005
     {7988,[953,787,769]},
 
1006
     {8004,[959,787,769]},
 
1007
     {8020,[965,787,769]},
 
1008
     {8036,[969,787,769]},
 
1009
     {8077,[913,837,788,769]},
 
1010
     {8093,[919,837,788,769]},
 
1011
     {8109,[937,837,788,769]},
 
1012
     {8069,[945,837,788,769]},
 
1013
     {8085,[951,837,788,769]},
 
1014
     {8101,[969,837,788,769]},
 
1015
     {7949,[913,788,769]},
 
1016
     {7965,[917,788,769]},
 
1017
     {7981,[919,788,769]},
 
1018
     {7997,[921,788,769]},
 
1019
     {8013,[927,788,769]},
 
1020
     {8029,[933,788,769]},
 
1021
     {8045,[937,788,769]},
 
1022
     {7941,[945,788,769]},
 
1023
     {7957,[949,788,769]},
 
1024
     {7973,[951,788,769]},
 
1025
     {7989,[953,788,769]},
 
1026
     {8005,[959,788,769]},
 
1027
     {8021,[965,788,769]},
 
1028
     {8037,[969,788,769]},
 
1029
     {7898,[79,795,769]},
 
1030
     {7912,[85,795,769]},
 
1031
     {7899,[111,795,769]},
 
1032
     {7913,[117,795,769]},
 
1033
     {7688,[67,807,769]},
 
1034
     {7689,[99,807,769]},
 
1035
     {8116,[945,837,769]},
 
1036
     {8132,[951,837,769]},
 
1037
     {8180,[959,837,769]},
 
1038
     {8123,[913,769]},
 
1039
     {8137,[917,769]},
 
1040
     {8139,[919,769]},
 
1041
     {8155,[921,769]},
 
1042
     {8185,[927,769]},
 
1043
     {8171,[933,769]},
 
1044
     {8187,[937,769]},
 
1045
     {8049,[945,769]},
 
1046
     {8051,[949,769]},
 
1047
     {8053,[951,769]},
 
1048
     {8055,[953,769]},
 
1049
     {8057,[959,769]},
 
1050
     {8059,[965,769]},
 
1051
     {8061,[969,769]},
 
1052
     {1027,[1043,769]},
 
1053
     {1036,[1050,769]},
 
1054
     {1107,[1075,769]},
 
1055
     {1116,[1082,769]},
 
1056
     {8142,[8127,769]},
 
1057
     {8158,[8190,769]},
 
1058
     {194,[65,770]},
 
1059
     {264,[67,770]},
 
1060
     {202,[69,770]},
 
1061
     {284,[71,770]},
 
1062
     {292,[72,770]},
 
1063
     {206,[73,770]},
 
1064
     {308,[74,770]},
 
1065
     {212,[79,770]},
 
1066
     {348,[83,770]},
 
1067
     {219,[85,770]},
 
1068
     {372,[87,770]},
 
1069
     {374,[89,770]},
 
1070
     {7824,[90,770]},
 
1071
     {226,[97,770]},
 
1072
     {265,[99,770]},
 
1073
     {234,[101,770]},
 
1074
     {285,[103,770]},
 
1075
     {293,[104,770]},
 
1076
     {238,[105,770]},
 
1077
     {309,[106,770]},
 
1078
     {244,[111,770]},
 
1079
     {349,[115,770]},
 
1080
     {251,[117,770]},
 
1081
     {373,[119,770]},
 
1082
     {375,[121,770]},
 
1083
     {7825,[122,770]},
 
1084
     {7852,[65,803,770]},
 
1085
     {7878,[69,803,770]},
 
1086
     {7896,[79,803,770]},
 
1087
     {7853,[97,803,770]},
 
1088
     {7879,[101,803,770]},
 
1089
     {7897,[111,803,770]},
 
1090
     {195,[65,771]},
 
1091
     {7868,[69,771]},
 
1092
     {296,[73,771]},
 
1093
     {209,[78,771]},
 
1094
     {213,[79,771]},
 
1095
     {360,[85,771]},
 
1096
     {7804,[86,771]},
 
1097
     {7928,[89,771]},
 
1098
     {227,[97,771]},
 
1099
     {7869,[101,771]},
 
1100
     {297,[105,771]},
 
1101
     {241,[110,771]},
 
1102
     {245,[111,771]},
 
1103
     {361,[117,771]},
 
1104
     {7805,[118,771]},
 
1105
     {7929,[121,771]},
 
1106
     {7850,[65,770,771]},
 
1107
     {7876,[69,770,771]},
 
1108
     {7894,[79,770,771]},
 
1109
     {7851,[97,770,771]},
 
1110
     {7877,[101,770,771]},
 
1111
     {7895,[111,770,771]},
 
1112
     {7860,[65,774,771]},
 
1113
     {7861,[97,774,771]},
 
1114
     {7904,[79,795,771]},
 
1115
     {7918,[85,795,771]},
 
1116
     {7905,[111,795,771]},
 
1117
     {7919,[117,795,771]},
 
1118
     {256,[65,772]},
 
1119
     {274,[69,772]},
 
1120
     {7712,[71,772]},
 
1121
     {298,[73,772]},
 
1122
     {332,[79,772]},
 
1123
     {362,[85,772]},
 
1124
     {257,[97,772]},
 
1125
     {275,[101,772]},
 
1126
     {7713,[103,772]},
 
1127
     {299,[105,772]},
 
1128
     {333,[111,772]},
 
1129
     {363,[117,772]},
 
1130
     {482,[198,772]},
 
1131
     {483,[230,772]},
 
1132
     {480,[65,775,772]},
 
1133
     {481,[97,775,772]},
 
1134
     {478,[65,776,772]},
 
1135
     {469,[85,776,772]},
 
1136
     {479,[97,776,772]},
 
1137
     {470,[117,776,772]},
 
1138
     {7736,[76,803,772]},
 
1139
     {7772,[82,803,772]},
 
1140
     {7737,[108,803,772]},
 
1141
     {7773,[114,803,772]},
 
1142
     {492,[79,808,772]},
 
1143
     {493,[111,808,772]},
 
1144
     {8121,[913,772]},
 
1145
     {8153,[921,772]},
 
1146
     {8169,[933,772]},
 
1147
     {8113,[945,772]},
 
1148
     {8145,[953,772]},
 
1149
     {8161,[965,772]},
 
1150
     {1250,[1048,772]},
 
1151
     {1262,[1059,772]},
 
1152
     {1251,[1080,772]},
 
1153
     {1263,[1091,772]},
 
1154
     {258,[65,774]},
 
1155
     {276,[69,774]},
 
1156
     {286,[71,774]},
 
1157
     {300,[73,774]},
 
1158
     {334,[79,774]},
 
1159
     {364,[85,774]},
 
1160
     {259,[97,774]},
 
1161
     {277,[101,774]},
 
1162
     {287,[103,774]},
 
1163
     {301,[105,774]},
 
1164
     {335,[111,774]},
 
1165
     {365,[117,774]},
 
1166
     {7862,[65,803,774]},
 
1167
     {7863,[97,803,774]},
 
1168
     {7708,[69,807,774]},
 
1169
     {7709,[101,807,774]},
 
1170
     {8120,[913,774]},
 
1171
     {8152,[921,774]},
 
1172
     {8168,[933,774]},
 
1173
     {8112,[945,774]},
 
1174
     {8144,[953,774]},
 
1175
     {8160,[965,774]},
 
1176
     {1232,[1040,774]},
 
1177
     {1238,[1045,774]},
 
1178
     {1217,[1046,774]},
 
1179
     {1049,[1048,774]},
 
1180
     {1038,[1059,774]},
 
1181
     {1233,[1072,774]},
 
1182
     {1239,[1077,774]},
 
1183
     {1218,[1078,774]},
 
1184
     {1081,[1080,774]},
 
1185
     {1118,[1091,774]},
 
1186
     {7682,[66,775]},
 
1187
     {266,[67,775]},
 
1188
     {7690,[68,775]},
 
1189
     {278,[69,775]},
 
1190
     {7710,[70,775]},
 
1191
     {288,[71,775]},
 
1192
     {7714,[72,775]},
 
1193
     {304,[73,775]},
 
1194
     {7744,[77,775]},
 
1195
     {7748,[78,775]},
 
1196
     {7766,[80,775]},
 
1197
     {7768,[82,775]},
 
1198
     {7776,[83,775]},
 
1199
     {7786,[84,775]},
 
1200
     {7814,[87,775]},
 
1201
     {7818,[88,775]},
 
1202
     {7822,[89,775]},
 
1203
     {379,[90,775]},
 
1204
     {7683,[98,775]},
 
1205
     {267,[99,775]},
 
1206
     {7691,[100,775]},
 
1207
     {279,[101,775]},
 
1208
     {7711,[102,775]},
 
1209
     {289,[103,775]},
 
1210
     {7715,[104,775]},
 
1211
     {7745,[109,775]},
 
1212
     {7749,[110,775]},
 
1213
     {7767,[112,775]},
 
1214
     {7769,[114,775]},
 
1215
     {7777,[115,775]},
 
1216
     {7787,[116,775]},
 
1217
     {7815,[119,775]},
 
1218
     {7819,[120,775]},
 
1219
     {7823,[121,775]},
 
1220
     {380,[122,775]},
 
1221
     {7835,[383,775]},
 
1222
     {7780,[83,769,775]},
 
1223
     {7781,[115,769,775]},
 
1224
     {784,[774,775]},
 
1225
     {7782,[83,780,775]},
 
1226
     {7783,[115,780,775]},
 
1227
     {7784,[83,803,775]},
 
1228
     {7785,[115,803,775]},
 
1229
     {196,[65,776]},
 
1230
     {203,[69,776]},
 
1231
     {7718,[72,776]},
 
1232
     {207,[73,776]},
 
1233
     {214,[79,776]},
 
1234
     {220,[85,776]},
 
1235
     {7812,[87,776]},
 
1236
     {7820,[88,776]},
 
1237
     {376,[89,776]},
 
1238
     {228,[97,776]},
 
1239
     {235,[101,776]},
 
1240
     {7719,[104,776]},
 
1241
     {239,[105,776]},
 
1242
     {246,[111,776]},
 
1243
     {7831,[116,776]},
 
1244
     {252,[117,776]},
 
1245
     {7813,[119,776]},
 
1246
     {7821,[120,776]},
 
1247
     {255,[121,776]},
 
1248
     {1242,[399,776]},
 
1249
     {1258,[415,776]},
 
1250
     {1243,[601,776]},
 
1251
     {1259,[629,776]},
 
1252
     {7758,[79,771,776]},
 
1253
     {7759,[111,771,776]},
 
1254
     {7802,[85,772,776]},
 
1255
     {7803,[117,772,776]},
 
1256
     {938,[921,776]},
 
1257
     {939,[933,776]},
 
1258
     {970,[953,776]},
 
1259
     {971,[965,776]},
 
1260
     {980,[978,776]},
 
1261
     {1031,[1030,776]},
 
1262
     {1234,[1040,776]},
 
1263
     {1025,[1045,776]},
 
1264
     {1244,[1046,776]},
 
1265
     {1246,[1047,776]},
 
1266
     {1252,[1048,776]},
 
1267
     {1254,[1054,776]},
 
1268
     {1264,[1059,776]},
 
1269
     {1268,[1063,776]},
 
1270
     {1272,[1067,776]},
 
1271
     {1235,[1072,776]},
 
1272
     {1105,[1077,776]},
 
1273
     {1245,[1078,776]},
 
1274
     {1247,[1079,776]},
 
1275
     {1253,[1080,776]},
 
1276
     {1255,[1086,776]},
 
1277
     {1265,[1091,776]},
 
1278
     {1269,[1095,776]},
 
1279
     {1273,[1099,776]},
 
1280
     {1111,[1110,776]},
 
1281
     {7842,[65,777]},
 
1282
     {7866,[69,777]},
 
1283
     {7880,[73,777]},
 
1284
     {7886,[79,777]},
 
1285
     {7910,[85,777]},
 
1286
     {7926,[89,777]},
 
1287
     {7843,[97,777]},
 
1288
     {7867,[101,777]},
 
1289
     {7881,[105,777]},
 
1290
     {7887,[111,777]},
 
1291
     {7911,[117,777]},
 
1292
     {7927,[121,777]},
 
1293
     {7848,[65,770,777]},
 
1294
     {7874,[69,770,777]},
 
1295
     {7892,[79,770,777]},
 
1296
     {7849,[97,770,777]},
 
1297
     {7875,[101,770,777]},
 
1298
     {7893,[111,770,777]},
 
1299
     {7858,[65,774,777]},
 
1300
     {7859,[97,774,777]},
 
1301
     {7902,[79,795,777]},
 
1302
     {7916,[85,795,777]},
 
1303
     {7903,[111,795,777]},
 
1304
     {7917,[117,795,777]},
 
1305
     {197,[65,778]},
 
1306
     {366,[85,778]},
 
1307
     {229,[97,778]},
 
1308
     {367,[117,778]},
 
1309
     {7832,[119,778]},
 
1310
     {7833,[121,778]},
 
1311
     {336,[79,779]},
 
1312
     {368,[85,779]},
 
1313
     {337,[111,779]},
 
1314
     {369,[117,779]},
 
1315
     {1266,[1059,779]},
 
1316
     {1267,[1091,779]},
 
1317
     {461,[65,780]},
 
1318
     {268,[67,780]},
 
1319
     {270,[68,780]},
 
1320
     {282,[69,780]},
 
1321
     {486,[71,780]},
 
1322
     {463,[73,780]},
 
1323
     {488,[75,780]},
 
1324
     {317,[76,780]},
 
1325
     {327,[78,780]},
 
1326
     {465,[79,780]},
 
1327
     {344,[82,780]},
 
1328
     {352,[83,780]},
 
1329
     {356,[84,780]},
 
1330
     {467,[85,780]},
 
1331
     {381,[90,780]},
 
1332
     {462,[97,780]},
 
1333
     {269,[99,780]},
 
1334
     {271,[100,780]},
 
1335
     {283,[101,780]},
 
1336
     {487,[103,780]},
 
1337
     {464,[105,780]},
 
1338
     {496,[106,780]},
 
1339
     {489,[107,780]},
 
1340
     {318,[108,780]},
 
1341
     {328,[110,780]},
 
1342
     {466,[111,780]},
 
1343
     {345,[114,780]},
 
1344
     {353,[115,780]},
 
1345
     {357,[116,780]},
 
1346
     {468,[117,780]},
 
1347
     {382,[122,780]},
 
1348
     {494,[439,780]},
 
1349
     {495,[658,780]},
 
1350
     {473,[85,776,780]},
 
1351
     {474,[117,776,780]},
 
1352
     {901,[168,781]},
 
1353
     {912,[953,776,781]},
 
1354
     {944,[965,776,781]},
 
1355
     {902,[913,781]},
 
1356
     {904,[917,781]},
 
1357
     {905,[919,781]},
 
1358
     {906,[921,781]},
 
1359
     {908,[927,781]},
 
1360
     {910,[933,781]},
 
1361
     {911,[937,781]},
 
1362
     {940,[945,781]},
 
1363
     {941,[949,781]},
 
1364
     {942,[951,781]},
 
1365
     {943,[953,781]},
 
1366
     {972,[959,781]},
 
1367
     {973,[965,781]},
 
1368
     {974,[969,781]},
 
1369
     {979,[978,781]},
 
1370
     {512,[65,783]},
 
1371
     {516,[69,783]},
 
1372
     {520,[73,783]},
 
1373
     {524,[79,783]},
 
1374
     {528,[82,783]},
 
1375
     {532,[85,783]},
 
1376
     {513,[97,783]},
 
1377
     {517,[101,783]},
 
1378
     {521,[105,783]},
 
1379
     {525,[111,783]},
 
1380
     {529,[114,783]},
 
1381
     {533,[117,783]},
 
1382
     {1142,[1140,783]},
 
1383
     {1143,[1141,783]},
 
1384
     {514,[65,785]},
 
1385
     {518,[69,785]},
 
1386
     {522,[73,785]},
 
1387
     {526,[79,785]},
 
1388
     {530,[82,785]},
 
1389
     {534,[85,785]},
 
1390
     {515,[97,785]},
 
1391
     {519,[101,785]},
 
1392
     {523,[105,785]},
 
1393
     {527,[111,785]},
 
1394
     {531,[114,785]},
 
1395
     {535,[117,785]},
 
1396
     {8072,[913,837,787]},
 
1397
     {8088,[919,837,787]},
 
1398
     {8104,[937,837,787]},
 
1399
     {8064,[945,837,787]},
 
1400
     {8080,[951,837,787]},
 
1401
     {8096,[969,837,787]},
 
1402
     {7944,[913,787]},
 
1403
     {7960,[917,787]},
 
1404
     {7976,[919,787]},
 
1405
     {7992,[921,787]},
 
1406
     {8008,[927,787]},
 
1407
     {8040,[937,787]},
 
1408
     {7936,[945,787]},
 
1409
     {7952,[949,787]},
 
1410
     {7968,[951,787]},
 
1411
     {7984,[953,787]},
 
1412
     {8000,[959,787]},
 
1413
     {8164,[961,787]},
 
1414
     {8016,[965,787]},
 
1415
     {8032,[969,787]},
 
1416
     {8073,[913,837,788]},
 
1417
     {8089,[919,837,788]},
 
1418
     {8105,[937,837,788]},
 
1419
     {8065,[945,837,788]},
 
1420
     {8081,[951,837,788]},
 
1421
     {8097,[969,837,788]},
 
1422
     {7945,[913,788]},
 
1423
     {7961,[917,788]},
 
1424
     {7977,[919,788]},
 
1425
     {7993,[921,788]},
 
1426
     {8009,[927,788]},
 
1427
     {8172,[929,788]},
 
1428
     {8025,[933,788]},
 
1429
     {8041,[937,788]},
 
1430
     {7937,[945,788]},
 
1431
     {7953,[949,788]},
 
1432
     {7969,[951,788]},
 
1433
     {7985,[953,788]},
 
1434
     {8001,[959,788]},
 
1435
     {8165,[961,788]},
 
1436
     {8017,[965,788]},
 
1437
     {8033,[969,788]},
 
1438
     {416,[79,795]},
 
1439
     {431,[85,795]},
 
1440
     {417,[111,795]},
 
1441
     {432,[117,795]},
 
1442
     {7840,[65,803]},
 
1443
     {7684,[66,803]},
 
1444
     {7692,[68,803]},
 
1445
     {7864,[69,803]},
 
1446
     {7716,[72,803]},
 
1447
     {7882,[73,803]},
 
1448
     {7730,[75,803]},
 
1449
     {7734,[76,803]},
 
1450
     {7746,[77,803]},
 
1451
     {7750,[78,803]},
 
1452
     {7884,[79,803]},
 
1453
     {7770,[82,803]},
 
1454
     {7778,[83,803]},
 
1455
     {7788,[84,803]},
 
1456
     {7908,[85,803]},
 
1457
     {7806,[86,803]},
 
1458
     {7816,[87,803]},
 
1459
     {7924,[89,803]},
 
1460
     {7826,[90,803]},
 
1461
     {7841,[97,803]},
 
1462
     {7685,[98,803]},
 
1463
     {7693,[100,803]},
 
1464
     {7865,[101,803]},
 
1465
     {7717,[104,803]},
 
1466
     {7883,[105,803]},
 
1467
     {7731,[107,803]},
 
1468
     {7735,[108,803]},
 
1469
     {7747,[109,803]},
 
1470
     {7751,[110,803]},
 
1471
     {7885,[111,803]},
 
1472
     {7771,[114,803]},
 
1473
     {7779,[115,803]},
 
1474
     {7789,[116,803]},
 
1475
     {7909,[117,803]},
 
1476
     {7807,[118,803]},
 
1477
     {7817,[119,803]},
 
1478
     {7925,[121,803]},
 
1479
     {7827,[122,803]},
 
1480
     {7906,[79,795,803]},
 
1481
     {7920,[85,795,803]},
 
1482
     {7907,[111,795,803]},
 
1483
     {7921,[117,795,803]},
 
1484
     {7794,[85,804]},
 
1485
     {7795,[117,804]},
 
1486
     {7680,[65,805]},
 
1487
     {7681,[97,805]},
 
1488
     {199,[67,807]},
 
1489
     {7696,[68,807]},
 
1490
     {290,[71,807]},
 
1491
     {7720,[72,807]},
 
1492
     {310,[75,807]},
 
1493
     {315,[76,807]},
 
1494
     {325,[78,807]},
 
1495
     {342,[82,807]},
 
1496
     {350,[83,807]},
 
1497
     {354,[84,807]},
 
1498
     {231,[99,807]},
 
1499
     {7697,[100,807]},
 
1500
     {291,[103,807]},
 
1501
     {7721,[104,807]},
 
1502
     {311,[107,807]},
 
1503
     {316,[108,807]},
 
1504
     {326,[110,807]},
 
1505
     {343,[114,807]},
 
1506
     {351,[115,807]},
 
1507
     {355,[116,807]},
 
1508
     {260,[65,808]},
 
1509
     {280,[69,808]},
 
1510
     {302,[73,808]},
 
1511
     {490,[79,808]},
 
1512
     {370,[85,808]},
 
1513
     {261,[97,808]},
 
1514
     {281,[101,808]},
 
1515
     {303,[105,808]},
 
1516
     {491,[111,808]},
 
1517
     {371,[117,808]},
 
1518
     {7698,[68,813]},
 
1519
     {7704,[69,813]},
 
1520
     {7740,[76,813]},
 
1521
     {7754,[78,813]},
 
1522
     {7792,[84,813]},
 
1523
     {7798,[85,813]},
 
1524
     {7699,[100,813]},
 
1525
     {7705,[101,813]},
 
1526
     {7741,[108,813]},
 
1527
     {7755,[110,813]},
 
1528
     {7793,[116,813]},
 
1529
     {7799,[117,813]},
 
1530
     {7722,[72,814]},
 
1531
     {7723,[104,814]},
 
1532
     {7706,[69,816]},
 
1533
     {7724,[73,816]},
 
1534
     {7796,[85,816]},
 
1535
     {7707,[101,816]},
 
1536
     {7725,[105,816]},
 
1537
     {7797,[117,816]},
 
1538
     {7686,[66,817]},
 
1539
     {7694,[68,817]},
 
1540
     {7732,[75,817]},
 
1541
     {7738,[76,817]},
 
1542
     {7752,[78,817]},
 
1543
     {7774,[82,817]},
 
1544
     {7790,[84,817]},
 
1545
     {7828,[90,817]},
 
1546
     {7687,[98,817]},
 
1547
     {7695,[100,817]},
 
1548
     {7830,[104,817]},
 
1549
     {7733,[107,817]},
 
1550
     {7739,[108,817]},
 
1551
     {7753,[110,817]},
 
1552
     {7775,[114,817]},
 
1553
     {7791,[116,817]},
 
1554
     {7829,[122,817]},
 
1555
     {8129,[168,834]},
 
1556
     {8151,[953,776,834]},
 
1557
     {8167,[965,776,834]},
 
1558
     {8078,[913,837,787,834]},
 
1559
     {8094,[919,837,787,834]},
 
1560
     {8110,[937,837,787,834]},
 
1561
     {8070,[945,837,787,834]},
 
1562
     {8086,[951,837,787,834]},
 
1563
     {8102,[969,837,787,834]},
 
1564
     {7950,[913,787,834]},
 
1565
     {7982,[919,787,834]},
 
1566
     {7998,[921,787,834]},
 
1567
     {8046,[937,787,834]},
 
1568
     {7942,[945,787,834]},
 
1569
     {7974,[951,787,834]},
 
1570
     {7990,[953,787,834]},
 
1571
     {8022,[965,787,834]},
 
1572
     {8038,[969,787,834]},
 
1573
     {8079,[913,837,788,834]},
 
1574
     {8095,[919,837,788,834]},
 
1575
     {8111,[937,837,788,834]},
 
1576
     {8071,[945,837,788,834]},
 
1577
     {8087,[951,837,788,834]},
 
1578
     {8103,[969,837,788,834]},
 
1579
     {7951,[913,788,834]},
 
1580
     {7983,[919,788,834]},
 
1581
     {7999,[921,788,834]},
 
1582
     {8031,[933,788,834]},
 
1583
     {8047,[937,788,834]},
 
1584
     {7943,[945,788,834]},
 
1585
     {7975,[951,788,834]},
 
1586
     {7991,[953,788,834]},
 
1587
     {8023,[965,788,834]},
 
1588
     {8039,[969,788,834]},
 
1589
     {8119,[945,837,834]},
 
1590
     {8135,[951,837,834]},
 
1591
     {8183,[969,837,834]},
 
1592
     {8118,[945,834]},
 
1593
     {8134,[951,834]},
 
1594
     {8150,[953,834]},
 
1595
     {8166,[965,834]},
 
1596
     {8182,[969,834]},
 
1597
     {8143,[8127,834]},
 
1598
     {8159,[8190,834]},
 
1599
     {8124,[913,837]},
 
1600
     {8140,[919,837]},
 
1601
     {8188,[937,837]},
 
1602
     {8115,[945,837]},
 
1603
     {8131,[951,837]},
 
1604
     {8179,[969,837]},
 
1605
     {64302,[1488,1463]},
 
1606
     {64287,[1522,1463]},
 
1607
     {64303,[1488,1464]},
 
1608
     {64331,[1493,1465]},
 
1609
     {64304,[1488,1468]},
 
1610
     {64305,[1489,1468]},
 
1611
     {64306,[1490,1468]},
 
1612
     {64307,[1491,1468]},
 
1613
     {64308,[1492,1468]},
 
1614
     {64309,[1493,1468]},
 
1615
     {64310,[1494,1468]},
 
1616
     {64312,[1496,1468]},
 
1617
     {64313,[1497,1468]},
 
1618
     {64314,[1498,1468]},
 
1619
     {64315,[1499,1468]},
 
1620
     {64316,[1500,1468]},
 
1621
     {64318,[1502,1468]},
 
1622
     {64320,[1504,1468]},
 
1623
     {64321,[1505,1468]},
 
1624
     {64323,[1507,1468]},
 
1625
     {64324,[1508,1468]},
 
1626
     {64326,[1510,1468]},
 
1627
     {64327,[1511,1468]},
 
1628
     {64328,[1512,1468]},
 
1629
     {64329,[1513,1468]},
 
1630
     {64330,[1514,1468]},
 
1631
     {64332,[1489,1471]},
 
1632
     {64333,[1499,1471]},
 
1633
     {64334,[1508,1471]},
 
1634
     {64300,[1513,1468,1473]},
 
1635
     {64298,[1513,1473]},
 
1636
     {64301,[1513,1468,1474]},
 
1637
     {64299,[1513,1474]},
 
1638
     {2392,[2325,2364]},
 
1639
     {2393,[2326,2364]},
 
1640
     {2394,[2327,2364]},
 
1641
     {2395,[2332,2364]},
 
1642
     {2396,[2337,2364]},
 
1643
     {2397,[2338,2364]},
 
1644
     {2345,[2344,2364]},
 
1645
     {2398,[2347,2364]},
 
1646
     {2399,[2351,2364]},
 
1647
     {2353,[2352,2364]},
 
1648
     {2356,[2355,2364]},
 
1649
     {2524,[2465,2492]},
 
1650
     {2525,[2466,2492]},
 
1651
     {2480,[2476,2492]},
 
1652
     {2527,[2479,2492]},
 
1653
     {2507,[2503,2494]},
 
1654
     {2508,[2503,2519]},
 
1655
     {2649,[2582,2620]},
 
1656
     {2650,[2583,2620]},
 
1657
     {2651,[2588,2620]},
 
1658
     {2652,[2593,2620]},
 
1659
     {2654,[2603,2620]},
 
1660
     {2908,[2849,2876]},
 
1661
     {2909,[2850,2876]},
 
1662
     {2911,[2863,2876]},
 
1663
     {2891,[2887,2878]},
 
1664
     {2888,[2887,2902]},
 
1665
     {2892,[2887,2903]},
 
1666
     {3018,[3014,3006]},
 
1667
     {3019,[3015,3006]},
 
1668
     {2964,[2962,3031]},
 
1669
     {3020,[3014,3031]},
 
1670
     {3144,[3142,3158]},
 
1671
     {3274,[3270,3266]},
 
1672
     {3264,[3263,3285]},
 
1673
     {3275,[3270,3266,3285]},
 
1674
     {3271,[3270,3285]},
 
1675
     {3272,[3270,3286]},
 
1676
     {3402,[3398,3390]},
 
1677
     {3403,[3399,3390]},
 
1678
     {3404,[3398,3415]},
 
1679
     {3635,[3661,3634]},
 
1680
     {3763,[3789,3762]},
 
1681
     {3955,[3954,3953]},
 
1682
     {3957,[3956,3953]},
 
1683
     {3959,[4018,3968,3953]},
 
1684
     {3961,[4019,3968,3953]},
 
1685
     {3958,[4018,3968]},
 
1686
     {3960,[4019,3968]},
 
1687
     {3945,[3904,4021]},
 
1688
     {4025,[3984,4021]},
 
1689
     {3907,[3906,4023]},
 
1690
     {3917,[3916,4023]},
 
1691
     {3922,[3921,4023]},
 
1692
     {3927,[3926,4023]},
 
1693
     {3932,[3931,4023]},
 
1694
     {3987,[3986,4023]},
 
1695
     {3997,[3996,4023]},
 
1696
     {4002,[4001,4023]},
 
1697
     {4007,[4006,4023]},
 
1698
     {4012,[4011,4023]},
 
1699
     {12436,[12358,12441]},
 
1700
     {12364,[12363,12441]},
 
1701
     {12366,[12365,12441]},
 
1702
     {12368,[12367,12441]},
 
1703
     {12370,[12369,12441]},
 
1704
     {12372,[12371,12441]},
 
1705
     {12374,[12373,12441]},
 
1706
     {12376,[12375,12441]},
 
1707
     {12378,[12377,12441]},
 
1708
     {12380,[12379,12441]},
 
1709
     {12382,[12381,12441]},
 
1710
     {12384,[12383,12441]},
 
1711
     {12386,[12385,12441]},
 
1712
     {12389,[12388,12441]},
 
1713
     {12391,[12390,12441]},
 
1714
     {12393,[12392,12441]},
 
1715
     {12400,[12399,12441]},
 
1716
     {12403,[12402,12441]},
 
1717
     {12406,[12405,12441]},
 
1718
     {12409,[12408,12441]},
 
1719
     {12412,[12411,12441]},
 
1720
     {12446,[12445,12441]},
 
1721
     {12532,[12454,12441]},
 
1722
     {12460,[12459,12441]},
 
1723
     {12462,[12461,12441]},
 
1724
     {12464,[12463,12441]},
 
1725
     {12466,[12465,12441]},
 
1726
     {12468,[12467,12441]},
 
1727
     {12470,[12469,12441]},
 
1728
     {12472,[12471,12441]},
 
1729
     {12474,[12473,12441]},
 
1730
     {12476,[12475,12441]},
 
1731
     {12478,[12477,12441]},
 
1732
     {12480,[12479,12441]},
 
1733
     {12482,[12481,12441]},
 
1734
     {12485,[12484,12441]},
 
1735
     {12487,[12486,12441]},
 
1736
     {12489,[12488,12441]},
 
1737
     {12496,[12495,12441]},
 
1738
     {12499,[12498,12441]},
 
1739
     {12502,[12501,12441]},
 
1740
     {12505,[12504,12441]},
 
1741
     {12508,[12507,12441]},
 
1742
     {12535,[12527,12441]},
 
1743
     {12536,[12528,12441]},
 
1744
     {12537,[12529,12441]},
 
1745
     {12538,[12530,12441]},
 
1746
     {12542,[12541,12441]},
 
1747
     {12401,[12399,12442]},
 
1748
     {12404,[12402,12442]},
 
1749
     {12407,[12405,12442]},
 
1750
     {12410,[12408,12442]},
 
1751
     {12413,[12411,12442]},
 
1752
     {12497,[12495,12442]},
 
1753
     {12500,[12498,12442]},
 
1754
     {12503,[12501,12442]},
 
1755
     {12506,[12504,12442]},
 
1756
     {12509,[12507,12442]}}.