~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%%%-------------------------------------------------------------------
119
119
            case [P || P <- Parents, P =/= root, P =/= object] of
120
120
                [] -> ignore;
121
121
                Ps -> 
122
 
                    w("%% <p>This class is derived (and can use functions) from: ~n", []),
 
122
                    w("%% <p>This class is derived (and can use functions) from:~n", []),
123
123
                    [w("%% <br />{@link ~s}~n", [P]) || P <- Ps],
124
124
                    w("%% </p>~n",[])               
125
125
            end,
302
302
gen_dest2(Class, Id) ->
303
303
    w("%% @spec (This::~s()) -> ok~n", [Class]),
304
304
    w("%% @doc Destroys this object, do not use object again~n", []),
305
 
    w("destroy(Obj=#wx_ref{type=Type}) -> ~n", []),
 
305
    w("destroy(Obj=#wx_ref{type=Type}) ->~n", []),
306
306
    w("  ?CLASS(Type,~s),~n",[Class]), 
307
307
    case Id of
308
308
        object ->
317
317
gen_inherited([Parent|Ps], Done0, Exported0) ->
318
318
    #class{name=Class, methods=Ms} = get({class,Parent}),
319
319
    case is_list(Exported0) of
320
 
        false -> w(" %% From ~s ~n", [Class]);
 
320
        false -> w(" %% From ~s~n", [Class]);
321
321
        true  -> ignore
322
322
    end,
323
323
    {Done,Exported} = gen_inherited_ms(Ms, Class, Done0, gb_sets:empty(), Exported0),
575
575
    "is_list(" ++ erl_arg_name(Name) ++  ")";
576
576
guard_test(#param{name=N,type=#type{base=int}}) ->
577
577
    "is_integer(" ++ erl_arg_name(N) ++ ")";
 
578
guard_test(#param{name=N,type=#type{base=int64}}) ->
 
579
    "is_integer(" ++ erl_arg_name(N) ++ ")";
578
580
guard_test(#param{name=N,type=#type{base=long}}) ->
579
581
    "is_integer(" ++ erl_arg_name(N) ++ ")";
580
582
guard_test(#param{name=N,type=#type{base=float}}) ->
603
605
    "tuple_size(" ++ erl_arg_name(N) ++ ") =:= 3; tuple_size(" ++ erl_arg_name(N) ++ ") =:= 4";
604
606
guard_test(#param{name=N,type=#type{base={comp,_,Tup}}}) ->
605
607
    Doc = fun({int,V}) -> "is_integer("++erl_arg_name(N)++V ++")";
 
608
             ({int64,V}) -> "is_integer("++erl_arg_name(N)++V ++")";
606
609
             ({double,V}) -> "is_number("++erl_arg_name(N)++V ++")"
607
610
          end,
608
611
    args(Doc, ",", Tup);
670
673
              [lowercase_all(Class),lowercase_all(Class),lowercase_all(N)])
671
674
    end,
672
675
    Name = case MT of constructor -> "new"; _ -> erl_func_name(N,A) end,
673
 
    w("%% <br /> Alternatives: ~n",[]),
 
676
    w("%% <br /> Alternatives:~n",[]),
674
677
    [gen_doc2(Name, Clause) || Clause <- Cs], 
675
678
    ok.
676
679
 
768
771
doc_arg_type3(#type{name="wxDateTime"}) ->    "wx:datetime()";
769
772
doc_arg_type3(#type{name="wxArtClient"}) ->    "string()";
770
773
doc_arg_type3(#type{base=int}) ->        "integer()";
 
774
doc_arg_type3(#type{base=int64}) ->        "integer()";
771
775
doc_arg_type3(#type{base=long}) ->       "integer()";
 
776
doc_arg_type3(#type{name="wxTreeItemId"}) -> "wxTreeCtrl:treeItemId()";
772
777
doc_arg_type3(#type{base=bool}) ->       "bool()";
773
778
doc_arg_type3(#type{base=float}) ->      "float()";
774
779
doc_arg_type3(#type{base=double}) ->     "float()";
851
856
    doc_enum_desc(R).
852
857
 
853
858
%% Misc functions prefixed with wx
854
 
erl_func_name("wx" ++ Name, undefined) ->   check_name(lowercase(Name));  
 
859
erl_func_name("wx" ++ Name, undefined) ->   check_name(lowercase(Name));
855
860
erl_func_name(Name, undefined) ->   check_name(lowercase(Name));
856
861
erl_func_name(_, Alias) -> check_name(lowercase(Alias)).
857
862
 
926
931
    align(32, Align, Name ++ ":32/?F");
927
932
marshal_arg(#type{single=true,base=double}, Name, Align) ->
928
933
    align(64, Align, Name ++ ":64/?F");
 
934
marshal_arg(#type{single=true,base=int64}, Name, Align) ->
 
935
    align(64, Align, Name ++ ":64/?UI");
929
936
marshal_arg(#type{single=true,base=int}, Name, Align) ->
930
937
    align(32, Align, Name ++ ":32/?UI");
931
938
marshal_arg(#type{single=true,base={enum,_Enum}}, Name, Align) ->
1019
1026
 
1020
1027
gen_enums_ints() ->
1021
1028
    %% open_write("../include/wx.hrl"), opened in gen_event_recs
1022
 
    w("~n%% Hardcoded Records ~n", []),
1023
 
    w("-record(wxMouseState, {x, y,  %% integer() ~n"
1024
 
      "          leftDown, middleDown, rightDown, %% bool() ~n"
 
1029
    w("~n%% Hardcoded Records~n", []),
 
1030
    w("-record(wxMouseState, {x, y,  %% integer()~n"
 
1031
      "          leftDown, middleDown, rightDown, %% bool()~n"
1025
1032
      "          controlDown, shiftDown, altDown, metaDown, cmdDown %% bool()~n"
1026
1033
      "        }).~n", []),
1027
 
    w("-record(wxHtmlLinkInfo, { ~n"
1028
 
      "          href, target %% string() ~n"
 
1034
    w("-record(wxHtmlLinkInfo, {~n"
 
1035
      "          href, target %% string()~n"
1029
1036
      "        }).~n", []),
1030
 
    w("~n%% Hardcoded Defines ~n", []),
 
1037
    w("~n%% Hardcoded Defines~n", []),
1031
1038
    Enums = [E || E = {{enum,_},#enum{as_atom=false}} <- get()],
1032
1039
    w("-define(wxDefaultSize, {-1,-1}).~n", []), 
1033
1040
    w("-define(wxDefaultPosition, {-1,-1}).~n", []), 
1034
 
    w("~n%% Global Variables ~n", []),
 
1041
    w("~n%% Global Variables~n", []),
1035
1042
    [w("-define(~s,  wxe_util:get_const(~s)).~n", [Gvar, Gvar]) || 
1036
1043
        {Gvar,_,_Id} <- get(gvars)],
1037
 
    w("~n%% Enum and defines ~n", []),
 
1044
    w("~n%% Enum and defines~n", []),
1038
1045
    foldl(fun({{enum,Type},Enum= #enum{as_atom=false}}, Done) ->
1039
1046
                  build_enum_ints(Type,Enum,Done);
1040
1047
             (_,Done) -> Done
1044
1051
build_enum_ints(Type,#enum{vals=Vals},Done) ->
1045
1052
    case Type of
1046
1053
        [$@|_] ->  ok; % anonymous
1047
 
        {Class,[$@|_]} when Vals =/= [] ->  w("% From class ~s ~n", [Class]);
1048
 
        {Class,Enum} when Vals =/= [] ->  w("% From ~s::~s ~n", [Class,Enum]);
1049
 
        _ when Vals =/= [] ->  w("% Type ~s ~n", [Type]);
 
1054
        {Class,[$@|_]} when Vals =/= [] ->  w("% From class ~s~n", [Class]);
 
1055
        {Class,Enum} when Vals =/= [] ->  w("% From ~s::~s~n", [Class,Enum]);
 
1056
        _ when Vals =/= [] ->  w("% Type ~s~n", [Type]);
1050
1057
        _ -> ok
1051
1058
    end,
1052
1059
    
1089
1096
    erl_copyright(),
1090
1097
    w("", []),
1091
1098
    w("%% This file is generated DO NOT EDIT~n~n", []),
1092
 
    w("%%  All event messages are encapsulated in a wx record ~n"
 
1099
    w("%%  All event messages are encapsulated in a wx record~n"
1093
1100
      "%%  they contain the widget id and a specialized event record.~n" 
1094
1101
      "%%  Each event record may be sent for one or more event types.~n" 
1095
1102
      "%%  The mapping to wxWidgets is one record per class.~n~n",[]),
1097
1104
    w("-record(wx, {id,     %% Integer Identity of object.~n"
1098
1105
      "             obj,    %% Object reference that was used in the connect call.~n"
1099
1106
      "             userData, %% User data specified in the connect call.~n"
1100
 
      "             event}).%% The event record ~n~n",[]),
 
1107
      "             event}).%% The event record~n~n",[]),
1101
1108
    w("%% Here comes the definitions of all event records.~n"
1102
1109
      "%% they contain the event type and possible some extra information.~n~n",[]),
1103
1110
    Types = [build_event_rec(C) || {_,C=#class{event=Evs}} <- get(), Evs =/= false],
1150
1157
%%              false -> w("%% This event will be handled by other handlers~n",[])
1151
1158
%%          end,
1152
1159
            w("%% Callback event: {@link ~s}~n", [Name]),
1153
 
            w("-record(~s, {type}). ~n~n", [Rec]);
 
1160
            w("-record(~s, {type}).~n~n", [Rec]);
1154
1161
        false ->
1155
1162
            w("%% @type ~s() = #~s{type=wxEventType(),~s}.~n", 
1156
1163
              [Rec,Rec,args(GetType,",",Attr)]),
1160
1167
%%              false -> w("%% This event will be handled by other handlers~n",[])
1161
1168
%%          end,            
1162
1169
            w("%% Callback event: {@link ~s}~n", [Name]),
1163
 
            w("-record(~s,{type, ~s}). ~n~n", [Rec,args(GetName,",",Attr)])
 
1170
            w("-record(~s,{type, ~s}).~n~n", [Rec,args(GetName,",",Attr)])
1164
1171
    end,
1165
1172
    EvTypes.
1166
1173
 
1190
1197
    open_write("../src/gen/wxe_debug.hrl"),
1191
1198
    erl_copyright(),
1192
1199
    w("%% This file is generated DO NOT EDIT~n~n", []),
1193
 
    w("wxdebug_table() -> ~n[~n", []),
 
1200
    w("wxdebug_table() ->~n[~n", []),
1194
1201
    w(" {0, {wx, internal_batch_start, 0}},~n", []),
1195
1202
    w(" {1, {wx, internal_batch_end, 0}},~n", []),
1196
1203
    w(" {4, {wxObject, internal_destroy, 1}},~n", []),