Skip to content

Commit

Permalink
wx: Generate doc into src code (again)
Browse files Browse the repository at this point in the history
So wx can be patched in the future.
  • Loading branch information
dgud committed Aug 7, 2024
1 parent 3b234fb commit 48af6d0
Show file tree
Hide file tree
Showing 240 changed files with 13,424 additions and 32,394 deletions.
4 changes: 2 additions & 2 deletions lib/wx/api_gen/gen_util.erl
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ close() ->
copyright -> %% We ignore copyright changes only
ok = file:delete(File ++ ".temp");
_ ->
io:format("Diff in ~s~n~.1000s ~n", [File, string:trim(Diff)]),
io:format("Diff in ~s~n~.1000ts ~n", [File, string:trim(Diff)]),
case file:rename(File ++ ".temp", File) of
ok -> ok;
_ -> io:format("***** Failed to save file ~p ~n",[File])
Expand All @@ -90,7 +90,7 @@ close() ->

check_diff(Diff) ->
try
[_,D1,_,D2|Tail] = re:split(Diff, "\n"),
[_,D1,_,D2|Tail] = re:split(Diff, "\n", [unicode]),
case Tail of
[] -> ok;
[<<>>] -> ok;
Expand Down
113 changes: 63 additions & 50 deletions lib/wx/api_gen/wx_extra/wxEvtHandler.erl
Original file line number Diff line number Diff line change
@@ -1,25 +1,32 @@
%% This module is actually handwritten see ../api_gen/wx_extra/wxEvtHandler.erl
%%
%% @doc The Event handler.
%%
%% To get events from wxwidgets objects you subscribe to them by
%% calling connect/[2-3]. Events are sent as messages, if no callback
%% was supplied These messages will be {@link wx(). #wx{}} where
%% EventRecord is a record that depends on the {@link
%% wxEventType(). event type}. The records are defined in:
%% wx/include/wx.hrl.
%%
%% If a callback was supplied to connect, the callback will be invoked
%% (in another process) to handle the event. The callback should be of
%% arity 2. fun(EventRecord::wx(), EventObject::wxObject()).
%%
%% Beware that the callback will be executed in a new process each time.
%%
%% <a href="http://www.wxwidgets.org/manuals/stable/wx_wxevthandler.html">
%% The original documentation</a>.
%%
%%
-module(wxEvtHandler).
-moduledoc """
The Event handler
A class that can handle events from the windowing system. `m:wxWindow` is (and
therefore all window classes are) derived from this class.
To get events from wxwidgets objects you subscribe to them by calling `connect/3`.
If the `callback` option is not supplied events are sent as messages.
These messages will be `#wx{}` where `EventRecord` is a record that depends on
the `wxEventType`. The records are defined in: `wx/include/wx.hrl`.
If a callback was supplied to connect, the callback will be invoked (in another
process) to handle the event. The callback should be of arity 2.
`fun Callback (EventRecord::wx(), EventObject::wxObject()).`
Note: The callback will be in executed in new process each time.
See:
[Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events_processing)
wxWidgets docs:
[wxEvtHandler](https://docs.wxwidgets.org/3.2/classwx_evt_handler.html)
""".
-include("wxe.hrl").
-include("../include/wx.hrl").

Expand All @@ -32,30 +39,37 @@
-export_type([wxEvtHandler/0, wx/0, event/0]).
-type wxEvtHandler() :: wx:wx_object().

%% @doc Equivalent to {@link connect/3. connect(This, EventType, [])}
-doc(#{equiv => connect(This, EventType, [])}).
-spec connect(This::wxEvtHandler(), EventType::wxEventType()) -> 'ok'.
connect(This, EventType) ->
connect(This, EventType, []).

%% @doc This function subscribes the to events of EventType,
%% in the range id, lastId. The events will be received as messages
%% if no callback is supplied.
%%
%% Options:
%% {id, integer()}, The identifier (or first of the identifier range) to be
%% associated with this event handler.
%% Default ?wxID_ANY
%% {lastId, integer()}, The second part of the identifier range.
%% If used 'id' must be set as the starting identifier range.
%% Default ?wxID_ANY
%% {skip, boolean()}, If skip is true further event_handlers will be called.
%% This is not used if the 'callback' option is used.
%% Default false.
%% callback Use `wx_object' callback `handle_sync_event/3'.
%% {callback, function()} Use a callback fun(EventRecord::wx(), EventObject::wxObject())
%% to process the event. Default not specified i.e. a message will
%% be delivered to the process calling this function.
%% {userData, term()} An erlang term that will be sent with the event. Default: [].
-doc """
This function subscribes to events.
Subscribes to events of type `EventType`, in the range `id`, `lastId`.
The events will be received as messages if no callback is supplied.
Options
id:`{id, integer()} `The identifier (or first of the identifier range) to be
associated with this event handler. Default is ?wxID_ANY
lastid:`{lastId,integer()} `The second part of the identifier range. If used
'id' must be set as the starting identifier range. Default is ?wxID_ANY
skip:`{skip,boolean()} `If skip is true further event_handlers will be called.
This is not used if the 'callback' option is used. Default is `false`.
callback:`{callback,function()} `Use a
callback`fun(EventRecord::wx(),EventObject::wxObject()) `to process the event.
Default not specified i.e. a message will be delivered to the process calling
this function.
userData:`{userData,term()} `An erlang term that will be sent with the event.
Default: [].
""".
-spec connect(This::wxEvtHandler(), EventType::wxEventType(), [Option]) -> 'ok' when
Option :: {'id', integer()} | {'lastId', integer()} | {'skip', boolean()} |
'callback' | {'callback', function()} | {'userData', term()}.
Expand Down Expand Up @@ -97,24 +111,24 @@ parse_opts([], Opts = #evh{id=Id,lastId=Lid,skip=Skip, cb=CB}) ->
Opts
end.


%% @doc Equivalent to {@link disconnect/3. disconnect(This, null, [])}
%% Can also have an optional callback Fun() as an additional last argument.
-doc(#{equiv => disconnect(This, null, [])}).
-spec disconnect(This::wxEvtHandler()) -> boolean().
disconnect(This=#wx_ref{type=ThisT,ref=_ThisRef}) ->
?CLASS(ThisT,wxEvtHandler),
disconnect(This, null, []).

%% @doc Equivalent to {@link disconnect/3. disconnect(This, EventType, [])}
-doc(#{equiv => disconnect(This, EventType, [])}).
-spec disconnect(This::wxEvtHandler(), EventType::wxEventType()) -> boolean().
disconnect(This=#wx_ref{type=ThisT,ref=_ThisRef}, EventType) when is_atom(EventType) ->
?CLASS(ThisT,wxEvtHandler),
disconnect(This, EventType, []).

%% @doc See <a href="http://www.wxwidgets.org/manuals/stable/wx_wxevthandler.html#wxevthandlerdisconnect">external documentation</a>
%% This function unsubscribes the process or callback fun from the event handler.
%% EventType may be the atom 'null' to match any eventtype.
%% Notice that the options skip and userdata is not used to match the eventhandler.
-doc """
This function unsubscribes the process or callback fun from the event handler.
EventType may be the atom 'null' to match any eventtype. Notice that the options
skip and userdata is not used to match the eventhandler.
""".
-spec disconnect(This::wxEvtHandler(), EventType::wxEventType(), [Option]) -> boolean() when
Option :: {'id', integer()} | {'lastId', integer()} | {'callback', function()}.
disconnect(This=#wx_ref{type=ThisT,ref=_ThisRef}, EventType, Opts) ->
Expand All @@ -127,8 +141,7 @@ disconnect(This=#wx_ref{type=ThisT,ref=_ThisRef}, EventType, Opts) ->
Bool
end.


%% @hidden
-doc false.
connect_impl(#wx_ref{type=ThisT}=This,
#evh{id=Winid, lastId=LastId, et=EventType,
skip=Skip, userdata=UserData, cb=FunID})
Expand All @@ -137,7 +150,7 @@ connect_impl(#wx_ref{type=ThisT}=This,
FunID, EventType, ThisT, ?get_env(), 100),
wxe_util:rec(100).

%% @hidden
-doc false.
disconnect_impl(#wx_ref{type=_ThisT}=This,
#evh{id=Winid, lastId=LastId, et=EventType,
handler=#wx_ref{type=wxeEvtListener}=EvtList}) ->
Expand Down
12 changes: 11 additions & 1 deletion lib/wx/api_gen/wx_extra/wxPrintout.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,11 +20,21 @@
<<EXPORT:wxPrintout new/2,new/3 wxPrintout:EXPORT>>

<<wxPrintout
%% @doc @equiv new(Title, OnPrintPage, [])
-doc(#{equiv => new/3}).
-spec new(Title::string(), OnPrintPage::function()) -> wxPrintout:wxPrintout().
new(Title, OnPrintPage) ->
new(Title, OnPrintPage, []).

-doc """
Constructor.
Creates a `m:wxPrintout` object with a callback fun and optionally other
callback funs. The `This` argument is the `m:wxPrintout` object reference to
this object
Notice: The callbacks may not call other processes.
""".

-spec new(Title::string(), OnPrintPage, [Option]) ->
wxPrintout:wxPrintout() when
OnPrintPage :: fun((wxPrintout(), Page::integer()) -> boolean()),
Expand Down
4 changes: 2 additions & 2 deletions lib/wx/api_gen/wx_gen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ safe(What, QuitOnErr) ->
catch Err:Reason:Stacktrace ->
io:format("Error in ~p ~p~n", [get(current_class),get(current_func)]),
%%erlang:display({Err,Reason,Stacktrace}),
io:format("~p:~p:~n ~p~n~n",[Err,Reason,Stacktrace]),
io:format("~p:~P:~n ~p~n~n",[Err,Reason, 30, Stacktrace]),
catch gen_util:close(),
timer:sleep(1500),
QuitOnErr andalso gen_util:halt(1)
Expand All @@ -69,7 +69,7 @@ gen_code() ->
Defs = translate_enums(Defs2),
wx_gen_erl:gen(Defs),
wx_gen_nif:gen(Defs),
wx_gen_doc:gen(Defs),
%% wx_gen_doc:gen(Defs),
ok.

-record(hs,{alias,skip,fs,fopt,ev,acc,info}).
Expand Down
Loading

0 comments on commit 48af6d0

Please sign in to comment.