~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/wx/api_gen/wx_gen_erl.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2008-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
19
19
%%%-------------------------------------------------------------------
20
20
%%% File    : wx_gen_erl.erl
21
21
%%% Author  : Dan Gudmundsson <dgud@erix.ericsson.se>
22
 
%%% Description : 
 
22
%%% Description :
23
23
%%%
24
24
%%% Created : 25 Jan 2007 by Dan Gudmundsson <dgud@erix.ericsson.se>
25
25
%%%-------------------------------------------------------------------
32
32
 
33
33
-import(lists, [foldl/3,foldr/3,reverse/1, keysearch/3, map/2, filter/2]).
34
34
-import(gen_util, [lowercase/1, lowercase_all/1, uppercase/1, uppercase_all/1,
35
 
                   open_write/1, close/0, erl_copyright/0, w/2, 
 
35
                   open_write/1, close/0, erl_copyright/0, w/2,
36
36
                   args/3, args/4, strip_name/2]).
37
37
 
38
38
gen(Defs) ->
42
42
    gen_enums_ints(),
43
43
    [gen_class(Class) || Class <- Defs],
44
44
    gen_funcnames().
45
 
        
 
45
 
46
46
gen_class(Class) ->
47
 
    try 
 
47
    try
48
48
        gen_class1(Class)
49
49
    catch throw:skipped ->
50
50
            Class
52
52
 
53
53
gen_class1(C=#class{name=Name,parent="static",methods=Ms,options=_Opts}) ->
54
54
    open_write("../src/gen/wx_misc.erl"),
55
 
    put(current_class, Name), 
 
55
    put(current_class, Name),
56
56
    erl_copyright(),
57
57
    w("", []),
58
 
    w("%% This file is generated DO NOT EDIT~n~n", []),    
 
58
    w("%% This file is generated DO NOT EDIT~n~n", []),
59
59
    w("%% @doc See external documentation: "
60
60
      "<a href=\"http://www.wxwidgets.org/manuals/stable/wx_miscellany.html\">Misc</a>.\n\n",[]),
61
61
 
67
67
    Exp = fun(M) -> gen_export(C,M) end,
68
68
    ExportList = lists:usort(lists:append(lists:map(Exp,reverse(Ms)))),
69
69
    w("-export([~s]).~n~n", [args(fun(EF) -> EF end, ",", ExportList, 60)]),
70
 
    
71
 
    
 
70
 
 
71
 
72
72
    Gen = fun(M) -> gen_method(Name,M) end,
73
73
    NewMs = lists:map(Gen,reverse(Ms)),
74
74
    close(),
79
79
    case Opts of
80
80
        ["ignore"] -> throw(skipped);
81
81
        _ -> ok
82
 
    end,    
 
82
    end,
83
83
    open_write("../src/gen/"++Name++".erl"),
84
 
    put(current_class, Name), 
 
84
    put(current_class, Name),
85
85
    erl_copyright(),
86
86
    w("", []),
87
 
    w("%% This file is generated DO NOT EDIT~n~n", []),    
88
 
    
 
87
    w("%% This file is generated DO NOT EDIT~n~n", []),
 
88
 
89
89
    case lists:member(taylormade, Opts) of
90
90
        true ->
91
91
            {ok, Bin} = file:read_file(filename:join([wx_extra, Name++".erl"])),
95
95
            w("%% @doc See external documentation: "
96
96
              "<a href=\"http://www.wxwidgets.org/manuals/stable/wx_~s.html\">~s</a>.\n",
97
97
              [lowercase_all(Name), Name]),
98
 
            
 
98
 
99
99
            case C#class.doc of
100
100
                undefined -> ignore;
101
101
                Str -> w("%%~n%% ~s~n~n%%~n", [Str])
102
102
            end,
103
 
            
 
103
 
104
104
            case C#class.event of
105
105
                false -> ignore;
106
106
                Evs ->
107
107
                    EvTypes = [event_type_name(Ev) || Ev <- Evs],
108
108
                    EvStr = args(fun(Ev) -> "<em>"++Ev++"</em>" end, ", ", EvTypes),
109
 
                    
 
109
 
110
110
                    w("%% <dl><dt>Use {@link wxEvtHandler:connect/3.} with EventType:</dt>~n",[]),
111
111
                    w("%% <dd>~s</dd></dl>~n", [EvStr]),
112
 
                    w("%% See also the message variant {@link wxEvtHandler:~s(). #~s{}} event record type.~n", 
 
112
                    w("%% See also the message variant {@link wxEvtHandler:~s(). #~s{}} event record type.~n",
113
113
                      [event_rec_name(Name),event_rec_name(Name)]),
114
114
                    w("%%~n",[]),
115
115
                    ok
116
116
            end,
117
 
            
 
117
 
118
118
            Parents = parents(Parent),
119
119
            case [P || P <- Parents, P =/= root, P =/= object] of
120
120
                [] -> ignore;
121
 
                Ps -> 
 
121
                Ps ->
122
122
                    w("%% <p>This class is derived (and can use functions) from:~n", []),
123
123
                    [w("%% <br />{@link ~s}~n", [P]) || P <- Ps],
124
 
                    w("%% </p>~n",[])               
 
124
                    w("%% </p>~n",[])
125
125
            end,
126
126
            w("%% @type ~s().  An object reference, The representation is internal~n",[Name]),
127
127
            w("%% and can be changed without notice. It can't be used for comparsion~n", []),
137
137
            Done0 = ["Destroy", "New", "Create", "destroy", "new", "create"],
138
138
            Done  = gb_sets:from_list(Done0 ++ [M|| #method{name=M} <- lists:append(Ms)]),
139
139
            {_, InExported} = gen_inherited(Parents, Done, []),
140
 
            w("-export([~s]).~n~n", [args(fun(EF) -> EF end, ",", 
141
 
                                          lists:usort(["parent_class/1"|InExported]), 
 
140
            w("-export([~s]).~n~n", [args(fun(EF) -> EF end, ",",
 
141
                                          lists:usort(["parent_class/1"|InExported]),
142
142
                                          60)]),
143
 
    
 
143
 
144
144
            w("%% @hidden~n", []),
145
145
            parents_check(Parents),
146
 
            
 
146
 
147
147
            Gen = fun(M) -> gen_method(Name,M) end,
148
148
            NewMs = lists:map(Gen,reverse(Ms)),
149
 
            gen_dest(C, Ms),        
150
 
            
 
149
            gen_dest(C, Ms),
 
150
 
151
151
            gen_inherited(Parents, Done, true)
152
152
    end,
153
153
 
203
203
        [] -> [];
204
204
        [M=#method{where=taylormade}|_] ->
205
205
            [taylormade_export(Class, M)];
206
 
        Ms -> 
 
206
        Ms ->
207
207
            GetF = fun(#method{method_type=constructor,where=W,params=Ps}) ->
208
208
                           {Args,Opts} = split_optional(Ps),
209
 
                           OptLen = case Opts of 
210
 
                                        [] -> 0; 
 
209
                           OptLen = case Opts of
 
210
                                        [] -> 0;
211
211
                                        _ when W =:= erl_no_opt -> 0;
212
 
                                        _ -> 1 
 
212
                                        _ -> 1
213
213
                                    end,
214
214
                           "new/" ++ integer_to_list(length(Args)+OptLen);
215
215
                      (#method{method_type=destructor}) ->
216
 
                           case Abs of 
217
 
                               true -> []; 
 
216
                           case Abs of
 
217
                               true -> [];
218
218
                               _ -> "destroy/1"
219
219
                           end;
220
220
                      (#method{name=N,alias=A,where=W, params=Ps}) ->
221
221
                           {Args,Opts} = split_optional(Ps),
222
 
                           OptLen = case Opts of 
223
 
                                        [] -> 0; 
 
222
                           OptLen = case Opts of
 
223
                                        [] -> 0;
224
224
                                        _ when W =:= erl_no_opt -> 0;
225
 
                                        _ -> 1 
 
225
                                        _ -> 1
226
226
                                    end,
227
227
                           erl_func_name(N,A) ++ "/" ++ integer_to_list(length(Args) + OptLen)
228
228
                   end,
235
235
    Res = filter(RemoveC, Ms0),
236
236
    case Res of
237
237
        [] -> Ms0;
238
 
        [M=#method{where=taylormade}|_] ->
239
 
            taylormade_func(Class, M),
 
238
        [#method{where=taylormade}|_] ->
 
239
            taylormade_func(Class, Res),
240
240
            Ms0;
241
 
        Ms -> 
 
241
        Ms ->
242
242
            gen_doc(Class,Ms),
243
243
            gen_method1(Ms),
244
244
            Ms0
279
279
        ignore -> skip;
280
280
        _ -> w("  _Result =", [])
281
281
    end,
282
 
    
 
282
 
283
283
    case have_return_vals(T, Ps) of
284
284
        _ when MT =:= constructor ->
285
285
            w("  wxe_util:construct(~s,~n  <<~s~s>>)", [MId, MArgs,MOpts]);
286
286
        true ->
287
287
            w("  wxe_util:call(~s,~n  <<~s~s>>)", [MId, MArgs,MOpts]);
288
 
        false -> 
 
288
        false ->
289
289
            w("  wxe_util:cast(~s,~n  <<~s~s>>)", [MId, MArgs,MOpts])
290
290
    end,
291
291
    case gen_util:get_hook(erl, M#method.post_hook) of
292
292
        ignore -> skip;
293
 
        Post -> 
 
293
        Post ->
294
294
            w(",~n  ~s~n", [Post]),
295
295
            w("  _Result", [])
296
296
    end,
297
 
   
 
297
 
298
298
    erase(current_func),
299
299
    M.
300
300
 
306
306
            case lists:keysearch(destructor,#method.method_type, lists:append(Ms)) of
307
307
                {value, #method{method_type=destructor, id=Id}} ->
308
308
                    case hd(reverse(parents(CName))) of
309
 
                        object -> 
 
309
                        object ->
310
310
                            gen_dest2(CName, object);
311
 
                        root -> 
 
311
                        root ->
312
312
                            gen_dest2(CName, Id)
313
313
                    end;
314
314
                false ->
320
320
    w("%% @spec (This::~s()) -> ok~n", [Class]),
321
321
    w("%% @doc Destroys this object, do not use object again~n", []),
322
322
    w("destroy(Obj=#wx_ref{type=Type}) ->~n", []),
323
 
    w("  ?CLASS(Type,~s),~n",[Class]), 
 
323
    w("  ?CLASS(Type,~s),~n",[Class]),
324
324
    case Id of
325
325
        object ->
326
326
            w("  wxe_util:destroy(?DESTROY_OBJECT,Obj),~n  ok.~n", []);
341
341
    gen_inherited(Ps, gb_sets:union(Done,Done0), Exported).
342
342
 
343
343
gen_inherited_ms([[#method{name=Name,alias=A,params=Ps0,where=W,method_type=MT}|_]|R],
344
 
                 Class,Skip,Done, Exported) 
345
 
  when W =/= merged_c ->    
 
344
                 Class,Skip,Done, Exported)
 
345
  when W =/= merged_c ->
346
346
    case gb_sets:is_member(Name,Skip) of
347
347
        false when MT =:= member, Exported =:= true ->
348
348
            Ps = [patch_param(P,all) || P <- Ps0],
349
349
            Opts = if W =:= erl_no_opt -> [];
350
 
                      true -> 
351
 
                           [Opt || Opt = #param{def=Def,in=In, where=Where} <- Ps, 
 
350
                      true ->
 
351
                           [Opt || Opt = #param{def=Def,in=In, where=Where} <- Ps,
352
352
                                   Def =/= none, In =/= false, Where =/= c]
353
353
                   end,
354
354
            w("%% @hidden~n", []),
359
359
            gen_inherited_ms(R,Class, Skip, gb_sets:add(Name,Done), Exported);
360
360
        false when MT =:= member, is_list(Exported) ->
361
361
            {Args,Opts} = split_optional(Ps0),
362
 
            OptLen = case Opts of 
363
 
                         [] -> 0; 
 
362
            OptLen = case Opts of
 
363
                         [] -> 0;
364
364
                         _ when W =:= erl_no_opt -> 0;
365
 
                         _ -> 1 
 
365
                         _ -> 1
366
366
                     end,
367
367
            Export = erl_func_name(Name,A) ++ "/" ++ integer_to_list(length(Args) + OptLen),
368
368
            gen_inherited_ms(R,Class,Skip, gb_sets:add(Name,Done), [Export|Exported]);
374
374
gen_inherited_ms([[]|R],Class,Skip,Done0,Exp) ->
375
375
    gen_inherited_ms(R,Class,Skip,Done0,Exp);
376
376
gen_inherited_ms([], _, _Skip, Done,Exp) -> {Done,Exp}.
377
 
    
 
377
 
378
378
 
379
379
%%%%%%%%%%%%%%%
380
380
 
381
 
taylormade_func(Class, #method{name=Name, id=Id}) ->
 
381
taylormade_func(Class, [#method{name=Name, id=Id}|_]) ->
382
382
    {ok, Bin} = file:read_file(filename:join([wx_extra, Class ++".erl"])),
383
 
    Str0 = binary_to_list(Bin),
384
 
    {match, [Str1]} = re:run(Str0, "<<"++Name++"(.*)"++Name++">>",
385
 
                             [dotall, {capture, all_but_first, list}]),
386
 
    
387
 
    w(Str1, ["?" ++ get_unique_name(Id)]),
 
383
    Src = binary_to_list(Bin),
 
384
    Str = case gen_util:get_taylor_made(Src, Name) of
 
385
              nomatch ->
 
386
                  {match, [Str0]} = gen_util:get_taylor_made(Src, get_unique_name(Id)),
 
387
                  Str0;
 
388
              {match, [Str0]} ->
 
389
                  Str0
 
390
          end,
 
391
    w(Str, ["?" ++ get_unique_name(Id)]),
388
392
    ok.
389
393
 
390
394
taylormade_export(Class, #method{name=Name}) ->
398
402
 
399
403
arg_type_tests([P|Ps], Mid0) ->
400
404
    case arg_type_test(P,"\n",Mid0) of
401
 
        Mid0 -> 
 
405
        Mid0 ->
402
406
            arg_type_tests(Ps, Mid0);
403
407
        Mid ->  %% Already checked the other args
404
408
            Mid
405
409
    end;
406
 
arg_type_tests([],Mid) -> Mid.        
 
410
arg_type_tests([],Mid) -> Mid.
407
411
 
408
412
arg_type_test(#param{where=c}, _, Acc) ->
409
413
    Acc;
412
416
    Name = erl_arg_name(Name0),
413
417
    w("  ?CLASS(~sT,~s),~s", [Name,T,EOS]),
414
418
    Acc;
415
 
arg_type_test(#param{name=Name0,in=In,type=#type{base={class,T}}, def=none},EOS,Acc) 
 
419
arg_type_test(#param{name=Name0,in=In,type=#type{base={class,T}}, def=none},EOS,Acc)
416
420
  when In =/= false ->
417
421
    Name = erl_arg_name(Name0),
418
422
    w("  [?CLASS(~sT,~s) || #wx_ref{type=~sT} <- ~s],~s", [Name,T,Name,Name,EOS]),
420
424
arg_type_test(#param{name=Name0,def=none,in=In,
421
425
                     type={merged,
422
426
                           M1, #type{base={class,T1},single=true},Ps1,
423
 
                           M2, #type{base={class,T2},single=true},Ps2}}, EOS, _Acc) 
 
427
                           M2, #type{base={class,T2},single=true},Ps2}}, EOS, _Acc)
424
428
  when In =/= false ->
425
429
    Name = erl_arg_name(Name0),
426
430
    Opname = Name++"OP",
427
431
    w("  ~s = case ?CLASS_T(~sT,~s) of~n     true ->\n       ", [Opname,Name,T1]),
428
 
    lists:foreach(fun(Param) -> arg_type_test(Param,"\n       ", ignore) end, 
 
432
    lists:foreach(fun(Param) -> arg_type_test(Param,"\n       ", ignore) end,
429
433
                  element(1,split_optional(Ps1))),
430
434
    w("?~s;~n",[get_unique_name(M1)]),
431
435
    w("     _ -> ?CLASS(~sT,~s),\n       ",[Name,T2]),
432
436
    {Ps21,_} = split_optional(patchArgName(Ps2,Ps1)),
433
 
    lists:foreach(fun(Param) -> arg_type_test(Param,"\n       ", ignore) end, 
 
437
    lists:foreach(fun(Param) -> arg_type_test(Param,"\n       ", ignore) end,
434
438
                  Ps21),
435
439
    w("?~s\n     end,~s",[get_unique_name(M2),EOS]),
436
440
    Opname;
437
 
arg_type_test(#param{name=Name0, type=#type{base=eventType}}, EOS, Acc) -> 
 
441
arg_type_test(#param{name=Name0, type=#type{base=eventType}}, EOS, Acc) ->
438
442
    Name = erl_arg_name(Name0),
439
443
    w("  ~sBin = list_to_binary([atom_to_list(~s)|[0]]),~s", [Name,Name,EOS]),
440
444
    w("  ThisTypeBin = list_to_binary([atom_to_list(ThisT)|[0]]),~s", [EOS]),
441
445
    Acc;
442
 
arg_type_test(#param{name=Name0,def=none,type=#type{base={term,_}}}, EOS, Acc) -> 
 
446
arg_type_test(#param{name=Name0,def=none,type=#type{base={term,_}}}, EOS, Acc) ->
443
447
    Name = erl_arg_name(Name0),
444
448
    w("  wxe_util:send_bin(term_to_binary(~s)),~s", [Name,EOS]),
445
449
    Acc;
446
 
arg_type_test(#param{name=Name0,type=#type{base=binary}},EOS,Acc) -> 
 
450
arg_type_test(#param{name=Name0,type=#type{base=binary}},EOS,Acc) ->
447
451
    Name = erl_arg_name(Name0),
448
452
    w("  wxe_util:send_bin(~s),~s", [Name,EOS]),
449
453
    Acc;
450
 
arg_type_test(#param{name=Name0,type=#type{name=Type,base=Base,single=Single}},EOS,Acc) -> 
451
 
    if 
 
454
arg_type_test(#param{name=Name0,type=#type{name=Type,base=Base,single=Single}},EOS,Acc) ->
 
455
    if
452
456
        Type =:= "wxArtClient", Single =:= true ->
453
457
            Name = erl_arg_name(Name0),
454
458
            w("  ~s_UC = unicode:characters_to_binary([~s, $_, $C,0]),~s",
458
462
            w("  ~s_UC = unicode:characters_to_binary([~s,0]),~s", [Name,Name,EOS]);
459
463
        Type =:= "wxArrayString" ->
460
464
            Name = erl_arg_name(Name0),
461
 
            w("  ~s_UCA = [unicode:characters_to_binary([~sTemp,0]) || ~s", 
 
465
            w("  ~s_UCA = [unicode:characters_to_binary([~sTemp,0]) || ~s",
462
466
              [Name,Name, EOS]),
463
467
            w("              ~sTemp <- ~s],~s", [Name,Name,EOS]);
464
468
        true -> %% Not a string
465
 
            ignore 
 
469
            ignore
466
470
    end,
467
471
    Acc;
468
472
arg_type_test(_,_,Acc) -> Acc.
476
480
have_return_vals(#type{}, _) -> true.
477
481
 
478
482
gen_function_clause(Name0,MT,Ps,Optional,Variant) ->
479
 
    PArg = fun(Arg) -> 
 
483
    PArg = fun(Arg) ->
480
484
                   case lists:member(name_only, Variant) of
481
485
                       true -> func_arg_name(Arg);
482
 
                       false -> 
 
486
                       false ->
483
487
                           case lists:member(name_type, Variant) of
484
488
                               true ->
485
489
                                   Name = func_arg_name(Arg),
495
499
    Args = args(PArg, ",", Ps),
496
500
    Name = case MT of constructor -> "new"; _ -> Name0 end,
497
501
    w("~s(~s",[Name,Args]),
498
 
    Opts = case Optional of 
 
502
    Opts = case Optional of
499
503
               [] -> "";
500
504
               empty_list when Args =:= [] -> "[]";
501
505
               empty_list -> ", []";
502
506
               _ when Args =:= [] -> "Options";
503
 
               _ -> ", Options" 
 
507
               _ -> ", Options"
504
508
           end,
505
509
    w("~s)", [Opts]),
506
510
    case lists:member(no_guards, Variant) of
507
511
        true ->  ok;
508
 
        false -> 
 
512
        false ->
509
513
            Guards = args(fun guard_test/1, ",", Ps),
510
514
            if
511
515
                Guards =:= [], Opts =:= "" -> w(" ->~n", []);
517
521
 
518
522
split_optional(Ps) ->
519
523
    split_optional(Ps, [], []).
520
 
split_optional([P=#param{def=Def,in=In, where=Where}|Ps], Standard, Opts) 
 
524
split_optional([P=#param{def=Def,in=In, where=Where}|Ps], Standard, Opts)
521
525
  when Def =/= none, In =/= false, Where =/= c ->
522
526
    split_optional(Ps, Standard, [P|Opts]);
523
 
split_optional([P=#param{def=Def,in=In, where=Where}|Ps], Standard, Opts) 
 
527
split_optional([P=#param{def=Def,in=In, where=Where}|Ps], Standard, Opts)
524
528
  when Def =:= none, In =/= false, Where =/= c ->
525
529
    split_optional(Ps, [P|Standard], Opts);
526
530
split_optional([_|Ps], Standard, Opts) ->
532
536
    P#param{type={class,ignore}};
533
537
patch_param(P=#param{type={merged,_,_,_,_,_,_}}, _) ->
534
538
    P#param{type={class,ignore}};
535
 
patch_param(P=#param{type=#type{base={class,_}}},_) -> 
 
539
patch_param(P=#param{type=#type{base={class,_}}},_) ->
536
540
    P#param{type={class,ignore}};
537
 
patch_param(P=#param{type=#type{base={ref,_}}},_) -> 
 
541
patch_param(P=#param{type=#type{base={ref,_}}},_) ->
538
542
    P#param{type={class,ignore}};
539
543
patch_param(P,_) -> P.
540
544
 
541
545
func_arg_name(#param{def=Def}) when Def =/= none -> skip;
542
546
func_arg_name(#param{in=false}) -> skip;
543
547
func_arg_name(#param{where=c}) -> skip;
544
 
func_arg_name(#param{name=Name}) -> 
 
548
func_arg_name(#param{name=Name}) ->
545
549
    erl_arg_name(Name).
546
550
 
547
551
func_arg(#param{def=Def}) when Def =/= none -> skip;
548
552
func_arg(#param{in=false}) -> skip;
549
553
func_arg(#param{where=c}) -> skip;
550
 
func_arg(#param{name=Name,type=#type{base=string}}) -> 
 
554
func_arg(#param{name=Name,type=#type{base=string}}) ->
551
555
    erl_arg_name(Name);
552
 
func_arg(#param{name=Name,type=#type{name="wxArrayString"}}) -> 
 
556
func_arg(#param{name=Name,type=#type{name="wxArrayString"}}) ->
553
557
    erl_arg_name(Name);
554
558
func_arg(#param{name=Name0,type=#type{base={class,_CN}, single=true}}) ->
555
559
    Name = erl_arg_name(Name0),
570
574
func_arg(#param{name=Name,type=#type{name="wxArtClient", single=true}}) ->
571
575
    erl_arg_name(Name);
572
576
func_arg(#param{name=Name,type=#type{base={comp,_,Tup}, single=true}}) ->
573
 
    N = erl_arg_name(Name),    
 
577
    N = erl_arg_name(Name),
574
578
    Doc = fun({_,V}) -> erl_arg_name(N)++V end,
575
579
    "{" ++ args(Doc, ",", Tup) ++ "}";
576
580
func_arg(#param{name=Name}) ->
587
591
    "is_list(" ++ erl_arg_name(N) ++")";
588
592
guard_test(#param{name=N, type=#type{name="wxArrayString"}}) ->
589
593
    "is_list(" ++ erl_arg_name(N) ++")";
590
 
guard_test(#param{name=Name,type=#type{single=Single}}) 
 
594
guard_test(#param{name=Name,type=#type{single=Single}})
591
595
  when Single =/= true->
592
596
    "is_list(" ++ erl_arg_name(Name) ++  ")";
593
597
guard_test(#param{name=N,type=#type{base=int}}) ->
637
641
    gen_function_clause(erl_func_name(N,A),MT,Ps,empty_list,[no_guards,name_only]);
638
642
gen_doc(Class,[#method{name=N,params=Ps,type=T}])->
639
643
    {_, Optional} = split_optional(Ps),
640
 
    NonDef = [Arg || Arg = #param{def=Def,in=In, where=Where} <- Ps, 
 
644
    NonDef = [Arg || Arg = #param{def=Def,in=In, where=Where} <- Ps,
641
645
                     Def =:= none, In =/= false, Where =/= c],
642
646
    OptsType = case Optional of
643
647
                   [] -> "";
644
648
                   _ when NonDef =:= [] -> "[Option]";
645
 
                   _ -> ", [Option]"           
 
649
                   _ -> ", [Option]"
646
650
               end,
647
651
    w("%% @spec (~s~s) -> ~s~n",
648
652
      [doc_arg_types(Ps),OptsType,doc_return_types(T,Ps)]),
649
653
    doc_optional(Optional, normal),
650
 
    DocEnum = doc_enum(T,Ps, normal),   
 
654
    DocEnum = doc_enum(T,Ps, normal),
651
655
    case Class of
652
656
        "utils" ->
653
657
            w("%% @doc See <a href=\"http://www.wxwidgets.org/manuals/stable/wx_miscellany.html#~s\">"
654
 
              "external documentation</a>.~n", 
 
658
              "external documentation</a>.~n",
655
659
              [lowercase_all(N)]);
656
660
        _ ->
657
661
            w("%% @doc See <a href=\"http://www.wxwidgets.org/manuals/stable/wx_~s.html#~s~s\">"
658
 
              "external documentation</a>.~n", 
 
662
              "external documentation</a>.~n",
659
663
              [lowercase_all(Class),lowercase_all(Class),lowercase_all(N)])
660
664
    end,
661
665
    doc_enum_desc(DocEnum);
662
666
gen_doc(Class, Cs = [#method{name=N, alias=A,method_type=MT}|_]) ->
663
 
    GetRet  = fun(#method{params=Ps,type=T}) -> 
 
667
    GetRet  = fun(#method{params=Ps,type=T}) ->
664
668
                      doc_return_types(T,Ps)
665
669
              end,
666
 
    GetArgs = fun(#method{params=Ps, where=Where}) -> 
 
670
    GetArgs = fun(#method{params=Ps, where=Where}) ->
667
671
                      Opt = case Where of
668
672
                                erl_no_opt -> [];
669
 
                                _ -> 
 
673
                                _ ->
670
674
                                    case split_optional(Ps) of
671
675
                                        {_, []} -> [];
672
676
                                        _ ->  ["[Option]"]
673
677
                                    end
674
678
                            end,
675
 
                      [doc_arg_type(P) || 
 
679
                      [doc_arg_type(P) ||
676
680
                          P=#param{in=In,def=none,where=W} <- Ps,
677
681
                          In =/= false, W =/= c] ++ Opt
678
682
              end,
682
686
    case Class of
683
687
        "utils" ->
684
688
            w("%% @doc See <a href=\"http://www.wxwidgets.org/manuals/stable/wx_miscellany.html#~s\">"
685
 
              "external documentation</a>.~n", 
 
689
              "external documentation</a>.~n",
686
690
              [lowercase_all(N)]);
687
691
        _ ->
688
692
            w("%% @doc See <a href=\"http://www.wxwidgets.org/manuals/stable/wx_~s.html#~s~s\">"
689
 
              "external documentation</a>.~n", 
 
693
              "external documentation</a>.~n",
690
694
              [lowercase_all(Class),lowercase_all(Class),lowercase_all(N)])
691
695
    end,
692
696
    Name = case MT of constructor -> "new"; _ -> erl_func_name(N,A) end,
693
697
    w("%% <br /> Alternatives:~n",[]),
694
 
    [gen_doc2(Name, Clause) || Clause <- Cs], 
 
698
    [gen_doc2(Name, Clause) || Clause <- Cs],
695
699
    ok.
696
700
 
697
701
gen_doc2(Name,#method{params=Ps,where=erl_no_opt,method_type=MT}) ->
704
708
    OptsType = case Optional of
705
709
                   [] -> "";
706
710
                   _ when NonDef =:= [] -> "[Option]";
707
 
                   _ -> ", [Option]"           
 
711
                   _ -> ", [Option]"
708
712
               end,
709
713
    w("%% <p><c>~n",[]),
710
714
    w("%% ~s(~s~s) -> ~s </c>~n",
711
 
      [Name,doc_arg_types(Ps),OptsType,doc_return_types(T,Ps)]),    
 
715
      [Name,doc_arg_types(Ps),OptsType,doc_return_types(T,Ps)]),
712
716
    doc_optional(Optional, xhtml),
713
717
    DocEnum = doc_enum(T,Ps, xhtml),
714
718
    doc_enum_desc(DocEnum),
717
721
doc_arg(ArgList) ->
718
722
    case all_eq(ArgList) of
719
723
        true ->  hd(ArgList);
720
 
        false -> 
 
724
        false ->
721
725
            Get = fun(Str) ->
722
726
                          [_Name|Types] = string:tokens(Str, ":"),
723
727
                          case Types of
734
738
doc_ret(ArgList) ->
735
739
    case all_eq(ArgList) of
736
740
        true ->  hd(ArgList);
737
 
        false -> 
 
741
        false ->
738
742
            args(fun(A) -> A end, "|", ArgList)
739
743
    end.
740
744
 
741
745
unique([], U) -> reverse(U);
742
 
unique([H|R], U) -> 
 
746
unique([H|R], U) ->
743
747
    case lists:member(H,U) of
744
748
        false -> unique(R,[H|U]);
745
749
        true  -> unique(R,U)
756
760
 
757
761
zip([[F|L1]|List], Rest, AccL, Acc) ->
758
762
    zip(List, [L1|Rest], [F|AccL], Acc);
759
 
zip(Empty, Rest, AccL, Acc) -> 
 
763
zip(Empty, Rest, AccL, Acc) ->
760
764
    true = empty(Empty),
761
765
    case empty(Rest) andalso empty(AccL) of
762
766
        true -> reverse(Acc);
779
783
 
780
784
doc_arg_type2(T=#type{single=Single}) when Single =:= array; Single =:= list ->
781
785
    "[" ++ doc_arg_type3(T) ++ "]";
782
 
doc_arg_type2(T) -> 
 
786
doc_arg_type2(T) ->
783
787
    doc_arg_type3(T).
784
788
 
785
789
doc_arg_type3(#type{base=string}) -> "string()";
799
803
doc_arg_type3(#type{base=eventType}) ->  "atom()";
800
804
doc_arg_type3(#type{base={ref,N}}) ->     N++"()";
801
805
doc_arg_type3(#type{base={term,_N}}) ->  "term()";
802
 
doc_arg_type3(T=#type{base={class,N}}) -> 
803
 
    check_class(T),   
 
806
doc_arg_type3(T=#type{base={class,N}}) ->
 
807
    check_class(T),
804
808
    case get(current_class) of
805
809
        N -> N ++ "()";
806
810
        _ ->  N++":" ++ N++"()"
809
813
    check_class(T1),
810
814
    check_class(T2),
811
815
    Curr = get(current_class),
812
 
    if 
 
816
    if
813
817
        N1 =:= Curr, N2 =:= Curr ->  N1++"() | "++ N2++"()";
814
818
        N1 =:= Curr -> N1++"() | "++ N2++":" ++ N2++"()";
815
819
        N2 =:= Curr -> N1++":" ++ N1++"() | "++ N2++"()";
824
828
    "wx:" ++ atom_to_list(Name) ++ "()";
825
829
doc_arg_type3(#type{base={comp,_,Tup}}) ->
826
830
    Doc = fun({int,V}) -> V ++ "::integer()";
827
 
             ({double,V}) -> V ++ "::float()" 
 
831
             ({double,V}) -> V ++ "::float()"
828
832
          end,
829
 
    "{" ++ args(Doc, ",", Tup) ++ "}";
 
833
    "{" ++ args(Doc, ", ", Tup) ++ "}";
830
834
doc_arg_type3(T) -> ?error({unknown_type,T}).
831
835
 
832
836
doc_return_types(T, Ps) ->
834
838
doc_return_types2(void, []) ->    "ok";
835
839
doc_return_types2(void, [#param{type=T}]) ->     doc_arg_type2(T);
836
840
doc_return_types2(T, []) ->                      doc_arg_type2(T);
837
 
doc_return_types2(void, Ps) -> 
838
 
    "{" ++ args(fun doc_arg_type/1,",",Ps) ++ "}";
 
841
doc_return_types2(void, Ps) ->
 
842
    "{" ++ args(fun doc_arg_type/1,", ",Ps) ++ "}";
839
843
doc_return_types2(T, Ps) ->
840
 
    "{" ++ doc_arg_type2(T) ++ "," ++ args(fun doc_arg_type/1,",",Ps) ++ "}".
 
844
    "{" ++ doc_arg_type2(T) ++ ", " ++ args(fun doc_arg_type/1,", ",Ps) ++ "}".
841
845
 
842
846
break(xhtml) -> "<br />";
843
847
break(_) ->     "".
887
891
 
888
892
marshal_opts([], _,_) -> "";     %% No opts skip this!
889
893
marshal_opts(Opts, Align, Args) ->
890
 
    w("  MOpts = fun", []), 
 
894
    w("  MOpts = fun", []),
891
895
    marshal_opts1(Opts,1),
892
896
    w(";~n          (BadOpt, _) -> erlang:error({badoption, BadOpt}) end,~n", []),
893
897
    w("  BinOpt = list_to_binary(lists:foldl(MOpts, [<<0:32>>], Options)),~n", []),
896
900
        [] -> Str;   % All Args are optional
897
901
        _ ->    ", " ++ Str
898
902
    end.
899
 
    
 
903
 
900
904
marshal_opts1([P],N) ->
901
905
    marshal_opt(P,N);
902
906
marshal_opts1([P|R],N) ->
909
913
    {Arg,Align} = marshal_arg(Type,erl_arg_name(Name),1),
910
914
    AStr = if Align =:= 0 -> "";
911
915
              Align =:= 1 -> ",0:32"
912
 
           end, 
913
 
    w("({~s, ~s}, Acc) -> ", [erl_option_name(Name), func_arg(P)]), 
 
916
           end,
 
917
    w("({~s, ~s}, Acc) -> ", [erl_option_name(Name), func_arg(P)]),
914
918
    arg_type_test(P,"",[]),
915
919
    case Arg of
916
 
        skip -> 
 
920
        skip ->
917
921
            w("[<<~p:32/?UI~s>>|Acc]", [N, AStr]);
918
 
        _ -> 
 
922
        _ ->
919
923
            w("[<<~p:32/?UI,~s~s>>|Acc]", [N, Arg,AStr])
920
 
    end.   
 
924
    end.
921
925
marshal_args(Ps) ->
922
926
    marshal_args(Ps, [], 0).
923
927
 
957
961
 
958
962
marshal_arg(#type{single=true,base=bool}, Name, Align) ->
959
963
    align(32, Align, "(wxe_util:from_bool(" ++ Name ++ ")):32/?UI");
960
 
marshal_arg(#type{name="wxChar", single=Single}, Name, Align0)  
 
964
marshal_arg(#type{name="wxChar", single=Single}, Name, Align0)
961
965
  when Single =/= true ->
962
 
    {Str,Align} = 
 
966
    {Str,Align} =
963
967
        align(32,Align0, "(byte_size("++Name++"_UC)):32/?UI,(" ++ Name ++ "_UC)/binary"),
964
968
    MsgSize = "(" ++ integer_to_list(Align*4)++"+byte_size("++Name++"_UC))",
965
969
    {Str++", 0:(((8- (" ++ MsgSize ++" band 16#7)) band 16#7))/unit:8",0};
966
970
marshal_arg(#type{base=string}, Name, Align0) ->
967
 
    {Str,Align} = 
 
971
    {Str,Align} =
968
972
        align(32,Align0, "(byte_size("++Name++"_UC)):32/?UI,(" ++ Name ++ "_UC)/binary"),
969
973
    MsgSize = "(" ++ integer_to_list(Align*4)++"+byte_size("++Name++"_UC))",
970
974
    {Str++", 0:(((8- (" ++ MsgSize ++" band 16#7)) band 16#7))/unit:8",0};
971
975
marshal_arg(#type{name="wxArrayString"}, Name, Align0) ->
972
 
    InnerBin  = "<<(byte_size(UC_Str)):32/?UI, UC_Str/binary>>", 
 
976
    InnerBin  = "<<(byte_size(UC_Str)):32/?UI, UC_Str/binary>>",
973
977
    Outer =  "(<< " ++ InnerBin ++ "|| UC_Str <- "++ Name ++"_UCA>>)/binary",
974
978
    Str0  =  "(length("++Name++"_UCA)):32/?UI, " ++ Outer,
975
979
    {Str,Align} = align(32,Align0,Str0),
976
 
    MsgSize = "("++integer_to_list(Align*4) ++ 
 
980
    MsgSize = "("++integer_to_list(Align*4) ++
977
981
        " + lists:sum([byte_size(S)+4||S<-" ++ Name ++"_UCA]))",
978
982
    AStr = ", 0:(((8- (" ++ MsgSize ++" band 16#7)) band 16#7))/unit:8",
979
983
    {Str ++ AStr, 0};
997
1001
    {skip,Align0};
998
1002
marshal_arg(#type{base=binary}, _Name, Align0) ->
999
1003
    {skip,Align0};
1000
 
marshal_arg(#type{base=Base, single=Single}, Name, Align0) 
 
1004
marshal_arg(#type{base=Base, single=Single}, Name, Align0)
1001
1005
  when Single =/= true ->
1002
 
    case Base of 
1003
 
        int -> 
 
1006
    case Base of
 
1007
        int ->
1004
1008
            Str0 = "(length("++Name++")):32/?UI,\n"
1005
1009
                "        (<< <<C:32/?I>> || C <- "++Name++">>)/binary",
1006
1010
            {Str,Align} = align(32,Align0, Str0),
1007
1011
            {Str ++ ", 0:((("++integer_to_list(Align)++"+length("++Name++ ")) rem 2)*32)", 0};
1008
 
        {ObjRef,_} when ObjRef =:= class; ObjRef =:= ref -> 
 
1012
        {ObjRef,_} when ObjRef =:= class; ObjRef =:= ref ->
1009
1013
            Str0 = "(length("++Name++")):32/?UI,",
1010
1014
            Str1 = "\n     (<< <<(C#wx_ref.ref):32/?UI>> || C <- "++Name++">>)/binary",
1011
1015
            {Str2,Align} = align(32, Align0, Str1),
1033
1037
align(64, 1, Str) -> {"0:32," ++ Str,0};
1034
1038
align(Sz, W, Str) -> align(Sz, W rem 2, Str).
1035
1039
 
1036
 
enum_name(Name) -> 
 
1040
enum_name(Name) ->
1037
1041
    case string:tokens(Name, ":") of
1038
1042
        [Name] -> Name;
1039
1043
        [C,N] ->  C ++ "_" ++ N
1053
1057
      "        }).~n", []),
1054
1058
    w("~n%% Hardcoded Defines~n", []),
1055
1059
    Enums = [E || {{enum,_},E = #enum{as_atom=false}} <- get()],
1056
 
    w("-define(wxDefaultSize, {-1,-1}).~n", []), 
1057
 
    w("-define(wxDefaultPosition, {-1,-1}).~n", []), 
 
1060
    w("-define(wxDefaultSize, {-1,-1}).~n", []),
 
1061
    w("-define(wxDefaultPosition, {-1,-1}).~n", []),
1058
1062
    w("~n%% Global Variables~n", []),
1059
 
    [w("-define(~s,  wxe_util:get_const(~s)).~n", [Gvar, Gvar]) || 
 
1063
    [w("-define(~s,  wxe_util:get_const(~s)).~n", [Gvar, Gvar]) ||
1060
1064
        {Gvar,_,_Id} <- get(gvars)],
1061
1065
    w("~n%% Enum and defines~n", []),
1062
1066
    foldl(fun(Enum= #enum{vals=Vals}, Done) when Vals =/= [] ->
1076
1080
        {_File, Class, Name} ->
1077
1081
            w("% From class ~s::~s~n",[Class, Name])
1078
1082
    end,
1079
 
    
 
1083
 
1080
1084
    Format = fun(#const{name="wxEVT_" ++ _}) ->
1081
1085
                     ignore; %% Ignore event macros they are not valid in our event model
1082
1086
                (#const{name=Name,val=Value,is_const=true}) when is_integer(Value) ->
1100
1104
    Consts = get(consts),
1101
1105
    Write = fun({Name,_What}, Skip) ->
1102
1106
                    case gb_sets:is_member(Name,Skip) of
1103
 
                        true -> 
 
1107
                        true ->
1104
1108
                            Skip;
1105
1109
                        false ->
1106
1110
                            case gb_trees:lookup(Name, Consts) of
1107
1111
                                {value, Const} ->
1108
 
                                    Format(Const), 
 
1112
                                    Format(Const),
1109
1113
                                    gb_sets:add(Name,Skip);
1110
1114
                                none -> Skip
1111
1115
                            end
1119
1123
    w("", []),
1120
1124
    w("%% This file is generated DO NOT EDIT~n~n", []),
1121
1125
    w("%%  All event messages are encapsulated in a wx record~n"
1122
 
      "%%  they contain the widget id and a specialized event record.~n" 
1123
 
      "%%  Each event record may be sent for one or more event types.~n" 
 
1126
      "%%  they contain the widget id and a specialized event record.~n"
 
1127
      "%%  Each event record may be sent for one or more event types.~n"
1124
1128
      "%%  The mapping to wxWidgets is one record per class.~n~n",[]),
1125
1129
    w("%% @type wx() = #wx{id=integer(), obj=wx:wxObject(), userData=term(), event=Rec}. Rec is a event record.~n",[]),
1126
1130
    w("-record(wx, {id,     %% Integer Identity of object.~n"
1130
1134
    w("%% Here comes the definitions of all event records.~n"
1131
1135
      "%% they contain the event type and possible some extra information.~n~n",[]),
1132
1136
    Types = [build_event_rec(C) || {_,C=#class{event=Evs}} <- get(), Evs =/= false],
1133
 
    w("%% @type wxEventType() = ~s.~n", 
 
1137
    w("%% @type wxEventType() = ~s.~n",
1134
1138
      [args(fun(Ev) -> Ev end, " | ", lists:sort(lists:append(Types)))]),
1135
1139
    %% close(), closed in gen_enums_ints
1136
1140
    ok.
1145
1149
    end.
1146
1150
 
1147
1151
filter_attrs(#class{name=Name, parent=Parent,attributes=Attrs}) ->
1148
 
    Attr1 = lists:foldl(fun(#param{acc=skip},Acc) -> Acc; 
 
1152
    Attr1 = lists:foldl(fun(#param{acc=skip},Acc) -> Acc;
1149
1153
                           (P=#param{prot=public},Acc) -> [P|Acc];
1150
 
                           (#param{acc=undefined},Acc) -> Acc; 
 
1154
                           (#param{acc=undefined},Acc) -> Acc;
1151
1155
                           ({inherited, PName},Acc) ->
1152
1156
                                case find_inherited_attr(PName, Parent) of
1153
 
                                    undefined -> 
 
1157
                                    undefined ->
1154
1158
                                        io:format("~p:~p: Missing Event Attr ~p in ~p~n",
1155
1159
                                                  [?MODULE,?LINE, PName, Name]),
1156
1160
                                        Acc;
1157
 
                                    P -> 
 
1161
                                    P ->
1158
1162
                                        [P|Acc]
1159
1163
                                end;
1160
1164
                           (P, Acc) -> [P|Acc]
1161
1165
                        end, [], Attrs),
1162
1166
    lists:reverse(Attr1).
1163
 
   
 
1167
 
1164
1168
build_event_rec(Class=#class{name=Name, event=Evs}) ->
1165
1169
    EvTypes = [event_type_name(Ev) || Ev <- Evs],
1166
1170
    Str  = args(fun(Ev) -> "<em>"++Ev++"</em>" end, ", ", EvTypes),
1168
1172
    Rec = event_rec_name(Name),
1169
1173
    GetName = fun(#param{name=N}) ->event_attr_name(N) end,
1170
1174
    GetType = fun(#param{name=N,type=T}) ->
1171
 
                      event_attr_name(N) ++ "=" ++ doc_arg_type2(T) 
 
1175
                      event_attr_name(N) ++ "=" ++ doc_arg_type2(T)
1172
1176
              end,
1173
1177
    case Attr =:= [] of
1174
 
        true -> 
 
1178
        true ->
1175
1179
            w("%% @type ~s() = #~s{type=wxEventType()}.~n", [Rec,Rec]),
1176
1180
            w("%% <dl><dt>EventType:</dt> <dd>~s</dd></dl>~n",[Str]),
1177
 
%%          case is_command_event(Name) of 
 
1181
%%          case is_command_event(Name) of
1178
1182
%%              true  -> w("%% This event skips other event handlers.~n",[]);
1179
1183
%%              false -> w("%% This event will be handled by other handlers~n",[])
1180
1184
%%          end,
1181
1185
            w("%% Callback event: {@link ~s}~n", [Name]),
1182
1186
            w("-record(~s, {type}).~n~n", [Rec]);
1183
1187
        false ->
1184
 
            w("%% @type ~s() = #~s{type=wxEventType(),~s}.~n", 
 
1188
            w("%% @type ~s() = #~s{type=wxEventType(),~s}.~n",
1185
1189
              [Rec,Rec,args(GetType,",",Attr)]),
1186
1190
            w("%% <dl><dt>EventType:</dt> <dd>~s</dd></dl>~n",[Str]),
1187
 
%%          case is_command_event(Name) of 
 
1191
%%          case is_command_event(Name) of
1188
1192
%%              true -> w("%% This event skips other event handlers.~n",[]);
1189
1193
%%              false -> w("%% This event will be handled by other handlers~n",[])
1190
 
%%          end,            
 
1194
%%          end,
1191
1195
            w("%% Callback event: {@link ~s}~n", [Name]),
1192
1196
            w("-record(~s,{type, ~s}).~n~n", [Rec,args(GetName,",",Attr)])
1193
1197
    end,
1198
1202
        true -> true;
1199
1203
        false -> false
1200
1204
    end.
1201
 
            
 
1205
 
1202
1206
event_rec_name(Name0 = "wx" ++ _) ->
1203
1207
    "tnevE" ++ Name1 = reverse(Name0),
1204
1208
    reverse(Name1).
1215
1219
    lowercase(Attr).
1216
1220
 
1217
1221
 
1218
 
gen_funcnames() -> 
 
1222
gen_funcnames() ->
1219
1223
    open_write("../src/gen/wxe_debug.hrl"),
1220
1224
    erl_copyright(),
1221
1225
    w("%% This file is generated DO NOT EDIT~n~n", []),
1257
1261
    Ms  = split_list(fun(#method{name=N}, M) -> {N =:= M, N} end, undefined, Ms2),
1258
1262
    unique_names2(Ms,Class).
1259
1263
%% by Names
1260
 
unique_names2([[#method{id=Id, name=Method,alias=Alias, max_arity=A}]|Ms], Class) -> 
 
1264
unique_names2([[#method{id=Id, name=Method,alias=Alias, max_arity=A}]|Ms], Class) ->
1261
1265
    [{Class,uname(alias(Method,Alias),Class),A,Id} | unique_names2(Ms,Class)];
1262
1266
unique_names2([Ms0|RMs], Class) ->
1263
1267
    Split = fun(#method{max_arity=A}, P) -> {A =:= P, A} end,
1278
1282
 
1279
1283
alias(Method, undefined) -> Method;
1280
1284
alias(_, Alias) -> Alias.
1281
 
     
 
1285
 
1282
1286
uname(Class,Class) ->   "new";
1283
1287
uname([$~ | _], _  ) -> "destruct";
1284
1288
uname(Name, _) -> Name.
1285
 
       
 
1289
 
1286
1290
split_list(F, Keep, List) ->
1287
1291
    split_list(F, Keep, List, []).
1288
1292
 
1297
1301
    end;
1298
1302
split_list(_, _, [], []) -> [];
1299
1303
split_list(_, _, [], Acc) -> [lists:reverse(Acc)].
1300
 
   
 
1304
 
1301
1305