~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%% Api wrapper generator
 
20
 
 
21
-module(wx_gen). 
 
22
-export([code/0,xml/0]).
 
23
 
 
24
-include("wx_gen.hrl").
 
25
 
 
26
-include_lib("xmerl/include/xmerl.hrl").
 
27
 
 
28
-import(lists, [foldl/3,foldr/3,reverse/1, keysearch/3, map/2, filter/2]).
 
29
-import(proplists, [get_value/2,get_value/3]).
 
30
 
 
31
-compile(export_all).
 
32
 
 
33
code() ->  safe(fun gen_code/0,true).
 
34
xml()  ->  safe(fun gen_xml/0,true). 
 
35
 
 
36
devcode() -> erase(),safe(fun gen_code/0,false).
 
37
 
 
38
safe(What, QuitOnErr) ->
 
39
    try 
 
40
        What(),
 
41
        io:format("Completed succesfully~n~n", []),
 
42
        QuitOnErr andalso gen_util:halt(0)
 
43
    catch Err:Reason ->
 
44
            io:format("Error in ~p ~p~n", [get(current_class),get(current_func)]),
 
45
            erlang:display({Err,Reason, erlang:get_stacktrace()}),
 
46
            catch gen_util:close(),
 
47
            QuitOnErr andalso gen_util:halt(1)
 
48
    end.
 
49
 
 
50
gen_code() ->
 
51
    {ok, Defs0} = file:consult("wxapi.conf"),
 
52
    %% {ok, Defs0} = file:consult("test.conf"),
 
53
    erase(func_id),
 
54
    put(class_id, 10), %% Start from 10 using the other as special
 
55
    Defs1 = init_defs(Defs0),
 
56
    Defs2 = parse_defs(Defs1, []),
 
57
    parse_enums([File || {{include, File},_} <- get()]),
 
58
    Defs = translate_enums(Defs2),
 
59
    wx_gen_erl:gen(Defs),
 
60
    wx_gen_cpp:gen(Defs),
 
61
    ok.
 
62
 
 
63
gen_xml() ->
 
64
%%     {ok, Defs} = file:consult("wxapi.conf"),
 
65
    
 
66
%%     Rel = reverse(tl(reverse(os:cmd("wx-config --release")))),
 
67
%%     Dir = " /usr/include/wx-" ++ Rel ++ "/wx/",
 
68
%%     Files0 = [Dir ++ File || {class, File, _, _, _} <- Defs],
 
69
%%     Files1 = [Dir ++ File || {doxygen, File} <- Defs],
 
70
%%     ok = file:write_file("wxapi.files", list_to_binary("INPUT = "++Files0++Files1)),
 
71
    ok.
 
72
    
 
73
-record(hs,{alias,skip,fs,fopt,ev,acc,info}).
 
74
 
 
75
init_defs(List0) ->
 
76
    List1 = to_lists(List0),
 
77
    lists:map(fun mangle_info/1, List1).
 
78
 
 
79
mangle_info(E={enum,Type0,SkipStr}) ->
 
80
    Type = case is_atom(Type0) of true -> atom_to_list(Type0); false -> Type0 end,
 
81
    put({enum, Type}, #enum{skip=SkipStr,as_atom=false}), %% as_atom=true}),
 
82
    E;
 
83
mangle_info(E={const_skip,List}) ->
 
84
    put(const_skip, [atom_to_list(M) || M <- List]),
 
85
    E;
 
86
mangle_info(E={not_const,List}) ->
 
87
    put(not_const,  [atom_to_list(M) || M <- List]),
 
88
    E;
 
89
mangle_info(E={gvars,List}) ->
 
90
    A2L = fun({N,{T,C}}) -> {atom_to_list(N), {T,atom_to_list(C)}};
 
91
             ({N,C}) ->     {atom_to_list(N), atom_to_list(C)}
 
92
          end,    
 
93
    put(gvars, map(A2L,List)),
 
94
    E;
 
95
mangle_info({class,CN,P,O,FL}) ->
 
96
    Alias  = get_value(alias,O, []),
 
97
    Skip   = get_value(skip, O, []),
 
98
    Event  = get_value(event,O, false),
 
99
    Acc    = get_value(acc, O, []),
 
100
    {Fs,Fopts} = foldr(fun(FWO={F,FO},{Fl,Fopt}) when is_list(FO) ->
 
101
                               {[F|Fl],[FWO|Fopt]};
 
102
                          (F,{Fl,Fopt}) ->
 
103
                               {[F|Fl], Fopt}
 
104
                       end, {[],[]}, FL),
 
105
    {class,CN,P,#hs{alias=Alias,skip=Skip,fs=Fs,ev=Event,acc=Acc,info=O,
 
106
                    fopt=gb_trees:from_orddict(lists:sort(Fopts))}}.
 
107
 
 
108
to_lists(Defs) ->
 
109
    map(fun({class,C,P,O,Fs}) ->
 
110
                {class,atom_to_list(C),atom_to_list(P),to_lists2(O),to_lists2(Fs)};
 
111
           (Skip) -> Skip
 
112
        end, Defs).
 
113
 
 
114
to_lists2(List) ->
 
115
    map(fun(Skip = {const_skip, _List}) -> Skip;
 
116
           (Skip = {not_const, _List}) -> Skip;
 
117
           (Skip = {skip, _List}) -> Skip;
 
118
           (Skip = {event, _List}) -> Skip;
 
119
           (Skip = {acc, _List}) -> Skip;
 
120
           (Skip = {doc, _List}) -> Skip;
 
121
           (Skip = taylormade) -> Skip;
 
122
           (Skip = {ifdef,_}) -> Skip;
 
123
           (Skip = {erl_func, _Name})  -> Skip;
 
124
           ({alias, AList}) -> {alias, [{atom_to_list(A),atom_to_list(B)} || {A,B} <- AList]};
 
125
           (Else) when is_atom(Else) -> atom_to_list(Else);
 
126
           ({Else,W}) when is_atom(Else) -> {atom_to_list(Else),W};
 
127
           ({{Else,W},O}) when is_atom(Else) -> {{atom_to_list(Else),W},O};
 
128
           (Else) -> Else
 
129
        end, List).
 
130
 
 
131
parse_defs([{class,Name,Parent,Info}|Rest], Acc0) ->
 
132
    {FileName, Type} = 
 
133
        case Parent of
 
134
            "static" -> {Name ++ "_8h", static};
 
135
            _ ->        {"class" ++ Name, class}
 
136
        end,
 
137
    Tab   = ets:new(defs, [bag]), 
 
138
    Defs0 = load_members(FileName, Name, gb_trees:empty(), Tab, Type, Info),
 
139
        
 
140
    put(current_class, Name),
 
141
    Class0 = #class{name=name(Name,Info),parent=Parent,
 
142
                    doc=get_value(doc,Info#hs.info,undefined),
 
143
                    file=FileName,options=Info#hs.info, id=next_id(class_id)},
 
144
    ParseClass = fun(Member,{Class,Dfs}) -> 
 
145
                         parse_class(Member,Tab,Dfs,Class,Info)
 
146
                 end,
 
147
    {Class1,Defs} = foldl(ParseClass,{Class0,Defs0},Info#hs.fs),
 
148
    
 
149
    Class2 = case Info#hs.ev of 
 
150
                 false -> Class1;
 
151
                 Ev -> parse_attr(gb_trees:to_list(Defs), Class1, Ev, Info)
 
152
             end,
 
153
    Class = meta_info(Class2),
 
154
    erase(current_class),
 
155
    [erase(Del) ||  {Del = {loaded, _},_} <- get()],
 
156
    %% ets:delete(Tab),  keep it for debugging
 
157
    parse_defs(Rest, [Class|Acc0]);
 
158
parse_defs([_|Rest], Acc) ->
 
159
    parse_defs(Rest, Acc);
 
160
parse_defs([], Acc) -> reverse(Acc). 
 
161
 
 
162
meta_info(C=#class{name=CName,methods=Ms0}) ->
 
163
    Ms = lists:append(Ms0),
 
164
    HaveConstructor = 
 
165
        lists:keysearch(constructor, #method.method_type, Ms) =/= false,
 
166
    case lists:keysearch(destructor, #method.method_type, Ms) of
 
167
        false when HaveConstructor -> 
 
168
            Dest = #method{name="destroy",id=next_id(func_id),
 
169
                           method_type=destructor, params=[this(CName)]},
 
170
            C#class{methods = [[Dest]|Ms0]};
 
171
        false ->
 
172
            C#class{abstract = true};
 
173
        _ -> 
 
174
            C
 
175
    end.
 
176
            
 
177
parse_class(Member0,Tab,Defs0,Class = #class{name=CName},Opts) ->
 
178
    {Member,NoArgs} = case Member0 of 
 
179
                          {_, _} ->  Member0; 
 
180
                          _ ->       {Member0,all}
 
181
                      end,
 
182
    case ets:lookup(Tab, Member) of
 
183
        [] -> 
 
184
            case Member of
 
185
                [$~|_] -> ignore; 
 
186
                _ ->
 
187
                    ?warning("Skipped Member ~p in ~p (not found in ~p)~n", 
 
188
                             [Member,CName,Tab])
 
189
            end,
 
190
            {Class,Defs0};
 
191
        Ms ->
 
192
            case select_member(Ms, Class, Defs0, Opts) of
 
193
                {[],Defs} -> 
 
194
                    ?warning("Skipped Member ~p in ~p (not found in base)~n", 
 
195
                             [Member,CName]),
 
196
                    {Class,Defs};
 
197
                {Selected,Defs} ->
 
198
                    Parsed = parse_members(Member,Selected,Defs,CName,Opts),
 
199
                    {add_method(Parsed,NoArgs,Class,Opts), Defs}
 
200
            end
 
201
    end.
 
202
 
 
203
parse_members(MemberName, Members, Defs, Class, Opts) ->
 
204
    ParseAll = 
 
205
        fun(Member,Acc) ->
 
206
                try 
 
207
                    case gb_trees:lookup(Member, Defs) of
 
208
                        {value,#xmlElement{name=memberdef,attributes=Attrs,
 
209
                                           content=Data}} -> 
 
210
                            MType = case keysearch(static,#xmlAttribute.name,Attrs) of
 
211
                                        {value, #xmlAttribute{value = "yes"}} -> 
 
212
                                            static;
 
213
                                        _ ->
 
214
                                            member 
 
215
                                    end,
 
216
                            Virtual = 
 
217
                                case keysearch(virt,#xmlAttribute.name,Attrs) of
 
218
                                    {value, #xmlAttribute{value = "virtual"}} -> 
 
219
                                        true;
 
220
                                    {value, #xmlAttribute{value = "non-virtual"}} -> 
 
221
                                        false;
 
222
                                    _ ->
 
223
                                        undefined
 
224
                                end,
 
225
                            [parse_member(Data,MType,Virtual,Opts)|Acc];
 
226
                        none ->                             
 
227
                            Acc;
 
228
                        _Hmm ->
 
229
                            Acc
 
230
                    end
 
231
                catch throw:skip_member ->
 
232
                        Acc
 
233
                end
 
234
        end,
 
235
    case foldl(ParseAll,[],Members) of
 
236
        [] -> 
 
237
            ?warning("Skipped ~p No public def found in ~p ~n", 
 
238
                     [MemberName,Class]),
 
239
            io:format("~p ~p~n",[MemberName, Members]),
 
240
            [];
 
241
        Res -> 
 
242
            Res
 
243
    end.
 
244
            
 
245
 
 
246
parse_attr(Defs, Class, Ev, Info = #hs{acc=AccList0}) ->
 
247
%    io:format("Parsing Class ~p~n", [Class#class.name]),
 
248
    {Attrs, AccList} = parse_attr1(Defs, AccList0, Info, []),
 
249
    case AccList of 
 
250
        [] -> 
 
251
            Class#class{attributes=Attrs, event=Ev};
 
252
        _ ->
 
253
            Inherited = [{inherited, Inherit} || Inherit <- AccList],
 
254
            Class#class{attributes=Attrs++Inherited, event=Ev}
 
255
    end.
 
256
    
 
257
parse_attr1([{{attr,_}, #xmlElement{content=C, attributes=Attrs}}|R], AttrList0, Opts, Res) ->    
 
258
    Parse  = fun(Con, Ac) -> parse_param(Con, Opts, Ac) end,
 
259
    Param0 = foldl(Parse, #param{}, drop_empty(C)),
 
260
    case keysearch(prot, #xmlAttribute.name, Attrs) of
 
261
        {value, #xmlAttribute{value = "public"}} ->
 
262
            {Acc,AttrList} = attr_acc(Param0, AttrList0),           
 
263
            parse_attr1(R,AttrList,Opts,
 
264
                        [Param0#param{in=false,prot=public,acc=Acc}|Res]);
 
265
        {value, #xmlAttribute{value = "protected"}} ->
 
266
            {Acc,AttrList} = attr_acc(Param0, AttrList0),           
 
267
            parse_attr1(R,AttrList,Opts,
 
268
                        [Param0#param{in=false,prot=protected,acc=Acc}|Res]);
 
269
        {value, #xmlAttribute{value = "private"}} ->
 
270
            {Acc,AttrList} = attr_acc(Param0, AttrList0),
 
271
            parse_attr1(R,AttrList,Opts, 
 
272
                        [Param0#param{in=false,prot=private,acc=Acc}|Res])
 
273
    end;
 
274
parse_attr1([{_Id,_}|R],AttrList,Info, Res) ->
 
275
    parse_attr1(R,AttrList,Info, Res);
 
276
parse_attr1([],Left,_, Res) ->
 
277
    {lists:reverse(Res), Left}.
 
278
 
 
279
attr_acc(#param{name=N}, List) ->
 
280
    Name = list_to_atom(N),
 
281
    case get_value(Name, List, undefined) of
 
282
        undefined -> {undefined, List};
 
283
        Val -> {Val, lists:keydelete(Name,1,List)}
 
284
    end.
 
285
                
 
286
load_members(FileName, Class, Defs, Tab, Type,Opts) ->
 
287
    File = filename:join(["wx_xml",FileName ++ ".xml"]),
 
288
    put({loaded, FileName}, true),
 
289
    case xmerl_scan:file(File, [{space, normalize}]) of 
 
290
        {error, enoent} ->
 
291
            io:format("Skipped File not found ~p ~n", [File]),
 
292
            Defs;
 
293
        {Doc, _} ->
 
294
            %% io:format("Scanning ~p ~n", [File]),
 
295
            INCs = xmerl_xpath:string("./compounddef/includes/text()", Doc),
 
296
            [put({include,reverse(tl(tl(reverse(Inc))))},ref) || 
 
297
                #xmlText{value=Inc} <- INCs],
 
298
            case Type of
 
299
                class ->
 
300
                    AM = xmerl_xpath:string("./compounddef/listofallmembers/*", Doc),
 
301
                    foldl(fun(X,Y) -> extract_rmembers(X,Y,Opts) end, Tab, AM);
 
302
                _ ->
 
303
                    ignore
 
304
            end,
 
305
            LMembers0 = xmerl_xpath:string("./compounddef/sectiondef/*", Doc),
 
306
            foldl(fun(E,Acc) -> extract_lmembers(E,Class,Type,Tab,Opts,Acc) end, Defs, LMembers0)
 
307
    end.
 
308
            
 
309
extract_lmembers(Entry=#xmlElement{name=memberdef,attributes=Attrs,content=C},Class,Type,Tab,Opts,Acc) ->
 
310
    case keysearch(kind, #xmlAttribute.name, Attrs) of
 
311
        {value, #xmlAttribute{value = "function"}} ->       
 
312
            case keysearch(prot, #xmlAttribute.name, Attrs) of
 
313
                {value, #xmlAttribute{value = "public"}} ->
 
314
                    {value, #xmlAttribute{value = Id}} =
 
315
                        keysearch(id, #xmlAttribute.name, Attrs),
 
316
                    case Type of
 
317
                        static ->
 
318
                            Get = fun(#xmlElement{name=name,content=[#xmlText{value=Name}]},NAcc) ->
 
319
                                          [name(string:strip(Name),Opts)|NAcc];
 
320
                                     (_D, NAcc) -> 
 
321
                                          NAcc
 
322
                                  end,
 
323
                            case foldl(Get, [], C) of
 
324
                                [Name] -> 
 
325
                                    true = ets:insert(Tab,{Name,Id});
 
326
                                [] -> 
 
327
                                    ignore
 
328
                            end;
 
329
                        _ -> ignore                 
 
330
                    end,
 
331
                    case gb_trees:lookup(Id,Acc) of
 
332
                        {value, _Entry} -> gb_trees:update(Id,Entry,Acc);
 
333
                        none -> gb_trees:insert(Id,Entry,Acc)
 
334
                    end;
 
335
                _ -> 
 
336
                    Acc
 
337
            end;
 
338
        {value, #xmlAttribute{value = "variable"}} when Type =/= static -> 
 
339
%%          {value, #xmlAttribute{value = Id}} =
 
340
%%              keysearch(id, #xmlAttribute.name, Attrs),
 
341
            %% Hopefully wxW have some decent order!!
 
342
            Id = next_id(attr_id),
 
343
            gb_trees:insert({attr,Id},Entry,Acc);
 
344
        {value, #xmlAttribute{value = "enum"}} when Type =/= static ->
 
345
            extract_enum(Entry,Class, undefined),
 
346
            Acc;
 
347
        _ -> Acc
 
348
 
 
349
    end.
 
350
 
 
351
extract_rmembers(#xmlElement{name=member,attributes=Attrs,content=C},Tab, Opts) ->
 
352
    {value,#xmlAttribute{value=Id}} = keysearch(refid, #xmlAttribute.name, Attrs),
 
353
    Get = fun(#xmlElement{name=name,content=[#xmlText{value=Name}]},Acc) ->
 
354
                  [name(string:strip(Name),Opts)|Acc];
 
355
             (_D, Acc) -> 
 
356
                  Acc
 
357
          end,
 
358
    case foldl(Get, [], C) of
 
359
        [Name] -> 
 
360
            true = ets:insert(Tab,{Name,Id});
 
361
        [] -> 
 
362
            ignore
 
363
    end,
 
364
    Tab.
 
365
 
 
366
select_member([{_,ID}], #class{name=Class,file=Orig}, Defs0, Opts) ->
 
367
    [FileName, _8H|_] = string:tokens(ID, "_"),
 
368
    case get({loaded, FileName}) =:= undefined 
 
369
        andalso get({loaded, FileName ++ "_" ++ _8H}) =:= undefined of
 
370
        true ->
 
371
            true = FileName =/= Orig, % Assert
 
372
            Defs = load_members(FileName, Class, Defs0, skip, skip, Opts),
 
373
            {[ID],Defs};
 
374
        false ->
 
375
            {[ID],Defs0}
 
376
    end;
 
377
select_member(Several, #class{name=Class,file=Orig}, Defs0, Opts) ->
 
378
    MIds = [{string:tokens(MId, "_"),MId} || {_,MId} <- Several],
 
379
    [StatFile |_ ] = string:tokens(Orig, "_"),
 
380
    Check = 
 
381
        fun({[FN,_|_],ID}, {T,D}) when FN =:= Orig -> {[ID|T],D};
 
382
           ({[FN,"8h"|_],ID}, {T,D}) when FN =:= StatFile -> {[ID|T],D};
 
383
           ({[FN,_A|_],ID},{T,D}) -> 
 
384
                InBase = "class" ++ Class ++ "Base" =:= FN,
 
385
                "wx" ++ ClassName = Class,
 
386
                InGeneric = "classwxGeneric" ++ ClassName =:= FN,
 
387
                IsHelper = case regexp:first_match(FN, "Helper$") of
 
388
                               {match,_,_} -> true;
 
389
                               _ -> false
 
390
                           end,
 
391
                ImplBase = case regexp:first_match(FN, "Base$") of
 
392
                               {match,_,_} -> true;
 
393
                               _ -> 
 
394
                                   %% Hack for base-base class
 
395
                                   FN =:= "classwxItemContainer"
 
396
                           end,
 
397
                case InBase orelse InGeneric orelse IsHelper orelse ImplBase of 
 
398
                    true ->
 
399
                        Defs = case get({loaded, FN}) of
 
400
                                   undefined ->
 
401
                                       true = FN =/= Orig, % Assert
 
402
                                       load_members(FN,Class,D,skip,skip,Opts);
 
403
                                   true -> D
 
404
                               end,
 
405
                        {[ID|T], Defs};
 
406
                    _C -> 
 
407
                        %% io:format("DBG ~p ~p ~p ~p ~n",[FN,_A,_C,Class]),
 
408
                        {T,D}
 
409
                end
 
410
        end,
 
411
    foldl(Check,{[],Defs0},MIds).
 
412
 
 
413
parse_member(Data,MType,Virtual,Opts = #hs{fopt=Fopts}) ->
 
414
    Parse  = fun(Con,A) -> parse_member2(Con,Opts,A) end,
 
415
    Method = #method{name=MName,params=PS0} = 
 
416
        foldl(Parse, #method{method_type=MType, virtual=Virtual}, Data),
 
417
    %% Skip motif name's if it's last and optional
 
418
    PS2 = case PS0 of %% Backward order..
 
419
              [#param{name="name",def=Def,type=#type{name="wxString"}}|PS1] 
 
420
              when Def =/= none -> 
 
421
                  PS1;
 
422
              _ ->
 
423
                  PS0
 
424
          end,
 
425
    Sz = length(PS2),
 
426
    PS = map(fun(P=#param{name=PName}) -> 
 
427
                     patch_param(MName,{Sz,PName},P,Fopts)
 
428
             end, PS2),
 
429
    Alias = find_erl_alias_name(MName,PS,Fopts),            
 
430
    Method#method{params=PS, alias=Alias}.
 
431
 
 
432
find_erl_alias_name(MName,Ps,Fopts) ->
 
433
    case gb_trees:lookup(MName, Fopts) of
 
434
        {value, FuncO} when is_list(FuncO) ->
 
435
            Aliases = lists:foldl(fun({Var, {erl_func, AliasName}}, Acc) ->
 
436
                                          [{Var,AliasName}|Acc];
 
437
                                     ({erl_func, AliasName}, Acc) ->
 
438
                                          [{all,AliasName}|Acc];
 
439
                                     ({Var, List}, Acc) when is_list(List) ->
 
440
                                          case get_value(erl_func,List) of 
 
441
                                              undefined ->
 
442
                                                  Acc;
 
443
                                              AliasName ->
 
444
                                                  [{Var,AliasName}|Acc]
 
445
                                          end;          
 
446
                                     (_,Acc) -> Acc
 
447
                                  end, [], FuncO),
 
448
            case Aliases of
 
449
                [] -> 
 
450
                    undefined;
 
451
                _ -> 
 
452
                    Find = fun({all,AliasName},Acc) -> [AliasName|Acc];
 
453
                              ({Var,AliasName},Acc) -> 
 
454
                                   case lists:keysearch(Var, #param.name, Ps) of
 
455
                                       {value, _} -> [AliasName|Acc];
 
456
                                       _  -> Acc
 
457
                                   end                             
 
458
                           end, 
 
459
                    case lists:foldl(Find, [], Aliases) of
 
460
                        [Alias] -> Alias;
 
461
                        [] -> undefined
 
462
                    end             
 
463
            end;
 
464
        _ ->        
 
465
            undefined 
 
466
    end.
 
467
 
 
468
parse_member2(#xmlElement{name=type, content=C},Opts,M0) ->
 
469
    Type = parse_type(drop_empty(C), Opts),
 
470
    M0#method{type=Type};
 
471
parse_member2(#xmlElement{name=name, content=[#xmlText{value=C}]}, Opts, M0) ->
 
472
    Func = string:strip(C),
 
473
    put(current_func, Func),
 
474
    M0#method{name=name(Func,Opts)};
 
475
parse_member2(#xmlElement{name=param, content=C},Opts,M0) -> 
 
476
    Parse = fun(Con, Ac) -> parse_param(Con, Opts, Ac) end,
 
477
    Param0 = foldl(Parse, #param{}, drop_empty(C)),
 
478
    add_param(Param0, Opts, M0);
 
479
parse_member2(_, _,M0) ->
 
480
    M0.
 
481
 
 
482
add_param(InParam, Opts, M0) ->
 
483
    Param0 = case InParam#param.name of
 
484
                 undefined -> InParam#param{name="val"};
 
485
                 _ -> InParam
 
486
             end,  
 
487
    Param = case Param0#param.type of
 
488
                #type{base={comp,_,_Comp}} ->   Param0;
 
489
                #type{base={class,_Class}} -> Param0;
 
490
                #type{base={ref,_}} -> Param0;
 
491
                #type{base={term,_}} -> Param0;
 
492
                #type{base=List} when is_list(List) -> Param0;
 
493
                %% Assume the pointer args to base types are out parameters
 
494
                #type{by_val=false,single=true, mod=Mod} -> 
 
495
                    case lists:member(const, Mod) of
 
496
                        true  -> Param0; % But not if they are const
 
497
                        false -> Param0#param{in=false}
 
498
                    end;
 
499
                _  -> Param0
 
500
            end,
 
501
    add_param2(Param, Opts, M0).
 
502
 
 
503
add_param2(P=#param{name=Name},#hs{fopt=FOpt},M0=#method{name=MName,params=Ps}) ->
 
504
    case patch_param(MName, Name, P, FOpt) of 
 
505
        #param{where=nowhere} ->
 
506
            M0#method{params=Ps};
 
507
        Patched ->
 
508
            %%  case MName of  %% DEBUG
 
509
            %%      "GetSelections" -> 
 
510
            %%      io:format("~p~n",[Patched]);
 
511
            %%          _ -> ignore
 
512
            %%  end,
 
513
            %%ASSERT 
 
514
            case Patched#param.type of
 
515
                #type{base=undefined} -> ?error({unknown_type,Patched});
 
516
                _ -> ok
 
517
            end,
 
518
            M0#method{params=[Patched|Ps]}
 
519
    end.
 
520
 
 
521
patch_param(Method, Name, P, Opt) ->    
 
522
    case gb_trees:lookup(Method,Opt) of
 
523
        none -> P;
 
524
        {value,NoArg} when is_integer(NoArg) -> P;
 
525
        {value,Opts} when is_list(Opts) ->
 
526
            case get_value(Name, Opts) of
 
527
                undefined -> P;
 
528
                List when is_list(List) -> 
 
529
                    foldl(fun handle_param_opt/2,P,List);
 
530
                Val -> 
 
531
                    handle_param_opt(Val,P)
 
532
            end
 
533
    end.
 
534
 
 
535
handle_param_opt(skip, P) -> P#param{where=c};
 
536
handle_param_opt(nowhere, P) -> P#param{where=nowhere};
 
537
handle_param_opt(skip_member, _P) -> throw(skip_member);
 
538
handle_param_opt({skip_member, Type}, P) ->
 
539
    case P of
 
540
        #param{type=#type{name=Type}} ->
 
541
            throw(skip_member);
 
542
        #param{type=Type} ->
 
543
            throw(skip_member);
 
544
        _ -> 
 
545
            P
 
546
    end;
 
547
handle_param_opt({erl_func,_Name}, P) -> P;  %% Handled elsewhere
 
548
handle_param_opt(in, P) -> P#param{in=true};
 
549
handle_param_opt(out, P) -> P#param{in=false};
 
550
handle_param_opt(both, P) -> P#param{in=both};
 
551
handle_param_opt({def,Def},P) -> P#param{def=Def};
 
552
handle_param_opt({type,Type}, P=#param{type=T})  ->  P#param{type=T#type{name=Type}};
 
553
handle_param_opt({single,Opt}, P=#param{type=T}) ->  P#param{type=T#type{single=Opt}};
 
554
handle_param_opt({base,Opt},  P=#param{type=T}) ->   P#param{type=T#type{base=Opt}};
 
555
handle_param_opt({c_only,Opt},P) -> P#param{where=c, alt=Opt};
 
556
handle_param_opt({ref, pointer}, P=#param{type=T}) ->   
 
557
    P#param{type=T#type{by_val=false,ref={pointer, 1}}};
 
558
handle_param_opt({mod,Mods}, P=#param{type=T=#type{mod=Mods0}}) ->  
 
559
    P#param{type=T#type{mod=Mods++Mods0}}.
 
560
 
 
561
get_opt(Opt, Method, Sz, Opts) -> 
 
562
    case gb_trees:lookup(Method,Opts) of
 
563
        none -> undefined;
 
564
        {value, List} when is_list(List) ->
 
565
            case get_value({Sz,Opt}, List, undefined) of
 
566
                undefined -> 
 
567
                    get_value(Opt, List, undefined);
 
568
                Res -> Res
 
569
            end
 
570
    end.
 
571
 
 
572
parse_param(#xmlElement{name=type,content=C},Opts,T) ->   
 
573
    Type = parse_type(drop_empty(C),Opts),
 
574
    T#param{type=Type};
 
575
parse_param(#xmlElement{name=declname,content=[C]},_Opts,T) -> 
 
576
    #xmlText{value=Name} = C,
 
577
    T#param{name=Name};
 
578
parse_param(#xmlElement{name=defval,content=[#xmlText{value=Def}]},_Opts,T) -> 
 
579
    T#param{def=string:strip(Def)};
 
580
parse_param(#xmlElement{name=defval,content=Other},_Opts,T) -> 
 
581
    %% For defaults = (modifer wxType *) NULL 
 
582
    Def0 = foldr(fun(#xmlText{value=V}, Acc) -> V ++ Acc;
 
583
                    (#xmlElement{content=[#xmlText{value=V}]},Acc) -> 
 
584
                         V ++ Acc
 
585
                 end, [], Other),
 
586
%%     Def1 = lists:dropwhile(fun($)) -> false;(_) -> true end, Def0), 
 
587
%%     Def = string:strip(Def1),  %% Drop type cast !!
 
588
%%    io:format("Def ~s => ~s => ~s ~n", [Def0, Def1,string:strip(Def)]),
 
589
    T#param{def=string:strip(Def0)};
 
590
parse_param(#xmlElement{name=array,content=C},_Opts, T = #param{type=Type0}) -> 
 
591
    case Type0 of
 
592
        _ when T#param.name=:="WXUNUSED" -> %% doxygen can't handle this macro
 
593
            [#xmlText{value=RealVar}] = C,
 
594
            [Name] = string:tokens(RealVar, "() "),
 
595
            T#param{name=Name};
 
596
%%      #type{mod=[const]} -> 
 
597
%%          T#param{type=Type0#type{single=array, by_val=true}};
 
598
%%      _ -> 
 
599
%%          T#param{type=Type0#type{single=array, by_val=false}}
 
600
        _ -> 
 
601
            T#param{type=Type0#type{single=array, by_val=true}}
 
602
    end;
 
603
parse_param(#xmlElement{name=name,content=[C]}, _, T) ->
 
604
    %% Attributes have this
 
605
    #xmlText{value=Name} = C,
 
606
    T#param{name=Name};
 
607
%% Skipped: Attributes have this
 
608
parse_param(#xmlElement{name=definition}, _, T) ->    T;
 
609
parse_param(#xmlElement{name=argsstring}, _, T) ->    T;
 
610
parse_param(#xmlElement{name=briefdescription}, _, T) ->    T;
 
611
parse_param(#xmlElement{name=detaileddescription}, _, T) ->    T;
 
612
parse_param(#xmlElement{name=inbodydescription}, _, T) ->    T;
 
613
parse_param(#xmlElement{name=location}, _, T) ->    T;
 
614
parse_param(#xmlElement{name=referencedby}, _, T) ->    T;
 
615
parse_param(Other=#xmlElement{name=Name}, _, T) ->
 
616
    io:format("Unhandled Param ~p ~p ~n in ~p~n", [Name,Other,T]),
 
617
    ?error(unhandled_param).
 
618
 
 
619
parse_type([], _Opts) -> void;
 
620
parse_type(TypeInfo, Opts) ->
 
621
    {Type,Info} = foldl(fun extract_type_info/2,{[],undefined},TypeInfo),
 
622
    case Info of
 
623
        {"member", Ref} ->
 
624
            case string:tokens(Ref, "_") of
 
625
                [FileName, "8h", _Id] ->
 
626
                    put({file_ref, FileName++"_8h"}, ref);
 
627
                _ -> 
 
628
                    ok
 
629
            end;
 
630
        _ -> ok
 
631
    end,
 
632
 
 
633
    Empty = #type{},
 
634
    case parse_type2(reverse(Type),Info,Opts,#type{}) of
 
635
        Empty -> ?error({strange_type, Type});
 
636
        Assert  -> Assert
 
637
    end.
 
638
 
 
639
extract_type_info(#xmlText{value=Value}, {Acc, Info}) -> 
 
640
    {reverse(foldl(fun extract_type_info2/2, [], string:tokens(Value, " "))) ++ Acc, Info};
 
641
extract_type_info(#xmlElement{name=ref,attributes=As,content=[#xmlText{value=V}]},
 
642
                  {Acc,undefined}) ->
 
643
    {value, #xmlAttribute{value = Refid}} = keysearch(refid,#xmlAttribute.name,As),
 
644
    {value, #xmlAttribute{value = Kind}} = keysearch(kindref,#xmlAttribute.name,As),
 
645
    {reverse(foldl(fun extract_type_info2/2, [], string:tokens(V, " "))) ++ Acc,
 
646
     {Kind,Refid}};
 
647
extract_type_info(What,Acc) ->
 
648
    ?error({parse_error,What,Acc}).
 
649
 
 
650
extract_type_info2("const",Acc) -> [const|Acc];
 
651
extract_type_info2("*", [{by_ref,{pointer,N}}|Acc]) -> [{by_ref,{pointer,N+1}}|Acc];
 
652
extract_type_info2("*",   Acc) -> [{by_ref,{pointer,1}}|Acc];
 
653
extract_type_info2("**",  Acc) -> [{by_ref,{pointer,2}}|Acc];
 
654
extract_type_info2("&",   Acc) -> [{by_ref,reference}|Acc];
 
655
extract_type_info2("WXDLLIMP" ++ _, Acc) ->  Acc;
 
656
extract_type_info2(Type,  Acc) -> [Type|Acc].
 
657
 
 
658
parse_type2(["void"], _Info,  _Opts, _T) ->  void;
 
659
parse_type2(["virtual"|R], _Info,  _Opts, _T) ->  
 
660
    [] = R,
 
661
    %% Bug in old doxygen virtual destructors have type virtual
 
662
    void;
 
663
parse_type2(["wxe_cb"|R],Info,Opts, T) -> 
 
664
    parse_type2(R,Info,Opts,T#type{name=int,base=wxe_cb});
 
665
parse_type2([const|R],Info,Opts,T=#type{mod=Mod}) -> 
 
666
    parse_type2(R,Info,Opts,T#type{mod=[const|Mod]});
 
667
parse_type2(["unsigned"|R],Info,Opts,T=#type{mod=Mod}) -> 
 
668
    parse_type2(R,Info,Opts,T#type{mod=[unsigned|Mod]});
 
669
parse_type2(["int"|R],Info,Opts,  T) -> 
 
670
    parse_type2(R,Info,Opts,T#type{name=int,base=int});
 
671
parse_type2(["char"|R],Info,Opts,  T) -> 
 
672
    parse_type2(R,Info,Opts,T#type{name="char",base=int});
 
673
parse_type2([N="size_t"|R], Info, Opts,  T) -> 
 
674
    parse_type2(R,Info,Opts,T#type{name=N, base=int});
 
675
parse_type2(["long"|R],Info, Opts, T) -> 
 
676
    parse_type2(R,Info,Opts,T#type{name=long,base=int});
 
677
parse_type2(["float"|R],Info,Opts, T) -> 
 
678
    parse_type2(R,Info,Opts,T#type{name=float,base=float});
 
679
parse_type2(["double"|R],Info,Opts,T) -> 
 
680
    parse_type2(R,Info,Opts,T#type{name=double,base=double});
 
681
parse_type2([N="wxDouble"|R],Info,Opts,T) -> 
 
682
    parse_type2(R,Info,Opts,T#type{name=N,base=double});
 
683
parse_type2(["bool"|R],Info,Opts,T) -> 
 
684
    parse_type2(R,Info,Opts,T#type{name=bool,base=bool});
 
685
parse_type2([N="wxWindowID"|R],Info,Opts,T) -> 
 
686
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
687
parse_type2([N="wxTextCoord"|R],Info,Opts,T) ->      %%long 
 
688
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
689
parse_type2([N="wxTextPos"|R],Info,Opts,T) ->        %%long
 
690
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
691
parse_type2([N="wxPrintQuality"|R],Info,Opts,T) ->
 
692
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
693
parse_type2([N="wxPaperSize"|R],Info,Opts,T) ->
 
694
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
695
parse_type2(["wxDataFormat"|_R],_Info,_Opts,T) ->
 
696
    %% Hack Hack
 
697
    T#type{name="wxDataFormatId",base=int};
 
698
parse_type2([N="wxArrayInt"|R],Info,Opts,T) -> 
 
699
    parse_type2(R,Info,Opts,T#type{name=N,base=int,single=array});
 
700
parse_type2([N="wxArrayDouble"|R],Info,Opts,T) -> 
 
701
    parse_type2(R,Info,Opts,T#type{name=N,base=double,single=array});
 
702
parse_type2([N="wxTreeItemId"|R],Info,Opts,T) -> 
 
703
    parse_type2(R,Info,Opts,T#type{name=N,base={ref,N}});
 
704
parse_type2([N="wxArrayTreeItemIds"|R],Info,Opts,T) -> 
 
705
    parse_type2(R,Info,Opts,T#type{name=N,base={ref,"wxTreeItemId"},single=array});
 
706
parse_type2([N="wxTreeItemData"|R],Info,Opts,T) -> 
 
707
    parse_type2(R,Info,Opts,T#type{name="wxETreeItemData",base={term,N}});
 
708
parse_type2([N="wxClientData"|R],Info,Opts,T) -> 
 
709
    parse_type2(R,Info,Opts,T#type{name="wxeErlTerm",base={term,N}});
 
710
parse_type2([N="wxChar"|R],Info,Opts,T) -> 
 
711
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
712
parse_type2(["wxUint32"|R],Info,Opts,T=#type{mod=Mod}) -> 
 
713
    parse_type2(R,Info,Opts,T#type{name=int,base=int,mod=[unsigned|Mod]});
 
714
parse_type2([N="wxCoord"|R],Info,Opts,T) -> 
 
715
    parse_type2(R,Info,Opts,T#type{name=N,base=int});
 
716
parse_type2([N="wxPoint"|R],Info,Opts,T) -> 
 
717
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"X"},{int,"Y"}]}});
 
718
parse_type2([N="wxSize"|R],Info,Opts,T) -> 
 
719
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"W"},{int,"H"}]}});
 
720
parse_type2([N="wxGBPosition"|R],Info,Opts,T) -> 
 
721
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"R"},{int,"C"}]}});
 
722
parse_type2([N="wxGBSpan"|R],Info,Opts,T) -> 
 
723
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"RS"},{int,"CS"}]}});
 
724
parse_type2([N="wxGridCellCoords"|R],Info,Opts,T) -> 
 
725
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"R"},{int,"C"}]}});
 
726
parse_type2([N="wxGridCellCoordsArray"|R],Info,Opts,T) -> 
 
727
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,"wxGridCellCoords",
 
728
                                                [{int,"R"},{int,"C"}]},
 
729
                                   single=array});
 
730
parse_type2([N="wxRect"|R],Info,Opts,T) -> 
 
731
    parse_type2(R,Info,Opts,T#type{name=N,base={comp,N,[{int,"X"},{int,"Y"},
 
732
                                                        {int,"W"},{int,"H"}]}});
 
733
parse_type2([N="wxColour"|R],Info,Opts,T) -> 
 
734
    parse_type2(R,Info,Opts,T#type{name=N,
 
735
                                   base={comp,N,[{int,"R"},{int,"G"},{int,"B"},{int,"A"}]}});
 
736
parse_type2([N="wxColor"|R],Info,Opts,T) -> 
 
737
    parse_type2(R,Info,Opts,T#type{name="wxColour",
 
738
                                   base={comp,N,[{int,"R"},{int,"G"},{int,"B"},{int,"A"}]}});
 
739
 
 
740
parse_type2([N="wxPoint2DDouble"|R],Info,Opts,T) -> 
 
741
    parse_type2(R,Info,Opts,T#type{name=N,
 
742
                                   base={comp,N,[{double,"X"},{double,"Y"}]}});
 
743
parse_type2([N="wxRect2DDouble"|R],Info,Opts,T) -> 
 
744
    parse_type2(R,Info,Opts,T#type{name=N,
 
745
                                   base={comp,N,[{double,"X"},{double,"Y"},
 
746
                                                 {double,"W"},{double,"H"}]}});
 
747
 
 
748
parse_type2([N="wxDateTime"|R],Info,Opts,T) ->
 
749
    parse_type2(R,Info,Opts,T#type{name=N, 
 
750
                                   base={comp,N,[{int,"D"},{int,"Mo"},{int,"Y"},
 
751
                                                 {int,"H"},{int,"Mi"},{int,"S"}]}
 
752
                                  });
 
753
 
 
754
parse_type2([N="wxMouseState"|R],Info,Opts,T) -> 
 
755
    parse_type2(R,Info,Opts,T#type{name=N, base={comp,N,{record, wxMouseState}}});
 
756
parse_type2([N="wxString"|R],Info,Opts,T) -> 
 
757
    parse_type2(R,Info,Opts,T#type{name=N,base=[int]});
 
758
parse_type2([N="wxArtClient"|R],Info,Opts,T) -> 
 
759
    parse_type2(R,Info,Opts,T#type{name=N,base=[int]});
 
760
parse_type2(["wxArtID"|R],Info,Opts,T) -> 
 
761
    parse_type2(R,Info,Opts,T#type{name="wxString",base=[int]});
 
762
parse_type2([N="wxArrayString"|R],Info,Opts,T) -> 
 
763
    parse_type2(R,Info,Opts,T#type{name=N,base=[int],single=array,by_val=true});
 
764
parse_type2([{by_ref,Ref}|R],Info,Opts,T) -> 
 
765
    parse_type2(R,Info,Opts,T#type{ref=Ref,by_val=false});
 
766
parse_type2([],_,_,T) -> T;
 
767
 
 
768
parse_type2([N="wxImageList"|R],Info,Opts,T) ->  %% ARRG breaks the following clause
 
769
    parse_type2(R,Info,Opts,T#type{name=N,base={class,N}});
 
770
parse_type2(L=[Name|R],I,Opts,T) ->
 
771
    case reverse(Name) of
 
772
        "tsiL" ++ RBase -> 
 
773
            parse_type2(R,I,Opts,
 
774
                        T#type{name=Name,base={class,reverse(RBase)},single=list});
 
775
        _ -> 
 
776
            parse_type3(L,I,Opts,T)
 
777
    end.
 
778
 
 
779
parse_type3(["wxNotebookPage"|R],I,Opts,T) -> 
 
780
    Xml = case I of
 
781
              {_, Ref} -> Ref;
 
782
              undefined -> undefined
 
783
          end,
 
784
    parse_type2(R,I,Opts,T#type{name="wxWindow",base={class,"wxWindow"},xml=Xml});
 
785
parse_type3([N|R],I={"member",Ref},Opts,T) -> 
 
786
    Type = name(N,Opts),
 
787
    ErlClass = special_name(Type),
 
788
    case string:tokens(Ref, "_") of
 
789
        ["class" ++ _] -> ignore;
 
790
        Other -> 
 
791
            Inc0 = lists:takewhile(fun("8h") -> false;(_) -> true end,Other),
 
792
            Inc = gen_util:args(fun(A) -> A end, "_", Inc0),
 
793
%%          io:format("Inc ~s ~n", [Inc]),      
 
794
            put({include,Inc}, ref)
 
795
    end,
 
796
    case get_enum(Type) of
 
797
        {_, undefined} ->
 
798
            parse_type2(R,I,Opts,T#type{name=Type,base={class,ErlClass},xml=Ref});
 
799
        {TypeWOClass,#enum{}} -> 
 
800
            parse_type2(R,I,Opts,T#type{name=Type,base={enum,TypeWOClass},xml=Ref})
 
801
    end;
 
802
parse_type3([N = "wx"++_|R],I,Opts,T) -> 
 
803
    Xml = case I of
 
804
              {_, Ref} -> Ref;
 
805
              undefined -> undefined
 
806
          end,
 
807
    Class = name(N,Opts),
 
808
    ErlClass = special_name(Class),
 
809
    parse_type2(R,I,Opts,T#type{name=Class,base={class,ErlClass},xml=Xml});
 
810
parse_type3([N="WXWidget"|R], Info,Opts, T) -> 
 
811
    parse_type2(R,Info,Opts,T#type{name=N,base=long});
 
812
%% Let type errors be seen later because we don't know if these unhandled types
 
813
%% will be used.
 
814
parse_type3([Name|R],Info,Opts, T) ->
 
815
    New = T#type{name={unhandled,Name,Info,get(current_class),get(current_func)}},
 
816
    parse_type2(R,Info,Opts, New).
 
817
 
 
818
%%skipped(#method{method_type=constructor, type=void}, _Opts) -> true;
 
819
skipped(#method{}, #hs{skip=[]}) ->   false;
 
820
skipped(#method{name=Name,params=P}, #hs{skip=Skip}) ->    
 
821
    AtomName = list_to_atom(Name),
 
822
    Skipped = lists:member(AtomName, Skip) orelse 
 
823
        lists:member({AtomName,length(P)}, Skip),
 
824
    %% io:format("~p ~p skipped ~p ~n", [AtomName, length(P),Skipped]),
 
825
    Skipped.
 
826
    
 
827
add_method(Ms0, NoArgs, Class, Opts) ->
 
828
    Add = fun(M=#method{params=Ps0}, Acc) -> 
 
829
                  case length(Ps0) of
 
830
                      NoArgs -> 
 
831
                          [add_method2(M,Class,Opts)|Acc];
 
832
                      _ when NoArgs =:= all ->
 
833
                          [add_method2(M,Class,Opts)|Acc];
 
834
                      _ -> 
 
835
                          Acc
 
836
                  end
 
837
          end,
 
838
    NewMs  = lists:foldl(Add,[],Ms0),
 
839
    Unique = filter_functions(reverse(NewMs), Opts),
 
840
    erase(current_func),
 
841
    foldl(fun(M,C=#class{methods=Ms}) when is_list(M) -> C#class{methods=[M|Ms]} end,
 
842
          Class,reverse(Unique)).
 
843
 
 
844
add_method2(M0=#method{name=Name,params=Ps0,type=T0},#class{name=CName,parent=Par},#hs{fopt=Opts}) ->
 
845
    Type = case patch_param(Name, return, #param{type=T0}, Opts) of
 
846
               #param{type = T0} -> 
 
847
                   case patch_param(Name, {length(Ps0),return}, #param{type=T0}, Opts) of
 
848
                       #param{where=nowhere} -> void;
 
849
                       #param{type = Type0} -> Type0
 
850
                   end;
 
851
               #param{where=nowhere} -> void;
 
852
               #param{type = Type0} -> Type0
 
853
           end,
 
854
    
 
855
    {Req,Opt} = lists:partition(fun(#param{def=Def}) -> Def == none end, 
 
856
                                M0#method.params),
 
857
    Ps = reverse(Ps0),
 
858
    
 
859
    IsStatic = case Par of 
 
860
                   "static" -> static;
 
861
                   _ -> M0#method.method_type
 
862
               end,
 
863
    Where = case get_opt(where, Name, length(Ps), Opts) of
 
864
                undefined -> both;
 
865
                Other -> 
 
866
                    Other
 
867
            end,
 
868
    M1 = M0#method{defined_in=CName,
 
869
                   min_arity = length(Req),
 
870
                   max_arity = length(Req) + if length(Opt) > 0 -> 1; true -> 0 end,
 
871
                   type = Type,
 
872
                   method_type = IsStatic,
 
873
                   where = Where,
 
874
                   id=next_id(func_id),
 
875
                   pre_hook  = get_opt(pre_hook, Name, length(Ps), Opts),
 
876
                   post_hook = get_opt(post_hook, Name, length(Ps), Opts),
 
877
                   doc = get_opt(doc, Name, length(Ps), Opts) 
 
878
                  },
 
879
    M = case Name of
 
880
            CName ->
 
881
                M1#method{method_type=constructor,name=CName, 
 
882
                          type=constructor(CName), params=Ps};
 
883
            [$~|CName] ->
 
884
                M1#method{method_type=destructor,name=Name,
 
885
                          params=[this(CName)|Ps]};
 
886
            _ ->
 
887
                case M1#method.method_type of
 
888
                    static -> M1#method{params=Ps}; 
 
889
                    member -> M1#method{params=[this(CName)|Ps]}
 
890
                end
 
891
        end,
 
892
    M.
 
893
 
 
894
this(Class) ->
 
895
    #param{name="This",where=this,
 
896
           type=#type{name=Class,base={class,Class},by_val=false,ref={pointer,1}}}.
 
897
 
 
898
constructor(Class) ->
 
899
    #type{name=Class,base={class,Class},by_val=false,ref=reference}.
 
900
 
 
901
filter_functions(Parsed, Opts) ->
 
902
    Left = foldl(fun(M0,Acc) -> 
 
903
                         case skipped(M0, Opts) of
 
904
                             true ->  Acc;
 
905
                             false -> 
 
906
                                 TF = extract_type_footprint(M0),
 
907
                                 [TF|Acc]
 
908
                         end
 
909
                 end,[],Parsed),
 
910
    Clean = remove_or_merge(lists:sort(Left),[],[]),
 
911
    erl_skip_opt(reverse(Clean),[],[]).
 
912
 
 
913
remove_or_merge([{A,{L,In,O1},M1}|Rest=[{A,{L,In,O2},M2}|_]],Acc1,Acc2) 
 
914
  when M1#method.method_type =:= M2#method.method_type ->
 
915
    %% These are the same remove one of them.
 
916
    case O1 =:= O2 of
 
917
        true ->  ok;
 
918
        false -> 
 
919
            ?warning("Multiple out arguments of ~s:~s: ~p or ~p~n", 
 
920
                     [get(current_class),M1#method.name, O1,O2])
 
921
    end,
 
922
    remove_or_merge(Rest,Acc1,Acc2);
 
923
remove_or_merge([F={A,{Len,_,_},M1}|Rest],[{A,{Len,_,_},M2}|_]=Acc1,Acc2)
 
924
  when M1#method.method_type =:= M2#method.method_type ->
 
925
    NewAcc1 = maybe_merge(F,Acc1,[]),
 
926
    remove_or_merge(Rest,NewAcc1,Acc2);
 
927
remove_or_merge([F|Rest],[],Acc2) ->
 
928
    remove_or_merge(Rest,[F],Acc2);
 
929
remove_or_merge([F|Rest],Acc1,Acc2) ->
 
930
    remove_or_merge(Rest,[F], [reverse(Acc1)|Acc2]);
 
931
remove_or_merge([],[], Acc2) -> Acc2;
 
932
remove_or_merge([],Acc1,Acc2) -> [reverse(Acc1)|Acc2].
 
933
 
 
934
erl_skip_opt([Ms|R],[],Acc2) ->
 
935
    {Orig, Skipped} = erl_skip_opt2(Ms,[],[],[]),
 
936
    erl_skip_opt(R,Orig,[Skipped|Acc2]);
 
937
erl_skip_opt(All=[Ms=[{_,{Len,_,_},_}|_]|R],Acc1=[{_,{N,_,_},_}|_], Acc2) ->
 
938
    case Len =:= N+1 of
 
939
        true  ->
 
940
            {Orig, Skipped} = erl_skip_opt2(Ms,[],[],Acc1),
 
941
            erl_skip_opt(R,Orig,[Skipped++strip_ti(Acc1)|Acc2]);
 
942
        false ->
 
943
            erl_skip_opt(All, [], [strip_ti(Acc1)|Acc2])
 
944
    end;
 
945
erl_skip_opt([],Acc1,Acc2) -> [strip_ti(Acc1)|Acc2].
 
946
 
 
947
erl_skip_opt2([F={_,{N,In,_},M=#method{where=Where}}|Ms],Acc1,Acc2,Check) -> 
 
948
    case N > 0 andalso lists:last(In) =:= opt_list of
 
949
        true when Where =/= merged_c, Where =/= taylormade -> 
 
950
            case Check of 
 
951
                [] -> 
 
952
                    erl_skip_opt2(Ms,[F|Acc1],[M#method{where=erl_no_opt}|Acc2],[]);
 
953
                _  -> 
 
954
                    Skipped = reverse(tl(reverse(In))),
 
955
                    T = fun({_,{_,Args,_},_}) -> true =:= types_differ(Skipped,Args) end,
 
956
                    case lists:all(T, Check) of
 
957
                        true -> 
 
958
                            erl_skip_opt2(Ms,[F|Acc1],
 
959
                                          [M#method{where=erl_no_opt}|Acc2],
 
960
                                          Check);
 
961
                        false ->
 
962
                            erl_skip_opt2(Ms,[F|Acc1],Acc2,Check)
 
963
                    end
 
964
            end;
 
965
        _ ->
 
966
            erl_skip_opt2(Ms,[F|Acc1],Acc2,[])
 
967
    end;
 
968
erl_skip_opt2([],Acc1,Acc2,_) -> {Acc1,Acc2}.
 
969
 
 
970
strip_ti(Ms) ->
 
971
    [M || {_,{_,_,_},M} <- Ms].
 
972
 
 
973
maybe_merge(T1,[],Acc) -> reverse([T1|Acc]);
 
974
maybe_merge(F={A1,T1={Len,In1,O1},M1},[C={A2,T2={Len,In2,O2},M2}|Rest],Acc) ->
 
975
    case types_differ(In1,In2) of
 
976
        true -> maybe_merge(F,Rest,[C|Acc]);
 
977
        {class,C1,C2} when O1 =:= O2 ->
 
978
            {Merged,M2Mod} = merge_class_params(M1,M2,C1,C2),
 
979
            reverse([{A1,T1,Merged},{A2,T2,M2Mod}|Acc]) ++ Rest;
 
980
        false ->
 
981
            ?warning("Argument clash in ~s:~s:~n   ~p~nor ~p~n", 
 
982
                     [get(current_class),M1#method.name,{In1,O1},{In2,O2}]),
 
983
            [F|Rest++Acc]
 
984
    end.
 
985
 
 
986
merge_class_params(M1=#method{params=P1,id=Mi1},M2=#method{params=P2,id=Mi2},C1,C2) ->
 
987
    Merged = merge_class_params2({class,C1},P1,Mi1,{class,C2},P2,Mi2),
 
988
    {M1#method{params=Merged}, M2#method{where=merged_c}}.
 
989
 
 
990
merge_class_params2(B1,[P1|R1],M1,B2,[P1|R2],M2) ->
 
991
    [P1|merge_class_params2(B1,R1,M1,B2,R2,M2)];
 
992
merge_class_params2(B1,[P1=#param{type=T1=#type{base=B1}}|R1],M1,
 
993
                    B2,[#param{type=T2=#type{base=B2}}|R2],M2) ->
 
994
    [P1#param{type={merged,M1,T1,R1,M2,T2,R2}}|merge_class_params2(B1,R1,M1,B2,R2,M2)];
 
995
merge_class_params2(B1,[P1|R1],_M1,B2,[P2|R2],_M2) ->
 
996
    io:format("Merged Failed ~p ~p~n", [B1,B2]),
 
997
    io:format("  ~p ~p~n  ~p~p~n", [P1,R1,P2,R2]),
 
998
    ?error(merged_failed);
 
999
merge_class_params2(_,[],_,_,[],_) ->
 
1000
    [].
 
1001
 
 
1002
types_differ([C1|R1], [C2|R2]) when is_list(C1), is_list(C2) ->
 
1003
    types_differ(R1,R2); %% Different Classes
 
1004
types_differ([C|R1], [C|R2]) ->
 
1005
    types_differ(R1,R2);
 
1006
types_differ([{term,_}|R1], [_|R2]) ->
 
1007
    types_differ(R1,R2);
 
1008
types_differ([_|R1], [{term,_}|R2]) ->
 
1009
    types_differ(R1,R2);
 
1010
types_differ([{class,C1}|R1], [{class,C2}|R2]) ->
 
1011
    case types_differ(R1,R2) of
 
1012
        true -> 
 
1013
            true;
 
1014
        false -> 
 
1015
%%      _ ->
 
1016
            {class,C1,C2};
 
1017
        {class,C1,C2} -> 
 
1018
            {class,C1,C2};
 
1019
        {class, _,_} -> 
 
1020
            false
 
1021
    end;
 
1022
types_differ([int|_], _) -> true;
 
1023
types_differ(_, [int|_]) -> true;
 
1024
types_differ([{class,_}|_], _) -> true;
 
1025
types_differ(_, [{class,_}|_]) -> true;
 
1026
types_differ([binary|_], _) -> true;
 
1027
types_differ(_, [binary|_]) -> true;
 
1028
 
 
1029
types_differ([list|R1], [opt_list|R2]) ->
 
1030
    types_differ(R1,R2);
 
1031
types_differ([opt_list|R1], [list|R2]) ->
 
1032
    types_differ(R1,R2);
 
1033
types_differ([C1|R1], [C2|R2]) when is_tuple(C1), is_tuple(C2) ->
 
1034
    (size(C1) =/= size(C2)) orelse types_differ(R1,R2);
 
1035
types_differ([C1|_R1], [_C2|_R2]) when is_tuple(C1) ->
 
1036
    true;
 
1037
types_differ([_C1|_R1], [C2|_R2]) when is_tuple(C2)-> 
 
1038
    true;
 
1039
types_differ([_C1|R1], [_C2|R2]) -> %% More cases?
 
1040
    types_differ(R1,R2);
 
1041
types_differ([], []) ->
 
1042
    false.
 
1043
 
 
1044
extract_type_footprint(M=#method{type=void,alias=A,params=Ps}) ->
 
1045
    {A,extract_type_footprint2(Ps, [], [], false), M};
 
1046
extract_type_footprint(M=#method{type=Type,alias=A,params=Ps}) ->
 
1047
    {A,extract_type_footprint2(Ps, [type_foot_print(Type)], [], false), M}.
 
1048
 
 
1049
extract_type_footprint2([_P=#param{where=c, in=InArg}|R], Out, In, Opt) 
 
1050
  when InArg =/= false ->
 
1051
    extract_type_footprint2(R, Out, In, Opt);
 
1052
extract_type_footprint2([_P=#param{def=Def, in=InArg}|R], Out, In, _Opt) when Def =/= none, InArg =/= false ->
 
1053
    extract_type_footprint2(R, Out, In, true);
 
1054
extract_type_footprint2([#param{in=false, type=Type}|Ps], Out, In, Opt) ->
 
1055
    extract_type_footprint2(Ps, [type_foot_print(Type)|Out], In, Opt);
 
1056
extract_type_footprint2([#param{in=true, type=Type}|Ps], Out, In, Opt) ->
 
1057
    extract_type_footprint2(Ps, Out, [type_foot_print(Type)|In], Opt);
 
1058
extract_type_footprint2([#param{in=both, type=Type}|Ps], Out, In, Opt) ->
 
1059
    TFP = type_foot_print(Type),
 
1060
    extract_type_footprint2(Ps, [TFP|Out], [TFP|In], Opt);
 
1061
 
 
1062
extract_type_footprint2([], Out0, In, Opt) ->
 
1063
    Out = case Out0 of
 
1064
              [] -> void;
 
1065
              [One] -> One;
 
1066
              _ -> list_to_tuple(reverse(Out0))
 
1067
          end,
 
1068
    if Opt -> 
 
1069
            {length(In)+1,reverse([opt_list|In]),Out};
 
1070
       true ->
 
1071
            {length(In), reverse(In),Out}
 
1072
    end.
 
1073
 
 
1074
type_foot_print(#type{single=Single}) when Single =/= true -> list;
 
1075
type_foot_print(#type{base=Base}) when is_list(Base) -> list;
 
1076
type_foot_print(#type{base=long}) ->      int;
 
1077
type_foot_print(#type{base=binary}) ->    binary;
 
1078
type_foot_print(#type{base={binary,_}}) ->    binary;
 
1079
type_foot_print(#type{base=int}) ->       int;
 
1080
type_foot_print(#type{base=bool}) ->      bool;
 
1081
%%type_foot_print(#type{base=datetime}) ->  datetime;
 
1082
type_foot_print(#type{base=float}) ->     float;
 
1083
type_foot_print(#type{base=double}) ->    float;
 
1084
type_foot_print(#type{base=C={class,_}}) -> C;
 
1085
type_foot_print(#type{base={enum,_}}) ->  int;
 
1086
type_foot_print(#type{base={ref,_}}) ->   ref;
 
1087
type_foot_print(#type{base={term,_}}) ->  term;
 
1088
type_foot_print(#type{base=eventType}) -> atom;
 
1089
%% type_foot_print({Type,Str}) when is_list(Str) ->
 
1090
%%     type_foot_print(Type);
 
1091
type_foot_print(#type{base={comp,_,R={record,_}}}) ->
 
1092
    R;
 
1093
type_foot_print(#type{base={comp,_,Types}}) ->
 
1094
    TFL = map(fun({T,N}) when is_list(N) -> 
 
1095
                      case T of
 
1096
                          double -> float;
 
1097
                          _ -> T
 
1098
                      end
 
1099
              end, Types),
 
1100
    list_to_tuple(TFL).
 
1101
%type_foot_print(What) -> What.
 
1102
 
 
1103
 
 
1104
translate_enums(Defs) ->
 
1105
    Res = [translate_enums1(Def) || Def <- Defs],
 
1106
    Consts = [Enum || Enum = {{enum,_},_} <- get()],
 
1107
    translate_constants(Consts, get(not_const), get(const_skip)),
 
1108
    put(gvars, [{Gvar,Class,next_id(const)} || {Gvar,Class} <- lists:sort(get(gvars))]),
 
1109
    Res.
 
1110
 
 
1111
translate_enums1(C=#class{name=Name, methods=Ms0, attributes=As0}) ->
 
1112
    Ms = [translate_enums2(M, Name) || M <- Ms0],
 
1113
    As = [translate_enums3(A, Name) || A <- As0],
 
1114
    C#class{methods=Ms, attributes=As}.
 
1115
 
 
1116
translate_enums2(M=#method{params=Ps0, type=T0},Class) ->
 
1117
    Ps = [translate_enums3(P, Class) || P <- Ps0],
 
1118
    T = translate_enums_type(T0,Class),
 
1119
    M#method{params=Ps,type=T};
 
1120
translate_enums2(Ms,Class) when is_list(Ms) ->
 
1121
    [translate_enums2(M,Class) || M <- Ms].
 
1122
 
 
1123
translate_enums3(P=#param{type=Type0},InClass) ->
 
1124
    Type = translate_enums_type(Type0,InClass),
 
1125
    P#param{type=Type};
 
1126
translate_enums3(InHer = {inherited, _},_InClass) ->
 
1127
    InHer.
 
1128
 
 
1129
translate_enums_type(T=#type{base={class,C}},Class) ->
 
1130
    case get_enum(C,Class) of
 
1131
        {_, undefined} -> T;
 
1132
        {Enum, #enum{}} ->
 
1133
            %% io:format("ENUM Change class ~p to enum ~p~n", [C,Enum]),
 
1134
            T#type{base={enum, Enum}}
 
1135
    end;
 
1136
translate_enums_type(T,_Class) ->   T.
 
1137
 
 
1138
translate_constants(Enums, NotConsts0, Skip0) ->
 
1139
    NotConsts = gb_sets:from_list(NotConsts0),
 
1140
    Skip = gb_sets:from_list(Skip0),
 
1141
    Consts0 = create_consts(lists:sort(Enums), Skip, NotConsts, []),
 
1142
    put(consts, gb_trees:from_orddict(lists:ukeysort(1,[{N,C}|| C = #const{name=N} <- Consts0]))).
 
1143
 
 
1144
create_consts([{{enum, Name},Enum = #enum{vals=Vals}}|R], Skip, NotConsts, Acc0) ->
 
1145
    CC = fun(What, Acc) ->
 
1146
                 create_const(What, Skip, NotConsts, Acc)
 
1147
         end,
 
1148
    Acc = case Vals of
 
1149
              undefined -> 
 
1150
                  ?warning("Missing Enum ~p ~p ~n",[Name, Enum]), 
 
1151
                  Acc0;
 
1152
              [] -> %% ?warning("Ignored Empty Enum list ~p ~n",[_Name]), 
 
1153
                  Acc0;
 
1154
              _ ->  
 
1155
                  foldl(CC, Acc0, lists:sort(Vals))
 
1156
          end,
 
1157
    create_consts(R, Skip, NotConsts, Acc);
 
1158
create_consts([],_,_,Acc) -> Acc.
 
1159
 
 
1160
create_const({Name, Val}, Skip, NotConsts, Acc) ->
 
1161
    case gb_sets:is_member(Name, Skip) of
 
1162
        true -> Acc;
 
1163
        false ->
 
1164
            case gb_sets:is_member(Name, NotConsts) of
 
1165
                true ->
 
1166
                    [#const{name=Name,val=next_id(const),is_const=false}|Acc];
 
1167
                false ->
 
1168
                    [#const{name=Name,val=Val,is_const=true}|Acc]
 
1169
%%              false ->
 
1170
%%                  [#const{name=Name,val=Val}|Acc]
 
1171
            end
 
1172
    end.
 
1173
 
 
1174
%%%%%%%%%%%%%      
 
1175
next_id(What) ->
 
1176
    Next = case get(What) of
 
1177
               undefined -> 100;
 
1178
               N -> N+1
 
1179
           end,
 
1180
    put(What, Next),
 
1181
    Next.
 
1182
 
 
1183
name([$~|Name], Opts) ->
 
1184
    [$~|name(Name,Opts)];
 
1185
name(Name0, #hs{alias=Alias}) ->
 
1186
    Name = case reverse(Name0) of
 
1187
               "esaBlooT" ++ _ ->  %% Arrg uses base
 
1188
                   Name0;
 
1189
               "esaBelbaTdirG" ++ _ ->  %% Arrg uses base
 
1190
                   Name0;
 
1191
               "esaBrekciP"  ++ _ ->  %% Arrg uses base
 
1192
                   Name0;
 
1193
               "esaB" ++ Rest when hd(Name0) == $w -> 
 
1194
                   %% Arrg Some decl uses base class directly
 
1195
                   reverse(Rest);  
 
1196
               _F -> 
 
1197
                   Name0
 
1198
           end,
 
1199
    get_value(Name,Alias,Name).
 
1200
 
 
1201
special_name("wxIconLocation") -> "wx";
 
1202
special_name("wxToolBarToolBase") -> "wx";
 
1203
special_name("wxObject") -> "wx";
 
1204
special_name("wxValidator") -> "wx";     % XXXXX
 
1205
%% special_name("wxTreeItemData") -> "wx";  % XXXXX
 
1206
%% special_name("wxTreeItemId") -> "wx";
 
1207
%% special_name("wxDataObject") -> "wx";
 
1208
special_name(Other) -> Other.
 
1209
 
 
1210
drop_empty(List) ->
 
1211
    filter(fun(#xmlText { value = Text}) ->                
 
1212
                   string:strip(Text) =/= "";
 
1213
              (_)->
 
1214
                   true
 
1215
           end, List).
 
1216
 
 
1217
%%% Enums
 
1218
parse_enums(Files) ->
 
1219
    DontSearch = ["wxchar","filefn", "platform", "strconv", 
 
1220
                  "buffer", "string", "debug", "platinfo"],
 
1221
    %% Arg need to patch some specials, atleast for wx-2.6
 
1222
    ExtraSearch = ["gtk_2glcanvas", "generic_2splash"],
 
1223
    parse_enums(Files ++ ExtraSearch,gb_sets:from_list(DontSearch)).
 
1224
 
 
1225
parse_enums([File|Files], Parsed) ->
 
1226
    case gb_sets:is_member(File,Parsed) of
 
1227
        false ->
 
1228
            FileName = filename:join(["wx_xml",File ++ "_8h.xml"]),
 
1229
%%          io:format("Parse Enums in ~s ~n", [FileName]),
 
1230
            case xmerl_scan:file(FileName, [{space, normalize}]) of 
 
1231
                {error, enoent} ->
 
1232
                    parse_enums(Files, gb_sets:add(File,Parsed));
 
1233
                {Doc, _} ->                 
 
1234
                    ES = "./compounddef/sectiondef/memberdef[@kind=\"enum\"]",
 
1235
                    AM = xmerl_xpath:string(ES, Doc),
 
1236
                    lists:foreach(fun(Def) -> extract_enum(Def, undefined, File) end, AM),
 
1237
 
 
1238
                    DS = "./compounddef/sectiondef/memberdef[@kind=\"define\"]",
 
1239
                    Defs = xmerl_xpath:string(DS, Doc),
 
1240
                    extract_defs(Defs,File),
 
1241
 
 
1242
                    INCs = xmerl_xpath:string("./compounddef/includes/text()", Doc),
 
1243
                    New = [reverse(tl(tl(reverse(Inc)))) || 
 
1244
                              #xmlText{value="wx/"++Inc} <- INCs],
 
1245
                    %% io:format("Scan enums from ~p ~n", [File]),
 
1246
                    parse_enums(New ++ Files, gb_sets:add(File,Parsed))
 
1247
            end;
 
1248
        true ->
 
1249
            parse_enums(Files,Parsed)
 
1250
    end;
 
1251
parse_enums([],_) -> ok. 
 
1252
    
 
1253
extract_enum(#xmlElement{name=memberdef,content=C}, Class, File) ->
 
1254
    {Name0,Vals0} = extract_enum2(C,undefined,0,[]),
 
1255
    {Vals,Name} = 
 
1256
        if 
 
1257
            hd(Name0) =:= $@, Class =:= undefined ->
 
1258
                {Vals0, Name0 ++ "_" ++ File};
 
1259
            Class =:= undefined-> 
 
1260
                {Vals0, Name0};
 
1261
            true -> 
 
1262
                {[{Class++"::"++N,V} || {N,V} <- Vals0], {Class,Name0}}
 
1263
        end,
 
1264
    case get({enum, Name}) of
 
1265
        undefined -> 
 
1266
%%          io:format("1Enum name ~p~n", [Name]),
 
1267
%%          [io:format("  ~s ~p~n", [D,V]) || {D,V} <- Vals],
 
1268
            put({enum, Name}, #enum{vals=Vals});
 
1269
        E = #enum{vals=undefined} -> 
 
1270
%%          io:format("2Enum name ~p~n", [Name]),
 
1271
%%          [io:format("  ~s ~p~n", [D,V]) || {D,V} <- Vals],
 
1272
            put({enum, Name}, E#enum{vals=Vals});
 
1273
        #enum{vals=Vals} -> ok;
 
1274
%%          io:format("Same? ~p ~n", [PVals == Vals])
 
1275
        #enum{vals=OldVals} ->      
 
1276
            io:format("Enum ~p in ~p ~p ~p~n", [Name,Class,get(current_class),get(current_func)]),
 
1277
            io:format("New ~p~n", [Vals]),
 
1278
            io:format("Old ~p~n", [OldVals]),
 
1279
            erlang:error({enum_mismatch,Name,Vals,OldVals})
 
1280
    end,
 
1281
    ok.
 
1282
 
 
1283
extract_enum2([#xmlElement{name=name,content=[#xmlText{value=Name}]}|R],_,Id,Acc0) ->
 
1284
    extract_enum2(R,Name,Id,Acc0);
 
1285
 
 
1286
extract_enum2([#xmlElement{name=enumvalue,content=C}|R], N,Id,Acc0) ->
 
1287
    {Acc,NewId} = extract_enum3(C,Id,Acc0),
 
1288
    extract_enum2(R, N, NewId, Acc);
 
1289
extract_enum2([_|R], N, Id, Acc) ->
 
1290
    extract_enum2(R, N, Id, Acc);
 
1291
extract_enum2([], N, _Id, Acc) ->
 
1292
    {N, reverse(Acc)}.
 
1293
 
 
1294
extract_enum3([#xmlElement{name=name,content=[#xmlText{value=Name}]}|R], Id, Acc) ->
 
1295
    case lists:keymember(Name, 1, Acc) of
 
1296
        true ->  %% Doxygen double includes some defs. 
 
1297
            {Acc,Id};
 
1298
        false ->
 
1299
            case Id of
 
1300
                This = {Str,Num} -> 
 
1301
                    extract_enum3(R, {Str, Num+1}, [{Name,This}|Acc]);
 
1302
                Val ->
 
1303
                    extract_enum3(R, Val+1, [{Name,Val}|Acc])
 
1304
            end
 
1305
    end;
 
1306
 
 
1307
extract_enum3([#xmlElement{name=initializer,
 
1308
                           content=[#xmlText{value=V}]}|_],_Id,[{Name,_}|Acc]) ->
 
1309
    Val0 = string:strip(V),
 
1310
    try 
 
1311
        case Val0 of
 
1312
            "0x" ++ Val1 -> 
 
1313
                Val = http_util:hexlist_to_integer(Val1),
 
1314
                {[{Name, Val}|Acc], Val+1};
 
1315
            _ ->
 
1316
                Val = list_to_integer(Val0),
 
1317
                {[{Name, Val}|Acc], Val+1}
 
1318
        end
 
1319
    catch _:_ -> 
 
1320
            {[{Name,{Val0,0}}|Acc], {Val0,1}}
 
1321
    end;
 
1322
extract_enum3([_|R], Id, Acc) ->
 
1323
    extract_enum3(R, Id, Acc);
 
1324
extract_enum3([], Id, Acc) ->
 
1325
    {Acc, Id}.
 
1326
 
 
1327
extract_defs(Defs, File) ->
 
1328
    case foldl(fun extract_defs2/2, {[], gb_sets:empty()}, Defs) of
 
1329
        [] -> ok;
 
1330
        {Vals,_Skip} ->
 
1331
%%          io:format("Defs file ~p~n", [File]),
 
1332
%%          [io:format("  ~s ~p~n", [D,V]) || {D,V} <- Vals, not is_integer(V)]
 
1333
            put({enum, {define,"From " ++ File ++ ".h"}}, #enum{vals=Vals})
 
1334
    end.
 
1335
 
 
1336
extract_defs2(#xmlElement{name=memberdef,content=C},{Acc,Skip}) ->
 
1337
    try 
 
1338
        Res = {Name,_} = extract_def(C,undefined,Skip),
 
1339
        case gb_sets:is_member(Name,Skip) orelse lists:keymember(Name, 1, Acc) of
 
1340
            true -> {Acc,Skip};
 
1341
            false -> {[Res | Acc], Skip}
 
1342
        end
 
1343
    catch throw:SkipName -> {Acc, gb_sets:add(SkipName,Skip)}
 
1344
    end.
 
1345
             
 
1346
extract_def([#xmlElement{name=name,content=[#xmlText{value=Name}]}|R], _N, Skip) ->
 
1347
    case Name of
 
1348
        "wxUSE" ++ _ ->
 
1349
            throw(Name);
 
1350
        "wx" ++ _ ->
 
1351
            extract_def(R, Name, Skip);
 
1352
        _ -> 
 
1353
            throw(Name)
 
1354
    end;
 
1355
extract_def([#xmlElement{name=param}|_],Name,_) ->
 
1356
    throw(Name);
 
1357
extract_def([#xmlElement{name=initializer,content=[#xmlText{value=Val0}]}|_],N,Skip) ->
 
1358
    case Val0 of
 
1359
        "0x" ++ Val1 -> {N, http_util:hexlist_to_integer(Val1)};
 
1360
        _ ->
 
1361
            try
 
1362
                Val = list_to_integer(Val0),
 
1363
                {N, Val}
 
1364
            catch _:_ ->  
 
1365
                    case def_is_ok(Val0, Skip) of
 
1366
                        false ->
 
1367
                            throw(N);
 
1368
                        NVal when is_integer(NVal) -> 
 
1369
                            {N, NVal};
 
1370
                        NVal ->
 
1371
                            {N, {NVal,0}}
 
1372
                    end
 
1373
            end
 
1374
    end;
 
1375
extract_def([_|R],N,Skip) ->
 
1376
    extract_def(R,N,Skip);
 
1377
extract_def(_,N,_) ->
 
1378
    throw(N).
 
1379
                     
 
1380
def_is_ok(Name, Skip) ->
 
1381
    Toks = gen_util:tokens(Name,"()| \\:"),
 
1382
    R = def_is_ok(Toks, Skip, []),
 
1383
%    io:format("~s -> ~p~n", [Name,R]),
 
1384
    R.
 
1385
 
 
1386
def_is_ok([], _Skip, [")",Int, "("]) -> Int;
 
1387
def_is_ok([], _Skip, Acc) -> lists:append(reverse(Acc));
 
1388
def_is_ok([N="wx"++_|R],Skip,Acc) ->
 
1389
    case gb_sets:is_member(N,Skip) of
 
1390
        true -> false;
 
1391
        false -> def_is_ok(R,Skip,[N|Acc])
 
1392
    end;
 
1393
def_is_ok(["0x"++Val|R],Skip,Acc) ->
 
1394
    def_is_ok(R,Skip,["16#" ++ Val|Acc]);
 
1395
def_is_ok([N="|"|R], Skip, Acc) ->
 
1396
    def_is_ok(R,Skip,[N|Acc]);
 
1397
def_is_ok([N="("|R], Skip, Acc) ->
 
1398
    def_is_ok(R,Skip,[N|Acc]);
 
1399
def_is_ok([N=")"|R], Skip, Acc) ->
 
1400
    def_is_ok(R,Skip,[N|Acc]);
 
1401
def_is_ok([":"|_], _Skip, _Acc) ->
 
1402
    false;
 
1403
def_is_ok([N|R],Skip,Acc) ->
 
1404
    case catch list_to_integer(N) of
 
1405
        {'EXIT', _} -> false;
 
1406
        Int -> def_is_ok(R,Skip,[Int|Acc])
 
1407
    end.
 
1408
 
 
1409
get_enum(Type0) when is_list(Type0) ->
 
1410
    case string:tokens(Type0,":") of
 
1411
        [Type] -> 
 
1412
            {Type, get({enum,Type})};
 
1413
        [Class,Type] -> 
 
1414
            get_enum(Type,Class)
 
1415
    end;
 
1416
get_enum({Class,Type}) ->
 
1417
    get_enum(Type,Class).
 
1418
 
 
1419
get_enum(Type,Class) ->
 
1420
    case get({enum,Type}) of
 
1421
        undefined -> 
 
1422
            {{Class,Type},get({enum, {Class,Type}})};
 
1423
        Res = #enum{} ->
 
1424
            {Type,Res}
 
1425
    end.