diff --git a/lib/wx/api_gen/gen_util.erl b/lib/wx/api_gen/gen_util.erl index da36992fb805..9848d64c8bec 100644 --- a/lib/wx/api_gen/gen_util.erl +++ b/lib/wx/api_gen/gen_util.erl @@ -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]) @@ -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; diff --git a/lib/wx/api_gen/wx_extra/wxEvtHandler.erl b/lib/wx/api_gen/wx_extra/wxEvtHandler.erl index 628e22aa9e14..9f6026c414c8 100644 --- a/lib/wx/api_gen/wx_extra/wxEvtHandler.erl +++ b/lib/wx/api_gen/wx_extra/wxEvtHandler.erl @@ -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. -%% -%% -%% The original documentation. -%% -%% -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"). @@ -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()}. @@ -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 external documentation -%% 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) -> @@ -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}) @@ -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}) -> diff --git a/lib/wx/api_gen/wx_extra/wxPrintout.erl b/lib/wx/api_gen/wx_extra/wxPrintout.erl index 5e65498fed77..de335dc72878 100644 --- a/lib/wx/api_gen/wx_extra/wxPrintout.erl +++ b/lib/wx/api_gen/wx_extra/wxPrintout.erl @@ -20,11 +20,21 @@ <> < 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()), diff --git a/lib/wx/api_gen/wx_gen.erl b/lib/wx/api_gen/wx_gen.erl index 477e09d31841..70005a5f3dde 100644 --- a/lib/wx/api_gen/wx_gen.erl +++ b/lib/wx/api_gen/wx_gen.erl @@ -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) @@ -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}). diff --git a/lib/wx/api_gen/wx_gen_doc.erl b/lib/wx/api_gen/wx_gen_doc.erl index eb22dccfada7..c56d45e22605 100644 --- a/lib/wx/api_gen/wx_gen_doc.erl +++ b/lib/wx/api_gen/wx_gen_doc.erl @@ -20,7 +20,7 @@ %% Api wrapper generator -module(wx_gen_doc). --export([gen/1]). +-export([module_doc/1]). -compile([export_all, nowarn_export_all]). @@ -44,95 +44,12 @@ _ -> ok end). -gen(Defs) -> - %% Fail = ["wxTopLevelWindow", "wxFrame"], - Fail = [], - Ev2ClassL = [{wx_gen_erl:event_type_name(Ev),Name} || - #class{name=Name, event=Evs} <- Defs, Evs =/= false, Ev <- Evs], - Ev2Class = maps:from_list(Ev2ClassL), - true = length(Ev2ClassL) =:= maps:size(Ev2Class), - put(ev2class, Ev2Class), - [gen_class(Class) || #class{parent=Parent, name=Name,options=Opts} = Class <- Defs, - not (Parent =:= "static"), - not lists:member("ignore", Opts), - Fail =:= [] orelse lists:member(Name, Fail)], - Static = [Class || #class{parent="static", options=Opts} = Class <- Defs, - not lists:member("ignore", Opts)], - gen_misc(Static), - ok. - -gen_class(Class) -> - try gen_class1(Class) - catch throw:skipped -> - Class; - error:Reason:ST -> - ?LOG("Error: ~P in~n ~P~n",[Reason, 20, ST, 20]) - end. - -gen_class1(#class{name=Name,parent=Parent,methods=Ms, event=Evs}) -> - put(current_class, Name), - Funcs = case gen_funcs(Ms) of - [] -> [nl(0)]; - Fs -> [nl(0), {funcs, Fs}, nl(0)] - end, - erase(current_func), - - Types = case Evs of - false when Name =:= "wxEvtHandler" -> - [nl(4), {datatype, [{name, [{name, Name}], []}]}, - nl(4), {datatype, [{name, [{name, "wxEventType"}], []}]}, - nl(4), {datatype, [{name, [{name, "wx"}], []}]}, - nl(4), {datatype, [{name, [{name, "event"}], []}]} - ]; - false -> - [{datatype, [{name, [{name, Name}], []}]}]; - [_|_] -> - [nl(4), {datatype, [{name, [{name, Name}], []}]}, - nl(4), {datatype, [{name, [{name, wx_gen_erl:event_rec_name(Name)}], []}]}, - nl(4), {datatype, [{name, [{name, Name++"Type"}], []}]}] - end, - ErlRef = {erlref, - [nl(0), {header, gen_header(Name)}, - nl(0), {module, [Name]}, - nl(0), {modulesummary, class_brief(Name)}, - nl(0) | class_description(Name, Parent, Evs)] - ++ [nl(0), {datatypes, Types}, - nl(0) | Funcs] - }, - open_write("../doc/src/"++Name++".xml"), - Intro = "\n" - "\n" - "\n\n\n", - Root = [#xmlAttribute{name=prolog, value=Intro}], - Export = xmerl:export_simple([nl(0), ErlRef],xmerl_xml, Root), - w("~s~n",[unicode:characters_to_binary(Export)]), - close(), - erase(current_class), - ok. - -gen_misc(Files) -> - Ms = lists:append([Ms || #class{methods=Ms} <- Files]), - Name = "wx_misc", - put(current_class, Name), - Funcs = gen_funcs(Ms), - erase(current_func), - open_write("../doc/src/wx_misc.xml"), - Intro = "\n" - "\n" - "\n\n\n", - Root = [#xmlAttribute{name=prolog, value=Intro}], - ErlRef = {erlref, - [nl(0),{header, gen_header(Name)}, - nl(0),{module, [Name]}, - nl(0),{modulesummary, ["Miscellaneous functions."]}, - nl(0),{description, [{p,["Miscellaneous functions."]}]}, - nl(0),{funcs, Funcs}, - nl(0) - ]}, - Export = xmerl:export_simple([nl(0), ErlRef],xmerl_xml, Root), - w("~s~n",[unicode:characters_to_binary(Export)]), - close(), - erase(current_class), +module_doc(#class{name=Name,parent=Parent,event=Evs}) -> + w(~s'-moduledoc """\n', []), + %% io:format("~w: Gen ~p~n", [?LINE, Name]), + class_brief(Name), + class_description(Name, Parent, Evs), + w(~s'""".\n', []), ok. gen_header(Name) -> @@ -148,41 +65,73 @@ gen_header(Name) -> class_brief(Name) -> [{_,Doc}] = ets:lookup(docs, Name), - case fsummary(Doc) of - [] -> ["Functions for " ++ Name ++ " class"]; - Docs -> [to_text(Docs)] + Brief = case fsummary(Doc) of + [] -> ["Functions for " ++ Name ++ " class"]; + Docs -> [to_text(Docs)] + end, + try w("~s\n\n", [unicode:characters_to_binary(Brief)]) + catch Type:Err:ST -> + io:format("Error ~p~n ~p~n ~p~n", [Err, Brief, fsummary(Doc)]), + erlang:raise(Type,Err,ST) end. class_description(Name, Parent, Evs) -> [{_,Doc}] = ets:lookup(docs, Name), D0 = doc(detailed, Doc), - %% ?DBGCF("wxStyledTextEvent", undefined, "~tp~n",[p(D0)]), D1 = flatten_p(D0), - %% ?DBGCF("wxStyledTextEvent", undefined, "~tp~n",[p(D1)]), D2 = remove_doxy_link(D1), {Events, D3} = make_events(D2, Evs), - %% ?DBGCF("wxBrush", undefined, "~tp~n",[p(D2)]), + %% ?DBGCF("wxCheckBox", undefined, "~p~n", [p(D2)]), Docs = translate(D3), - Parents = wx_gen_erl:parents(Parent), - MRef = fun(M) -> #xmlElement{name=seeerl, attributes=[{marker,M}], - content=[{c, [#xmlText{value=M}]}]} - end, + MRef = fun(M) -> {url, "`m:" ++ M ++ "`", none} end, PRef = case [MRef(P) || P <- Parents, P =/= root, P =/= object] of [] -> []; Ps -> - Derived = {p, ["This class is derived (and can use functions) from: ", - nl(4) | lists:join(" ", Ps)] }, - [nl(2),Derived, nl(2)] + Derived = {p, "This class is derived, and can use functions, from: "}, + Items = [{list_item, [P]} || P <- Ps], + [Derived, {list, Items}] end, - Url = "https://docs.wxwidgets.org/3.1/class" ++ + Url = "https://docs.wxwidgets.org/3.2/class" ++ camelcase_to_underscore(Name) ++ ".html", - WxRef = {p, ["wxWidgets docs: ", {url, [{href, Url}], [Name]}]}, - [{description, Docs ++ PRef ++ [nl(2),WxRef,nl(2)]}|Events]. + WxRef = {p, [{text, "wxWidgets docs: "}, {url, Url, Name}]}, + try + Everything = Docs ++ PRef ++ [WxRef|Events], + Desc = to_text(Everything), + %% ?DBGCF("wxListView", undefined, "~p~n", [Docs]), + w("~s\n", [unicode:characters_to_binary(Desc)]), + ok + catch Type:Err:ST -> + io:format("Error ~p~n ~p~n ~p~n", [Err, Name, fsummary(Doc)]), + erlang:raise(Type,Err,ST) + end. -gen_funcs(Ms) -> - lists:foldl(fun(M, Acc) -> gen_func(M, Acc) end, [], Ms). +func(Ms) -> + try + Xml = gen_func(Ms, []), + case Xml of + [] -> + ignore; + _ -> + %% ?DBGCF("wxAuiManager", "InsertPane", "~p~n", [Xml]), + FuncDoc = to_text(Xml), + NoQuotes = string:find(FuncDoc, "\"") == nomatch, + case is_single_line(FuncDoc) andalso NoQuotes of + true -> + w(~s'-doc "~s".\n', [unicode:characters_to_binary(FuncDoc)]); + false -> + w(~s'-doc """\n', []), + FuncDoc = to_text(Xml), + w("~s", [unicode:characters_to_binary(FuncDoc)]), + w(~s'\n""".\n', []) + end, + ok + end + catch Err:Reason:St -> + io:format("Err ~p: ~P~n ~P~n",[Err, Reason, 20, St, 30]), + exit(gen_doc) + end. gen_func(Ms, Acc0) -> Last = length(Ms), @@ -190,77 +139,77 @@ gen_func(Ms, Acc0) -> fun(M, {N,Acc}) -> {N+1, [gen_func_1(M,N =/= Last,N)|Acc]} end, {1,[]}, Ms), - [nl(2), {func, lists:append(lists:reverse(Fs))}, nl(2) | Acc0]. + [lists:append(lists:reverse(Fs)) | Acc0]. gen_func_1(#method{name=N,alias=A,params=Ps,where=erl_no_opt,method_type=MT}, SkipDesc, Clause) -> put(current_func, N), Name = erl_func_name(N,A,MT), As = wx_gen_erl:erl_args_count(Ps, erl_no_opt), Impl = io_lib:format("~s/~w",[Name,As+1]), + %% ?DBGCF("wxBitmap", "Create", "~p~n", [Ps]), Desc = case SkipDesc of - true -> [nl(2)]; - false -> [nl(4),{fsummary, ["See: ", {c, [Impl]}]}, nl(2)] + true -> []; + false -> [{text, "Equivalent to: "}, {c, [Impl]}] end, - [nl(4),{name, xml_func_name(Name,As,Clause), []}|Desc]; + Desc; gen_func_1(#method{name=N,alias=A,params=Ps,where=erl_alias,method_type=MT}, SkipDesc, Clause) -> put(current_func, N), - Name = erl_func_name(N,A,MT), As = wx_gen_erl:erl_args_count(Ps, erl_alias), Impl = io_lib:format("~s/~w",[wx_gen_erl:erl_func_name(N,undefined),As]), + %% ?DBGCF("wxBitmap", "Create", "~p~n", [Ps]), Desc = case SkipDesc of - true -> [nl(2)]; - false -> - [nl(4),{fsummary, ["See: ", {c, [Impl]}]}, - nl(4),{desc, [{p, ["See: ", {seemfa, [{marker, [$#|Impl]}], [{c, [Impl]}]},"."]}, nl(4)]}, - nl(2)] + true -> []; + false -> [{text, "Equivalent to: "}, {c, [Impl]}] end, - [nl(4),{name, xml_func_name(Name,As,Clause), []}|Desc]; + Desc; gen_func_1(#method{name=N,id=Id,alias=A,params=Ps,method_type=MT}, SkipDesc, Clause) -> put(current_func, N), Name = erl_func_name(N,A,MT), As = wx_gen_erl:erl_args_count(Ps, erl_alias), - Desc = case (not SkipDesc) andalso ets:lookup(docs, Id) of + Docs = case (not SkipDesc) andalso ets:lookup(docs, Id) of false -> - [nl(2)]; + %% ?DBGCF("wxBitmap", "Create", "~p~n", [Ps]), + []; [] when Name =:= "destroy" -> [ - nl(4),{fsummary, ["Destructor"]}, - nl(4),{desc, [{p, ["Destroys the object."]}]}, - nl(2)]; + [{text, "Destroys the object."}] + ]; [] -> ?LOG(" /~w (~p ~p) is missing docs~n",[As, SkipDesc, Clause]), - [nl(4),{fsummary, [""]}, {desc, [""]}, - nl(2)]; + []; [{_,Doc}] -> - [nl(4),{fsummary, fsummary(Doc)}, - nl(4),{desc, desc(Doc)}, - nl(2)] + case {fsummary(Doc), desc(Doc)} of + {[], Desc} -> + Desc; + {Desc, []} -> + Desc; + {Sum, Desc} -> + [Sum, nl(0), Desc] + end end, - [nl(4),{name, xml_func_name(Name,As,Clause), []}|Desc]. + Docs. %% Remove paragraph -fsummary(Doc) -> - case flatten_p(doc(brief, Doc)) of +fsummary(Docs) -> + Doc = doc(brief, Docs), + case flatten_p(Doc) of [] -> %% Det = doc(detailed, Doc); []; - [#xmlElement{name=para, content=Cs}|_] -> - %% ?DBGCF("wxXmlResource", "ClearHandlers", "~p~n",[p(Cs)]), - Res = fsummary_1(Cs), - try xmerl:export_simple_content(Res, xmerl_xml) - catch _:Reason:ST -> - ?LOG("ERROR: ~p~n~p ~p~n ~p~n",[p(Cs), Reason, Res, ST]) - end, - Res + Head -> + %% ?DBGCF("wxBitmap", "wxBitmap", "'~p'~n",[Doc]), + %% ?DBGCF("wxHtmlWindow", "GetOpenedPageTitle", "~p~n", [Docs]), + [{p, [{text_nocut, to_text(translate(fsummary_1(Head)))}]}] end. desc(Doc) -> - Docs = doc(brief, Doc) ++ doc(detailed, Doc), + Docs = doc(detailed, Doc), %% ?DBGCF("wx_misc", "wxNewId", "~100p~n", [p(Docs)]), Flat = flatten_p(Docs), + %% ?DBGCF("wxArtProvider", "GetBitmap", "~100p~n", [p(Flat)]), Clean = remove_doxy_link(Flat), - %% ?DBGCF("wxSlider", "SetThumbLength", "~100p~n", [p(Flat)]), Res = translate(Clean), + %% ?DBGCF("wxArtProvider", "GetBitmap", "~100p~n", [p(Res)]), Res. %%%%%%%%%%%%%% @@ -269,6 +218,7 @@ make_events(D1, Evs) -> make_events(D1, Evs, []). make_events([#xmlElement{name=heading}=E|Es], Evs, Acc) -> + %% ?DBGCF("wxTopLevelWindow", undefined, "~100p~n", [p(E)]), case is_event_heading(E) of false -> make_events(Es, Evs, [E|Acc]); @@ -277,6 +227,7 @@ make_events([#xmlElement{name=heading}=E|Es], Evs, Acc) -> {Events, lists:reverse(Acc, Rest)} end; make_events([#xmlElement{name=sect1, content=[Title|Cs]}=E|Es], Evs, Acc) -> + %% ?DBGCF("wxTopLevelWindow", undefined, "~100p~n", [p(Title)]), case is_event_heading(Title) of false -> make_events(Es, Evs, [E|Acc]); @@ -295,33 +246,33 @@ is_event_heading(#xmlElement{name=Name, content=Cs}) %% "Default event" ++ _ -> true; "Events" ++ _ -> true; _ -> false - end. - + end; +is_event_heading(_) -> + false. make_events_sect(Cs, false) -> + %% ?DBGCF("wxTopLevelWindow", undefined, "~tp~n",[p(Cs)]), {Evs, Rest} = get_event_list(Cs), - Refs = [Ev || Item <- Evs, Ev <- get_event_class(Item), Ev =/= ignore], - %% ?DBGCF("wxSlider", undefined, "~100p~n",[Refs]), - EventRefs = lists:join(", ", Refs), - case EventRefs of + Refs = [{list_item, [Ev]} || Item <- Evs, Ev <- get_event_class(Item), Ev =/= ignore], + case Refs of [] -> {[], Rest}; _ -> - EventDoc = [{p, ["Event types emitted from this class: "|EventRefs]}], - {[{section, [{title, ["Events"]}|EventDoc]}], Rest} + EventDoc = [{p, ["Event types emitted from this class: "]}| + [{list, Refs}]], + {[{title, ["Events"]}|EventDoc], Rest} end; make_events_sect(Cs, [_|_]) -> - %% ?DBGCF("wxStyledTextEvent", undefined, "~tp~n",[p(Cs)]), {_Refs, Rest} = get_event_list(Cs), EvtMarker = "wxEvtHandler#connect/3", EvtFunc = "wxEvtHandler:connect/3", EvtHRef = #xmlElement{name=seemfa, attributes=[{marker,EvtMarker}], - content=[{c, [#xmlText{value=EvtFunc}]}]}, + content=[{c, [{text, EvtFunc}]}]}, EvType = get(current_class) ++ "Type", TypeRef = #xmlElement{name=seetype, attributes=[{marker,"#" ++ EvType}], - content=[{c, [#xmlText{value=EvType}]}]}, + content=[{c, [{text, EvType}]}]}, EventDoc = [{p, ["Use ", EvtHRef, " with ", TypeRef, " to subscribe to events of this type."]}], - EventSect = [{section, [{title, ["Events"]}|EventDoc]}], + EventSect = [{title, ["Events"]}|EventDoc], case get(current_class) of "wxStyledTextEvent" -> %% Broken xml {EventSect, []}; @@ -329,14 +280,23 @@ make_events_sect(Cs, [_|_]) -> {EventSect, Rest} end. -get_event_list(Cs) -> - [EvL|R] = lists:dropwhile(fun(#xmlElement{name=itemizedlist}) -> false; (_) -> true end, Cs), - #xmlElement{name=itemizedlist, content=Evs} = EvL, - {Evs, R}. +get_event_list([#xmlElement{name=para, content=Cs}|Rest]) -> + case get_event_list(Cs) of + false -> + get_event_list(Rest); + {Res,Cont} -> + {Res, Cont ++ Rest} + end; +get_event_list([#xmlElement{name=itemizedlist, content=Evs}|R]) -> + {Evs,R}; +get_event_list([_|R]) -> + get_event_list(R); +get_event_list([]) -> + false. get_event_class(#xmlText{}) -> []; get_event_class(#xmlElement{name=listitem, content=[#xmlElement{name=para, content=Cs}]}) -> - [#xmlText{value="EVT_" ++ EventMacro}|_] = Cs, + [#xmlText{value = "EVT_" ++ EventMacro}|_] = Cs, [WxName|_R] = string:split(EventMacro, "("), Map = get(ev2class), EvType0 = string:lowercase(WxName), @@ -355,18 +315,23 @@ get_event_class(#xmlElement{name=listitem, content=[#xmlElement{name=para, conte [ignore] end; Class -> - [#xmlElement{name=seeerl, attributes=[{marker,Class}], content=[{c, [EvType]}]}] + %% [#xmlElement{name=seeerl, attributes=[{marker,Class}], content=[{c, [EvType]}]}] + [{url, "`m:"++Class ++ "`", "`" ++ EvType ++ "`"}] end; Class -> - [#xmlElement{name=seeerl, attributes=[{marker,Class}], content=[{c, [EvType0]}]}] - end. + %% [#xmlElement{name=seeerl, attributes=[{marker,Class}], content=[{c, [EvType0]}]}] + [{url, "`m:"++Class ++ "`", "`" ++ EvType0 ++ "`"}] + end; +get_event_class(#xmlElement{name=Name, content=Cs}) -> + io:format("~w: ~P~n",[Name, p(Cs), 20]). + make_event_refs(Class) -> #class{event=Evs} = get({class, Class}), Fun = fun(Ev) -> EvType = wx_gen_erl:event_type_name(Ev), - #xmlElement{name=seeerl, attributes=[{marker,Class}], - content=[{c, [EvType]}]} + %% #xmlElement{name=seeerl, attributes=[{marker,Class}],content=[{c, [EvType]}]} + [{url, "`m:"++Class ++ "`", "`" ++ EvType ++ "`"}] end, [Fun(Ev) || Ev <- Evs]. @@ -488,7 +453,7 @@ xml_func_name(Name, As, Clause) -> nl(Indent) -> NL = [$\n, lists:duplicate(Indent, $\s)], - #xmlText{value=NL}. + {text, NL}. doc(_, undefined) -> []; @@ -514,29 +479,69 @@ translate([Doc|Docs], Acc) -> translate([], Acc) -> lists:reverse(Acc). -t(#xmlText{}=Txt) -> - Txt; +t(#xmlText{value = Txt} = Xml) -> + case is_include([Xml]) of + true -> ignore; + false -> {text, Txt} + end; t(#xmlElement{name=para, content=Cs}) -> Docs = translate(Cs), case is_empty(Docs) orelse is_include(Cs) of true -> ignore; - false -> #xmlElement{name=p, content=Docs ++ [nl(6)]} + false -> {p, Docs} end; t(#xmlElement{name=simplesect, attributes=As, content=Cs}) -> Split = case As of + [#xmlAttribute{value="example"}] -> + {ignore, ignore, []}; [#xmlAttribute{value="see"}] -> - {"See: ", see_sect(Cs)}; + case see_sect(Cs) of + [One] -> + {combine, "See: ", One}; + List -> + {list, {text, "See: \n"}, List} + end; + [#xmlAttribute{value="deprecated"}] -> + [{p, Doc}] = translate(Cs), + {combine, "Deprecated: ", Doc}; + [#xmlAttribute{value="return"}] -> + [{p, Doc}] = translate(Cs), + {combine, "Return: ", Doc}; + [#xmlAttribute{value="remark"}] -> + case translate(Cs) of + [] -> + {ignore, ignore, []}; + [{p, Doc}] -> + {combine, "Remark: ", Doc} + end; + [#xmlAttribute{value="note"}] -> + [{p, Doc}] = translate(Cs), + {combine, "Note: ", Doc}; + [#xmlAttribute{value="since"}] -> + [{p, Doc}] = translate(Cs), + {combine, "Since: ", Doc}; [#xmlAttribute{value=V}] -> - {string:titlecase(V) ++ ": ", translate(Cs)} + %% ?DBGCF("wxBitmap", "SetHeight", "~p~n", [V]), + {other, {p, string:titlecase(V) ++ ": "}, translate(Cs)} end, case Split of - {_, []} -> ignore; - {Intro, Docs} -> - #xmlElement{name=p, content=[Intro|Docs ++ [nl(6)]]} + {_, _, []} -> ignore; + {list, Intro, Refs} -> + Items = [{list_item, Ref} || Ref <- Refs], + [Intro, {list, Items}]; + {other, Intro, Text} -> + [Intro|Text]; + {combine, Intro, Text} -> + [{p, [Intro|Text]}] end; t(#xmlElement{name=sect1, content=[#xmlElement{name=title, content=Title}|Desc]}) -> - [{p, [get_text(Title)]} | translate(Desc)]; + case {get(current_class), get_text(Title)} of + {"wxStyledTextCtrl", "Index of" ++ _} -> + ignore; + _ -> + [{p, [get_text(Title)]} | translate(Desc)] + end; t(#xmlElement{name=xrefsect, content=[#xmlElement{name=xreftitle, content=Title}, @@ -544,7 +549,7 @@ t(#xmlElement{name=xrefsect, Intro = case get_text(Title) of [] -> []; "Todo" -> skip; - T -> [#xmlText{value=T ++ ": "}] + T -> [{text, T ++ ": "}] end, case Intro of skip -> ignore; @@ -552,14 +557,14 @@ t(#xmlElement{name=xrefsect, Docs = translate(Intro ++ Desc), case is_empty(Docs) of true -> ignore; - false -> Docs ++ [nl(6)] + false -> Docs end end; t(#xmlElement{name=ref}=Ref) -> see(Ref); t(#xmlElement{name=ulink, attributes=[#xmlAttribute{value=Url}], content=Cs}) -> - {url, [{href, Url}], Cs}; + {url, Url, get_text(Cs)}; t(#xmlElement{name=onlyfor, content=Cs}) -> {p, ["Only for:" | translate(Cs)]}; t(#xmlElement{name=C, content=Txt}) @@ -575,14 +580,15 @@ t(#xmlElement{name=C, content=Txt}) %% Fixme (lists and tables) t(#xmlElement{name=parameterlist, content=_C}) -> ignore; -t(#xmlElement{name=itemizedlist, content=_C}) -> - ignore; +t(#xmlElement{name=itemizedlist, content=C}) -> + {p, [{list, translate(C)}]}; t(#xmlElement{name=orderedlist, content=_C}) -> + %% {list, translate(C)}; ignore; t(#xmlElement{name=table, content=_C}) -> ignore; -t(#xmlElement{name=listitem, content=_C}) -> - ignore; +t(#xmlElement{name=listitem, content=C}) -> + {list_item, translate(C)}; t(#xmlElement{name=entry, content=_C}) -> ignore; @@ -592,14 +598,14 @@ t(#xmlElement{name=hruler}) -> ignore; t(#xmlElement{name=ndash, content=[]}) -> - #xmlText{value="-"}; + {text, "-"}; t(#xmlElement{name=mdash, content=[]}) -> - #xmlText{value="-"}; + {text, "-"}; t(#xmlElement{name=heading, content=Cs}) -> case Cs == [] orelse "" == get_text(Cs) of true -> ignore; - false -> {p, Cs} + false -> {title, translate(Cs)} end; t(#xmlElement{name=nonbreakablespace}) -> ignore; @@ -611,9 +617,15 @@ t(#xmlElement{name=native}) -> ignore; t(#xmlElement{name=anchor, content=[]}) -> ignore; +t(#xmlElement{name=htmlonly}) -> + ignore; t(#xmlElement{name=What, content=Cs}) -> ?LOG("xml unhand: ~p~n ~P~n", [What,p(Cs),15]), - ignore. + ignore; +t({url, _, _} = AlreadyTranslated) -> + AlreadyTranslated; +t({_, _} = AlreadyTranslated) -> + AlreadyTranslated. see(#xmlElement{name=ref, attributes=As, content=Cs}) -> #xmlAttribute{value=RefType} = lists:keyfind(kindref, #xmlAttribute.name, As), @@ -628,20 +640,20 @@ see("member", As, Cs) -> M -> {"#" ++ F ++ "/" ++ A, F ++ "/" ++ A}; _ -> {M ++ "#" ++ F ++ "/" ++ A, M ++ ":" ++ F ++ "/" ++ A} end, - #xmlElement{name=seemfa, attributes=[{marker,Marker}], content=[{c, [#xmlText{value=Func}]}]}; + #xmlElement{name=seemfa, attributes=[{marker,Marker}], content=[{c, [{text, Func}]}]}; enum -> - EnumP = get_text(Cs), - #xmlText{value=[$?|EnumP]}; + EnumP = markdown_qoute(get_text(Cs)), + [{text, [$?|EnumP]}]; not_found -> Func = get_text(Cs), - [{c, [Func]}, " (not implemented in wx)"] + [{c, [Func]}, {text, " (not implemented in wx)"}] end; see("compound", As, _Cs) -> #xmlAttribute{value=RefId} = lists:keyfind(refid, #xmlAttribute.name, As), case RefId of - "classwxPoint" -> ["{X,Y}"]; - "classwxRect" -> ["{X,Y,W,H}"]; - "classwxSize" -> ["{Width,Height}"]; + "classwxPoint" -> [{text, "{X,Y}"}]; + "classwxRect" -> [{text, "{X,Y,W,H}"}]; + "classwxSize" -> [{text, "{Width,Height}"}]; "classwxColor" -> #xmlElement{name=seetype, attributes=[{marker,"wx#wx_colour"}], content=[{c, ["wx_color()"]}]}; "classwxColour" -> @@ -655,10 +667,10 @@ see("compound", As, _Cs) -> "class" ++ Class -> case get({class, Class}) of undefined -> - [{c, [Class]}, " (not implemented in wx)"]; + [{c, [Class]}, {text, " (not implemented in wx)"}]; _ -> %% AppModule = Class, - #xmlElement{name=seeerl, attributes=[{marker,Class}], content=[{c, [Class]}]} + {url, "`m:" ++ Class ++ "`", none} end; "group__group" ++ _ -> ignore; @@ -667,69 +679,234 @@ see("compound", As, _Cs) -> ignore end. +see_sect([#xmlElement{content=Cs}]) -> + see_sect2(Cs, []); see_sect(Refs) -> - List = see_sect2(Refs, []), - WithComma = lists:join([", "], List), - %% ?LOG("~p~n",[WithComma]), - lists:append(WithComma). + Res = see_sect2(Refs, []), + Res. see_sect2([#xmlText{value=Txt}|Rest], Acc0) -> + %% ?DBGCF("wxArtProvider", undefined, "~p~n", [Txt]), MakeRef = fun(TextRef, Acc) -> Stripped = string:trim(TextRef, both, " ."), Split = string:split(Stripped, "_", all), - see_sect3(Split, Stripped, Acc) + case see_sect3(Split, Stripped) of + ignore -> Acc; + no_ref -> Acc; + Ref -> [Ref|Acc] + end end, Acc = lists:foldl(MakeRef, Acc0, string:lexemes(Txt, ",")), see_sect2(Rest, Acc); see_sect2([Ref|Rest], Acc) -> + %% ?DBGCF("wxArtProvider", undefined, "~p~n", [t(Ref)]), case t(Ref) of ignore -> see_sect2(Rest, Acc); + [{c,_}, {text, " (not implemented" ++ _}] -> see_sect2(Rest, Acc); Res when is_list(Res) -> see_sect2(Rest, [Res|Acc]); Res -> see_sect2(Rest, [[Res]|Acc]) end; see_sect2([], Acc) -> lists:reverse(Acc). -see_sect3(_, "", Acc) -> Acc; -see_sect3(["overview", Part], Stripped, Acc) -> - [see_sect4("Overview " ++ Part, "overview_" ++ Part, Stripped)|Acc]; -see_sect3(["overview", Part, _], Stripped, Acc) -> - [see_sect4("Overview " ++ Part, "overview_" ++ Part, Stripped)|Acc]; -see_sect3(["page", "samples" ++ _, _], Stripped, Acc) -> - [see_sect4("Examples", "page_samples", Stripped)|Acc]; -see_sect3(_Pre, Text, Acc) -> - %% ?LOG("~p ~p~n", [_Pre, Text]), - [[Text]|Acc]. - -see_sect4(Name, Pre, Stripped) -> - Url0 = "https://docs.wxwidgets.org/3.1/", +see_sect3(_, "") -> ignore; +see_sect3(["overview", Part], Stripped) -> + see_sect4("Overview " ++ Part, "overview_" ++ Part, Stripped); +see_sect3(["overview", Part, _], Stripped) -> + see_sect4("Overview " ++ Part, "overview_" ++ Part, Stripped); +see_sect3(["page", "samples" ++ _, _], Stripped) -> + see_sect4("Examples", "page_samples", Stripped); +see_sect3(_Pre, _Text) -> + no_ref. + +see_sect4(Name, Pre, Stripped0) -> + [Stripped| _] = string:split(Stripped0, " "), + Url0 = "https://docs.wxwidgets.org/3.2/", Url = Url0 ++ Pre ++ ".html#" ++ Stripped, - [{url, [{href, Url}], [Name]}]. + [{url, Url, Name}]. get_text([#xmlText{value=Val}]) -> Val; -get_text(_) -> - not_single_text. %% return atom so we crash if is not expected that the string is empty - -to_text([#xmlText{value=Val}|Rest]) -> - Val ++ to_text(Rest); -to_text([{c,Txt}|Rest]) -> - Txt ++ to_text(Rest); -to_text([C|Rest]) when is_integer(C) -> - [C|to_text(Rest)]; -to_text([L|Rest]) when is_list(L) -> - to_text(L) ++ to_text(Rest); -to_text([]) -> +get_text(_Debug) -> + {_, ST} = process_info(self(), current_stacktrace), + {not_single_text, ST, _Debug}. %% return atom so we crash + +to_text(Txt) -> + %% ?DBGCF("wxWindow", undefined, "~p~n", [p(Txt)]), + tighten_whitespace(to_text(Txt, 0)). + +to_text([{text, Txt1}, {text, Txt2}|Rest], Sz0) -> + to_text([{text, Txt1 ++ Txt2}|Rest], Sz0); +to_text([{text, Txt}|Rest], Sz0) -> + {Val, Sz} = split_line(Txt, Sz0), + [Val|to_text(Rest, Sz)]; +to_text([{text_nocut, Txt}|Rest], Sz0) -> + [Txt|to_text(Rest, string:length(Txt) + Sz0)]; + +to_text([#xmlElement{name=p, content=Val}|Rest], _) -> + case Rest of + [] -> + ["\n\n", to_text(Val, 0)]; + _ -> + ["\n\n", to_text(Val, 0),"\n\n" | to_text(Rest, 0)] + end; +to_text([{p,Val}|Rest], _) -> + case Rest of + [] -> + ["\n\n", to_text(Val, 0)]; + _ -> + ["\n\n", to_text(Val, 0),"\n\n" | to_text(Rest, 0)] + end; +to_text([#xmlElement{name=c, content=Val}|Rest], Sz) -> + Part1 = ["`", to_text(Val, 0), "`"], + [Part1 | to_text(Rest, string:length(Part1) + Sz)]; +to_text([{c,Val}|Rest], Sz) -> + Part1 = case Val of + [{c, _}|_] -> %% c in c don't double qoute + to_text(Val, 0); + _ -> + ["`", to_text(Val, 0), "`"] + end, + [Part1 | to_text(Rest, string:length(Part1) + Sz)]; +to_text([#xmlElement{name=seemfa, content=Val}|Rest], Sz) -> + [to_text(Val, 0) | to_text(Rest, Sz)]; +to_text([#xmlElement{name=seetype, content=Val}|Rest], Sz) -> + [to_text(Val, 0) | to_text(Rest, Sz)]; +to_text([{url, Url, none}|Rest], Sz) -> + UrlString = [Url], + [ UrlString | to_text(Rest, Sz + string:length(UrlString))]; +to_text([{url, Url, String}|Rest], Sz) -> + UrlString = ["[", String, "](", Url, ")"], + [ UrlString | to_text(Rest, Sz + string:length(UrlString))]; +to_text([{title, Title}|Rest], _) -> + [ "\n\n## ", to_text(Title,0), "\n\n"| to_text(Rest,0)]; +to_text([{list, List}|Rest], _Sz) -> + ListString = [["* ", list_item(Item), "\n\n"] || {list_item, Item} <- List], + [ ListString | to_text(Rest, 0)]; +to_text([$\s], _Sz) -> + []; +to_text([C|Rest], Sz) when is_integer(C) -> + [C|to_text(Rest, Sz+1)]; +to_text([L|Rest], Sz) when is_list(L) -> + to_text(L ++ Rest, Sz); +to_text([], _Sz) -> []. + +tighten_whitespace(String) -> + case string:next_codepoint(String) of + [$\n|Rest] -> + tighten_whitespace(Rest); + [$\s|Rest] -> + tighten_whitespace(Rest); + [Char|Rest] -> + [Char|t_wsp_char(Rest)]; + [] -> + [] + end. + +t_wsp_char(String) -> + case string:next_codepoint(String) of + [$\n|Rest] -> + t_wsp_nl(Rest); + [$\s|Rest] -> + t_wsp_space(Rest); + [Char|Rest] -> + [Char|t_wsp_char(Rest)]; + [] -> + [] + end. + +t_wsp_nl(String) -> + case string:next_codepoint(String) of + [$\n|Rest] -> + t_wsp_para(Rest); + [$\s|Rest] -> + t_wsp_nl(Rest); + [Char|Rest] -> + ["\n", Char|t_wsp_char(Rest)]; + [] -> + [] + end. + +t_wsp_para(String) -> + case string:next_codepoint(String) of + [$\n|Rest] -> + t_wsp_para(Rest); + [$\s|Rest] -> + t_wsp_para(Rest); + [Char|Rest] -> + ["\n\n", Char|t_wsp_char(Rest)]; + [] -> + [] + end. + +t_wsp_space(String) -> + case string:next_codepoint(String) of + [$\n|Rest] -> + t_wsp_nl(Rest); + [$\s|Rest] -> + t_wsp_space(Rest); + [Char|Rest] -> + [$\s, Char|t_wsp_char(Rest)]; + [] -> + [] + end. + +add_space([]) -> + []; +add_space(Words) -> + case string:next_codepoint(Words) of + [$\n|_] -> Words; + _ -> [$\s|Words] + end. + +split_line(Str, BefSz) -> + %% ?DBGCF("wxAcceleratorEntry", undefined, "~w ~p~n", [BefSz, Str]), + Split = string:split(Str, " ", all), + %% ?DBGCF("wxAcceleratorEntry", undefined, "~p~n", [Split]), + split_line_1(Split, BefSz). + +split_line_1([[Char]|Rest], Len) when Char =:= $,; Char =:= $.; Char =:= $:; Char =:= $) -> + {Cont, Sz} = split_line_1(Rest, Len+2), + {[Char|add_space(Cont)], Sz}; +split_line_1([[Char]|Rest], Len) when Char =:= $; ; Char =:= $( -> + {Cont, Sz} = split_line_1(Rest, Len+1), + {[Char|Cont], Sz}; +split_line_1([[Char, Char2]|Rest], Len) when Char =:= $; ; Char =:= $) -> + {Cont, Sz} = split_line_1(Rest, Len+1), + {[Char, Char2, $\s|Cont], Sz}; +split_line_1([Word|Rest], Len) -> + WordSz = string:length(Word), + NewLen = WordSz + Len + 1, + if Rest == [] -> + {[Word], Len}; + NewLen > 90 -> + {Cont, Sz} = split_line_1(Rest, WordSz), + {["\n",Word | add_space(Cont)], Sz}; + true -> + {Cont, Sz} = split_line_1(Rest, NewLen), + {[Word | add_space(Cont)], Sz} + end; +split_line_1([], Sz) -> + {[], Sz}. + +list_item([{p, Text}]) -> + to_text(Text); +list_item(Text) -> + to_text(Text). + is_text([#xmlText{}|R]) -> is_text(R); +is_text([{text, _}|R]) -> + is_text(R); is_text([C|R]) when is_integer(C) -> is_text(R); is_text([]) -> true; is_text(_) -> false. is_text_element(#xmlText{}) -> true; +is_text_element({text, _}) -> true; is_text_element(#xmlElement{name=E}) when E =:= ndash; E =:= emphasis; E =:= bold; E =:= computeroutput; E =:= nonbreakablespace; @@ -738,16 +915,25 @@ is_text_element(#xmlElement{name=E}) when is_text_element(_) -> false. +is_single_line(Text) -> + case string:find(Text, "\n") of + nomatch -> true; + _ -> false + end. + %%%%%%%%%%%%%%%% +fsummary_1([#xmlElement{name=para, content=Cs}|_Fs]) -> + fsummary_1(Cs); fsummary_1([#xmlText{value=Val}|Fs]) -> - [Val|fsummary_1(Fs)]; + [{text, markdown_qoute(Val)}|fsummary_1(Fs)]; +fsummary_1([{text, Val}|Fs]) -> + [{text, Val}|fsummary_1(Fs)]; fsummary_1([#xmlElement{name=E, content=Cs}|Fs]) when E =:= emphasis; E =:= bold; E=:= computeroutput -> - [{c, Cs}|fsummary_1(Fs)]; + [{c, fsummary_1(Cs)}|fsummary_1(Fs)]; fsummary_1([#xmlElement{name=ndash, content=[]}|Fs]) -> - ["--"|fsummary_1(Fs)]; - + [{text, "--"}|fsummary_1(Fs)]; fsummary_1([#xmlElement{name=ndash}=E|Fs]) -> [E|fsummary_1(Fs)]; fsummary_1([#xmlElement{name=ref}=Ref|Fs]) -> @@ -758,7 +944,9 @@ fsummary_1([#xmlElement{name=ref}=Ref|Fs]) -> Cs ++ fsummary_1(Fs); #xmlElement{name=seetype, content=Cs} -> Cs ++ fsummary_1(Fs); - #xmlText{value=Cs} -> + #xmlText{value = Cs} -> + [Cs | fsummary_1(Fs)]; + {text, Cs} -> [Cs | fsummary_1(Fs)]; Cs when is_list(Cs) -> Cs ++ fsummary_1(Fs); @@ -839,6 +1027,9 @@ lookup4([Class|R], Func) -> lookup(root, _) -> not_found; lookup(object, _) -> not_found; +lookup("static", Func) -> + %% ?LOG("Doc: ~p ~p~n", [get(current_class), _Func]), + lookup("utils", Func); lookup(Class, Func) -> case get({class, Class}) of #class{methods=Ms} -> @@ -857,107 +1048,93 @@ lookup(Class, Func) -> %%%%%%%%%%%%% +%% The xml doesn't close sections correctly due to the markdown +%% used in wxWidgets doesn't close the sections or is not indented +%% correctly, so we need to move sections to the top. + flatten_p(Docs) -> - R = flatten_p(Docs, top, []), - R. +%% ?DBGCF("wxWindow", undefined, "~p~n",[Docs]), + {_Stack, Res} = flatten_p(Docs, [], []), + %% ?DBGCF("wxWindow", undefined, "~p~n",[Res]), + try + true = is_list(Res), + Res + catch _:_ -> + ?LOG("Failed: ~p ~n ~p~n", [Res, Docs]), + exit(failed) + end. -flatten_p([Doc|Docs], Parent, Acc0) -> +flatten_p([Doc|Docs], Stack, Acc) -> case f(Doc) of - break when Parent =/= top -> - {break, [Doc|Docs], Acc0}; - break -> - flatten_p(Docs, Parent, [Doc|Acc0]); - {Type,Deep} when is_list(Deep), Parent =:= Type -> - case flatten_p(Deep, Type, Acc0) of - {break, Rest, Acc} -> - {break, Rest++Docs, Acc}; - Acc -> - flatten_p(Docs, Parent, Acc) - end; - {_Type,Deep} when is_list(Deep), Parent =:= para -> - %% list or simplsect inside para breakout - {break, [Doc|Docs], Acc0}; - {Type,Deep} when is_list(Deep) -> - Cont = [simplesect, xrefdescription, parameterdescription], - case Type =:= para andalso lists:member(Parent, Cont) of - true -> - flatten_p(Deep ++ Docs, Parent, Acc0); - false -> - case flatten_p(Deep, Type, []) of - {break, Rest, Cs} -> - Acc = lists:reverse(Cs), - case Parent of - top -> - flatten_p(Rest++Docs, top, [Doc#xmlElement{name=Type, content=Acc}|Acc0]); - _ -> - {break, Rest++Docs, [Doc#xmlElement{name=Type, content=Acc}|Acc0]} - end; - Cs -> - flatten_p(Docs, Parent, [Doc#xmlElement{name=Type, content=Cs}|Acc0]) - end - end; - Xml when Parent =:= top -> - %% We don't want text outside of para's - case lists:splitwith(fun is_text_element/1, [Doc|Docs]) of - {[], _Cont} -> - flatten_p(Docs, Parent, [Xml|Acc0]); - {Cs, Cont} -> - flatten_p([#xmlElement{name=para, content=Cs}|Cont], top, Acc0) - end; - #xmlText{} = Txt -> + #xmlText{value=_Val} = Txt -> case is_empty([Txt]) of - true when Acc0 =:= []; Docs =:= [] -> - flatten_p(Docs, Parent, Acc0); + true when Acc =:= []; Docs =:= [] -> + flatten_p(Docs, Stack, Acc); _ -> - flatten_p(Docs, Parent, [Txt|Acc0]) + flatten_p(Docs, Stack, [Txt|Acc]) end; - Xml -> - flatten_p(Docs, Parent, [Xml|Acc0]) + break when Stack == [] -> + #xmlElement{name=Type, content=Cs} = Doc, + {NewStack, Res} = flatten_p(Cs, [Doc#xmlElement{name=Type}], []), + flatten_2(Docs, NewStack, lists:reverse(Res) ++ Acc); + break -> + %% ?DBGCF("wxCheckBox", undefined, "~p ~p~n",[Type, [Name || #xmlElement{name = Name} <- Stack]]), + [Top|Stack1] = Stack, + New = Top#xmlElement{content=lists:reverse(Acc)}, + {{break, Stack1, [Doc|Docs]}, [New]}; + {para, Deep} when (hd(Stack))#xmlElement.name =:= para -> + %% Flatten para in para + {NewStack, Res} = flatten_p(Deep, Stack, []), %% ?? + flatten_2(Docs, NewStack, lists:reverse(Res) ++ Acc); + {Type, Deep} -> + %% ?DBGCF("wxFrame", undefined, "~p ~p~n",[Type, [Name || #xmlElement{name = Name} <- Stack]]), + {NewStack, Res} = flatten_p(Deep, [Doc#xmlElement{name=Type}|Stack], []), + flatten_2(Docs, NewStack, lists:reverse(Res) ++ Acc) end; -flatten_p([], _, Acc) -> - lists:reverse(Acc). +flatten_p([], [], Acc) -> + {[], lists:reverse(Acc)}; +flatten_p([], [Top|Stack], Acc) -> + %% ?DBGCF("wxWindow", undefined, "~p ~p ~p~n", + %% [Top#xmlElement.name, [Name || #xmlElement{name = Name} <- Stack], p(lists:reverse(Acc))]), + {Stack, [Top#xmlElement{content=lists:reverse(Acc)}]}. + +flatten_2(Cont, {break, [], Cont2}, Acc) -> + flatten_p(Cont2 ++ Cont, [], Acc); +flatten_2(Cont, {break, [Top|Stack], Cont2}, Acc) -> + {{break, Stack, Cont2 ++ Cont}, [Top#xmlElement{content=lists:reverse(Acc)}]}; +flatten_2(Cont, Stack, Acc) when is_list(Stack) -> + flatten_p(Cont, Stack, Acc). f(#xmlElement{name=heading}) -> break; f(#xmlElement{name=para, content=Cs}) -> {para,Cs}; -f(#xmlElement{name=sect1=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=simplesect=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=itemizedlist=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=orderedlist=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=parameterlist=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=listitem=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=parameterdescription=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=entry=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=row=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=table=T, content=Cs}) -> - {T,Cs}; -f(#xmlElement{name=onlyfor=T, content=Cs}) -> +f(#xmlElement{name=sect1, content=_Cs}) -> + break; +%% f(#xmlElement{name=simplesect=T, content=Cs}) -> +%% break; +f(#xmlElement{name=T, content=Cs}) -> {T,Cs}; - f(#xmlText{}=T) -> - T; -f(#xmlElement{name=Type, content=Cs0}=E) -> - case flatten_p(Cs0, Type, []) of - Cs when is_list(Cs) -> E#xmlElement{content=Cs}; - _Hmm -> - ?LOG("Break ~p ~P~n", [Type, p(E), 20]), - exit(break) - end. + T. camelcase_to_underscore(Name) -> Split = split_cc(Name, [], []), lists:append(lists:join([$_], Split)). +markdown_qoute([$_|Rest]) -> + [$\\, $_ | markdown_qoute(Rest)]; +markdown_qoute([$*|Rest]) -> + [$\\, $* | markdown_qoute(Rest)]; +markdown_qoute([$<|Rest]) -> + [ "*<" | markdown_qoute(Rest)]; +markdown_qoute([$>|Rest]) -> + [ ">*" | markdown_qoute(Rest)]; +markdown_qoute([Char|Rest]) -> + [Char|markdown_qoute(Rest)]; +markdown_qoute([]) -> + []. + split_cc([C|Cs], Word, Str) when C >= $A, C =< $W -> split_cc(Cs, [C+($a-$A)], [lists:reverse(Word)|Str]); @@ -981,6 +1158,7 @@ is_empty(List) -> is_include([#xmlText{value=Txt}|_]) -> case string:trim(Txt) of "Include file:" -> true; + "#include" ++ _ -> true; _ -> false end; is_include(_) -> false. @@ -988,8 +1166,8 @@ is_include(_) -> false. %% Dbg help p(List) when is_list(List) -> [p(E) || E <- List]; -p(#xmlElement{name=itemizedlist=What} = _DBG) -> - {What, [long_list]}; +p(#xmlElement{name=itemizedlist=What, content=List} = _DBG) -> + {What, [p(E) || E <- List]}; p(#xmlElement{name=programlisting=What}) -> {What, [code_example]}; p(#xmlElement{name=What, content=Cs}) -> @@ -997,7 +1175,12 @@ p(#xmlElement{name=What, content=Cs}) -> p(#xmlAttribute{name=What, value=V}) -> {attr, What, V}; p(#xmlText{value=Txt}) -> - {text, lists:flatten(io_lib:format("~-15.s",[Txt]))}; + case string:strip(Txt) of + [] -> %% io:format("Ignore: '~s'~n", [Txt]), + ' '; + _ -> + {text, lists:flatten(io_lib:format("~-45.s",[Txt]))} + end; p({break, Done, Cont}) -> {break, p(Done), p(Cont)}; p({C, List}) -> diff --git a/lib/wx/api_gen/wx_gen_erl.erl b/lib/wx/api_gen/wx_gen_erl.erl index 6b07689a1ed6..e57bbd64b33a 100644 --- a/lib/wx/api_gen/wx_gen_erl.erl +++ b/lib/wx/api_gen/wx_gen_erl.erl @@ -44,6 +44,12 @@ gen(Defs) -> [put({class,N},C) || C=#class{name=N} <- Defs], + Ev2ClassL = [{wx_gen_erl:event_type_name(Ev),Name} || + #class{name=Name, event=Evs} <- Defs, Evs =/= false, Ev <- Evs], + Ev2Class = maps:from_list(Ev2ClassL), + true = length(Ev2ClassL) =:= maps:size(Ev2Class), + put(ev2class, Ev2Class), + gen_unique_names(Defs), gen_event_recs(), gen_enums_ints(), @@ -75,10 +81,16 @@ gen_static(Files) -> w("-module(wx_misc).~n", []), w("-include(\"wxe.hrl\").~n",[]), %% w("-compile(export_all).~n~n", []), %% XXXX remove ??? + + w(~s'\n-moduledoc """\n', []), + w("Miscellaneous functions.\n\n", []), + w(~s'""".\n', []), + put(current_class, "wx_misc"), [gen_static_exports(C) || C <- Files], {ok, MiscExtra} = file:read_file(filename:join([wx_extra, "wx_misc.erl"])), w("~s", [MiscExtra]), Classes = [gen_static_methods(C) || C <- Files], + erase(current_func), close(), Classes. @@ -119,6 +131,8 @@ gen_class1(C=#class{name=Name,parent=Parent,methods=Ms,options=Opts}) -> Parents = parents(Parent), w("-module(~s).~n", [Name]), + wx_gen_doc:module_doc(C), + w("-include(\"wxe.hrl\").~n",[]), Exp = fun(M) -> gen_export(C,M) end, ExportList = lists:usort(lists:append(lists:map(Exp,reverse(Ms)))), @@ -164,8 +178,7 @@ gen_class1(C=#class{name=Name,parent=Parent,methods=Ms,options=Opts}) -> end, ",", NoWDepr, 60)]) end, - - w("%% @hidden~n", []), + w("-doc false.~n", []), parents_check(Parents), Gen = fun(M) -> gen_method(Name,M) end, NewMs = lists:map(Gen,reverse(Ms)), @@ -181,6 +194,7 @@ gen_class1(C=#class{name=Name,parent=Parent,methods=Ms,options=Opts}) -> parents("root") -> [root]; parents("object") -> [object]; +parents("static") -> ["static"]; parents(Parent) -> case get({class,Parent}) of #class{parent=GrandParent} -> @@ -354,7 +368,8 @@ gen_dest(#class{name=CName,abstract=Abs}, Ms) -> end. gen_dest2(Class, Id) -> - w("%% @doc Destroys this object, do not use object again~n", []), + w("-doc \"Destroys the object\".~n", []), + %% wx_gen_doc:func(Ms), w("-spec destroy(This::~s()) -> 'ok'.~n", [Class]), w("destroy(Obj=#wx_ref{type=Type}) ->~n", []), w(" ?CLASS(Type,~s),~n",[Class]), @@ -387,7 +402,7 @@ gen_inherited_ms([[M=#method{name=Name,alias=A,params=Ps0,where=W,method_type=MT [Opt || Opt = #param{def=Def,in=In, where=Where} <- Ps, Def =/= none, In =/= false, Where =/= c] end, - w("%% @hidden~n", []), + w("-doc false.~n", []), gen_function_clause(erl_func_name(Name,A),MT,Ps,Opts,[no_guards,name_only]), w(" -> ~s:", [Class]), gen_function_clause(erl_func_name(Name,A),MT,Ps,Opts,[no_guards,name_only]), @@ -685,26 +700,27 @@ guard_test(T) -> ?error({unknown_type,T}). gen_doc(_Class, [#method{method_type=destructor}]) -> skip; gen_doc(_Class,Ms=[#method{name=N,alias=A,params=Ps,where=erl_no_opt,method_type=MT}])-> - w("%% @equiv ", []), + w("-doc(#{equiv => ", []), gen_function_clause(erl_func_name(N,A),MT,Ps,empty_list,[no_guards,name_only]), - w("~n-spec ",[]), + w("}).~n", []), + w("-spec ",[]), write_specs(Ms, "\n"); gen_doc(Class,Ms=[#method{name=N, type=T}|Rest])-> %%doc_optional(Optional, normal), - doc_link(Class, N), - gen_overload_doc(Rest), + wx_gen_doc:func(Ms), + %% gen_overload_doc(Rest), Ps = lists:foldl(fun(#method{params=Ps}, Acc) -> Ps ++ Acc end,[],Ms), doc_enum_desc(lists:usort(doc_enum(T,Ps))), w("-spec ",[]), write_specs(Ms, "\n"), ok. -gen_overload_doc([]) -> ok; -%%gen_overload_doc(_) -> ok; -gen_overload_doc(Cs) -> - w("%%
Also:
~n%% ",[]), - write_specs(Cs, "
\n%% "), - w("~n", []). +%% gen_overload_doc([]) -> ok; +%% %%gen_overload_doc(_) -> ok; +%% gen_overload_doc(Cs) -> +%% w("%%
Also:
~n%% ",[]), +%% write_specs(Cs, "
\n%% "), +%% w("~n", []). write_specs(M=[#method{method_type=constructor}|_], Eol) -> w("new", []), @@ -758,14 +774,14 @@ optional_type(Opts, Eol) -> optional_type2(#param{name=Name, def=_Def, type=T}) -> "{'" ++ erl_option_name(Name) ++ "', " ++ doc_arg_type2(T) ++ "}". %% %% Default: " ++ Def. -doc_link("utils", Func) -> - w("%% @doc See " - "external documentation.~n", - [lowercase_all(Func)]); -doc_link(Class, Func) -> - w("%% @doc See " - "external documentation.~n", - [lowercase_all(Class),lowercase_all(Class),lowercase_all(Func)]). +%% doc_link("utils", Func) -> +%% w("%% @doc See " +%% "external documentation.~n", +%% [lowercase_all(Func)]); +%% doc_link(Class, Func) -> +%% w("%% @doc See " +%% "external documentation.~n", +%% [lowercase_all(Class),lowercase_all(Class),lowercase_all(Func)]). erl_arg_names(Ps0) -> Ps = [Name || #param{name=Name, in=In, where=Where} <- Ps0,In =/= false, Where =/= c], @@ -889,7 +905,7 @@ doc_enum_type(Type, Name) -> doc_enum_desc([]) -> ok; doc_enum_desc([{_Enum,Name,Vs}|R]) -> - w("%%
~s = ~s~n", [erl_arg_name(Name),Vs]), + w("%% ~s = ~s~n", [erl_arg_name(Name),Vs]), doc_enum_desc(R). %% Misc functions prefixed with wx diff --git a/lib/wx/doc/Makefile b/lib/wx/doc/Makefile index a181857c7654..26975bd2167b 100644 --- a/lib/wx/doc/Makefile +++ b/lib/wx/doc/Makefile @@ -17,8 +17,7 @@ # # %CopyrightEnd% # -include $(ERL_TOP)/make/target.mk -include $(ERL_TOP)/make/$(TARGET)/otp.mk +include ../config.mk # ---------------------------------------------------- # Application version @@ -30,4 +29,12 @@ APPLICATION=wx # ---------------------------------------------------- # Release Target # ---------------------------------------------------- + +## Don't build docs if driver is not built, +## exdoc can't load the driver in gl.erl onload function. + +ifneq ($(CAN_BUILD_DRIVER), true) +DOC_TARGETS= +endif + include $(ERL_TOP)/make/doc.mk diff --git a/lib/wx/src/gen/wxAcceleratorEntry.erl b/lib/wx/src/gen/wxAcceleratorEntry.erl index c2bb1eaf0626..a3dbc51f7db9 100644 --- a/lib/wx/src/gen/wxAcceleratorEntry.erl +++ b/lib/wx/src/gen/wxAcceleratorEntry.erl @@ -20,15 +20,14 @@ -module(wxAcceleratorEntry). -moduledoc """ -Functions for wxAcceleratorEntry class +An object used by an application wishing to create an accelerator table (see `m:wxAcceleratorTable`). -An object used by an application wishing to create an accelerator table (see -`m:wxAcceleratorTable`). +See: +* `m:wxAcceleratorTable` -See: `m:wxAcceleratorTable`, `wxWindow:setAcceleratorTable/2` +* `wxWindow:setAcceleratorTable/2` -wxWidgets docs: -[wxAcceleratorEntry](https://docs.wxwidgets.org/3.1/classwx_accelerator_entry.html) +wxWidgets docs: [wxAcceleratorEntry](https://docs.wxwidgets.org/3.2/classwx_accelerator_entry.html) """. -include("wxe.hrl"). -export([destroy/1,getCommand/1,getFlags/1,getKeyCode/1,new/0,new/1,set/4,set/5]). @@ -38,21 +37,15 @@ wxWidgets docs: -type wxAcceleratorEntry() :: wx:wx_object(). -export_type([wxAcceleratorEntry/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxAcceleratorEntry(). new() -> new([]). -%% @doc See external documentation. -%%
Also:
-%% new(Entry) -> wxAcceleratorEntry() when
-%% Entry::wxAcceleratorEntry().
-%% -doc "Copy ctor.". -spec new([Option]) -> wxAcceleratorEntry() when Option :: {'flags', integer()} @@ -76,7 +69,6 @@ new(#wx_ref{type=EntryT}=Entry) -> wxe_util:queue_cmd(Entry,?get_env(),?wxAcceleratorEntry_new_1_1), wxe_util:rec(?wxAcceleratorEntry_new_1_1). -%% @doc See external documentation. -doc "Returns the command identifier for the accelerator table entry.". -spec getCommand(This) -> integer() when This::wxAcceleratorEntry(). @@ -85,7 +77,6 @@ getCommand(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAcceleratorEntry_GetCommand), wxe_util:rec(?wxAcceleratorEntry_GetCommand). -%% @doc See external documentation. -doc "Returns the flags for the accelerator table entry.". -spec getFlags(This) -> integer() when This::wxAcceleratorEntry(). @@ -94,7 +85,6 @@ getFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAcceleratorEntry_GetFlags), wxe_util:rec(?wxAcceleratorEntry_GetFlags). -%% @doc See external documentation. -doc "Returns the keycode for the accelerator table entry.". -spec getKeyCode(This) -> integer() when This::wxAcceleratorEntry(). @@ -103,7 +93,7 @@ getKeyCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAcceleratorEntry_GetKeyCode), wxe_util:rec(?wxAcceleratorEntry_GetKeyCode). -%% @equiv set(This,Flags,KeyCode,Cmd, []) +-doc(#{equiv => set(This,Flags,KeyCode,Cmd, [])}). -spec set(This, Flags, KeyCode, Cmd) -> 'ok' when This::wxAcceleratorEntry(), Flags::integer(), KeyCode::integer(), Cmd::integer(). @@ -111,7 +101,6 @@ set(This,Flags,KeyCode,Cmd) when is_record(This, wx_ref),is_integer(Flags),is_integer(KeyCode),is_integer(Cmd) -> set(This,Flags,KeyCode,Cmd, []). -%% @doc See external documentation. -doc "Sets the accelerator entry parameters.". -spec set(This, Flags, KeyCode, Cmd, [Option]) -> 'ok' when This::wxAcceleratorEntry(), Flags::integer(), KeyCode::integer(), Cmd::integer(), @@ -124,8 +113,7 @@ set(#wx_ref{type=ThisT}=This,Flags,KeyCode,Cmd, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Flags,KeyCode,Cmd, Opts,?get_env(),?wxAcceleratorEntry_Set). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxAcceleratorEntry()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAcceleratorEntry), diff --git a/lib/wx/src/gen/wxAcceleratorTable.erl b/lib/wx/src/gen/wxAcceleratorTable.erl index dfaea42b18f5..be4b3ee91cdd 100644 --- a/lib/wx/src/gen/wxAcceleratorTable.erl +++ b/lib/wx/src/gen/wxAcceleratorTable.erl @@ -20,27 +20,26 @@ -module(wxAcceleratorTable). -moduledoc """ -Functions for wxAcceleratorTable class +An accelerator table allows the application to specify a table of keyboard shortcuts for +menu or button commands. -An accelerator table allows the application to specify a table of keyboard -shortcuts for menu or button commands. - -The object ?wxNullAcceleratorTable is defined to be a table with no data, and is -the initial accelerator table for a window. +The object ?wxNullAcceleratorTable is defined to be a table with no data, and is the +initial accelerator table for a window. Example: -Remark: An accelerator takes precedence over normal processing and can be a -convenient way to program some event handling. For example, you can use an -accelerator table to enable a dialog with a multi-line text control to accept -CTRL-Enter as meaning 'OK'. +Remark: An accelerator takes precedence over normal processing and can be a convenient +way to program some event handling. For example, you can use an accelerator table to +enable a dialog with a multi-line text control to accept CTRL-Enter as meaning 'OK'. Predefined objects (include wx.hrl): ?wxNullAcceleratorTable -See: `m:wxAcceleratorEntry`, `wxWindow:setAcceleratorTable/2` +See: +* `m:wxAcceleratorEntry` + +* `wxWindow:setAcceleratorTable/2` -wxWidgets docs: -[wxAcceleratorTable](https://docs.wxwidgets.org/3.1/classwx_accelerator_table.html) +wxWidgets docs: [wxAcceleratorTable](https://docs.wxwidgets.org/3.2/classwx_accelerator_table.html) """. -include("wxe.hrl"). -export([destroy/1,isOk/1,new/0,new/2,ok/1]). @@ -50,18 +49,15 @@ wxWidgets docs: -type wxAcceleratorTable() :: wx:wx_object(). -export_type([wxAcceleratorTable/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxAcceleratorTable(). new() -> wxe_util:queue_cmd(?get_env(), ?wxAcceleratorTable_new_0), wxe_util:rec(?wxAcceleratorTable_new_0). -%% @doc See external documentation. -doc "Initializes the accelerator table from an array of `m:wxAcceleratorEntry`.". -spec new(N, Entries) -> wxAcceleratorTable() when N::integer(), Entries::[wxAcceleratorEntry:wxAcceleratorEntry()]. @@ -71,8 +67,7 @@ new(N,Entries) wxe_util:queue_cmd(N,Entries,?get_env(),?wxAcceleratorTable_new_2), wxe_util:rec(?wxAcceleratorTable_new_2). -%% @doc See external documentation. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxAcceleratorTable(). @@ -80,7 +75,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See external documentation. -doc "Returns true if the accelerator table is valid.". -spec isOk(This) -> boolean() when This::wxAcceleratorTable(). @@ -89,12 +83,7 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAcceleratorTable_IsOk), wxe_util:rec(?wxAcceleratorTable_IsOk). -%% @doc Destroys this object, do not use object again --doc """ -Destroys the `m:wxAcceleratorTable` object. - -See overview_refcount_destruct for more info. -""". +-doc "Destroys the object". -spec destroy(This::wxAcceleratorTable()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAcceleratorTable), diff --git a/lib/wx/src/gen/wxActivateEvent.erl b/lib/wx/src/gen/wxActivateEvent.erl index ff22c6fd5fc0..2db2edf3869d 100644 --- a/lib/wx/src/gen/wxActivateEvent.erl +++ b/lib/wx/src/gen/wxActivateEvent.erl @@ -20,30 +20,19 @@ -module(wxActivateEvent). -moduledoc """ -Functions for wxActivateEvent class +An activate event is sent when a window or application is being activated or deactivated. -An activate event is sent when a window or application is being activated or -deactivated. +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -Note: Until wxWidgets 3.1.0 activation events could be sent by wxMSW when the -window was minimized. This reflected the native MSW behaviour but was often -surprising and unexpected, so starting from 3.1.0 such events are not sent any -more when the window is in the minimized state. +This class is derived, and can use functions, from: -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxApp::IsActive` (not implemented in wx) +* `m:wxEvent` -This class is derived (and can use functions) from: `m:wxEvent` - -wxWidgets docs: -[wxActivateEvent](https://docs.wxwidgets.org/3.1/classwx_activate_event.html) +wxWidgets docs: [wxActivateEvent](https://docs.wxwidgets.org/3.2/classwx_activate_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxActivateEventType`](`t:wxActivateEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxActivateEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getActive/1]). @@ -56,12 +45,10 @@ this type. -include("wx.hrl"). -type wxActivateEventType() :: 'activate' | 'activate_app' | 'hibernate'. -export_type([wxActivateEvent/0, wxActivate/0, wxActivateEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Returns true if the application or window is being activated, false otherwise.". -spec getActive(This) -> boolean() when This::wxActivateEvent(). @@ -71,30 +58,21 @@ getActive(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxActivateEvent_GetActive). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxArtProvider.erl b/lib/wx/src/gen/wxArtProvider.erl index dfaa55ef3112..55603373be33 100644 --- a/lib/wx/src/gen/wxArtProvider.erl +++ b/lib/wx/src/gen/wxArtProvider.erl @@ -20,68 +20,75 @@ -module(wxArtProvider). -moduledoc """ -Functions for wxArtProvider class - `m:wxArtProvider` class is used to customize the look of wxWidgets application. -When wxWidgets needs to display an icon or a bitmap (e.g. in the standard file -dialog), it does not use a hard-coded resource but asks `m:wxArtProvider` for it -instead. This way users can plug in their own `m:wxArtProvider` class and easily -replace standard art with their own version. +When wxWidgets needs to display an icon or a bitmap (e.g. in the standard file dialog), +it does not use a hard-coded resource but asks `m:wxArtProvider` for it instead. This way +users can plug in their own `m:wxArtProvider` class and easily replace standard art with +their own version. -All that is needed is to derive a class from `m:wxArtProvider`, override either -its `wxArtProvider::CreateBitmap()` (not implemented in wx) and/or its -`wxArtProvider::CreateIconBundle()` (not implemented in wx) methods and register -the provider with `wxArtProvider::Push()` (not implemented in wx): +All that is needed is to derive a class from `m:wxArtProvider`, override either its `wxArtProvider::CreateBitmap()` +(not implemented in wx) and/or its `wxArtProvider::CreateIconBundle()` (not implemented +in wx) methods and register the provider with `wxArtProvider::Push()` (not implemented in wx): -If you need bitmap images (of the same artwork) that should be displayed at -different sizes you should probably consider overriding -`wxArtProvider::CreateIconBundle` (not implemented in wx) and supplying icon -bundles that contain different bitmap sizes. +If you need bitmap images (of the same artwork) that should be displayed at different +sizes you should probably consider overriding `wxArtProvider::CreateIconBundle` (not +implemented in wx) and supplying icon bundles that contain different bitmap sizes. -There's another way of taking advantage of this class: you can use it in your -code and use platform native icons as provided by `getBitmap/2` or `getIcon/2`. +There's another way of taking advantage of this class: you can use it in your code and +use platform native icons as provided by `getBitmap/2` or `getIcon/2`. Identifying art resources -Every bitmap and icon bundle are known to `m:wxArtProvider` under an unique ID -that is used when requesting a resource from it. The ID is represented by the -?wxArtID type and can have one of these predefined values (you can see bitmaps -represented by these constants in the page_samples_artprov): - -Additionally, any string recognized by custom art providers registered using -`wxArtProvider::Push` (not implemented in wx) may be used. - -Note: When running under GTK+ 2, GTK+ stock item IDs (e.g. `"gtk-cdrom"`) may be -used as well: For a list of the GTK+ stock items please refer to the -[GTK+ documentation page](http://library.gnome.org/devel/gtk/stable/gtk-Stock-Items.html). -It is also possible to load icons from the current icon theme by specifying -their name (without extension and directory components). Icon themes recognized -by GTK+ follow the freedesktop.org -[Icon Themes specification](http://freedesktop.org/Standards/icon-theme-spec). -Note that themes are not guaranteed to contain all icons, so `m:wxArtProvider` -may return ?wxNullBitmap or ?wxNullIcon. The default theme is typically -installed in `/usr/share/icons/hicolor`. +Every bitmap and icon bundle are known to `m:wxArtProvider` under an unique ID that is +used when requesting a resource from it. The ID is represented by the ?wxArtID type and +can have one of these predefined values (you can see bitmaps represented by these +constants in the page_samples_artprov): + +Additionally, any string recognized by custom art providers registered using `wxArtProvider::Push` +(not implemented in wx) may be used. + +Note: When running under GTK+ 2, GTK+ stock item IDs (e.g. `"gtk-cdrom"`) may be used as +well: For a list of the GTK+ stock items please refer to the [GTK+ documentation page](http://library.gnome.org/devel/gtk/stable/gtk-Stock-Items.html). +It is also possible to load icons from the current icon theme by specifying their name +(without extension and directory components). Icon themes recognized by GTK+ follow the +freedesktop.org [Icon Themes specification](http://freedesktop.org/Standards/icon-theme-spec). +Note that themes are not guaranteed to contain all icons, so `m:wxArtProvider` may return +?wxNullBitmap or ?wxNullIcon. The default theme is typically installed in `/usr/share/icons/hicolor`. Clients -The `client` is the entity that calls `m:wxArtProvider`'s `getBitmap/2` or -`getIcon/2` function. It is represented by wxClientID type and can have one of -these values: +The `client` is the entity that calls `m:wxArtProvider`'s `getBitmap/2` or `getIcon/2` function. It is +represented by wxClientID type and can have one of these values: + +* `wxART_TOOLBAR` + +* `wxART_MENU` + +* `wxART_BUTTON` + +* `wxART_FRAME_ICON` -Client ID serve as a hint to `m:wxArtProvider` that is supposed to help it to -choose the best looking bitmap. For example it is often desirable to use -slightly different icons in menus and toolbars even though they represent the -same action (e.g. wxART_FILE_OPEN). Remember that this is really only a hint for -`m:wxArtProvider` \- it is common that `getBitmap/2` returns identical bitmap -for different client values\! +* `wxART_CMN_DIALOG` + +* `wxART_HELP_BROWSER` + +* `wxART_MESSAGE_BOX` + +* `wxART_OTHER` (used for all requests that don't fit into any of the categories above) + +Client ID serve as a hint to `m:wxArtProvider` that is supposed to help it to choose the +best looking bitmap. For example it is often desirable to use slightly different icons in +menus and toolbars even though they represent the same action (e.g. wxART_FILE_OPEN). +Remember that this is really only a hint for `m:wxArtProvider` - it is common that `getBitmap/2` +returns identical bitmap for different client values! See: -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_artprov -for an example of), `m:wxArtProvider`, usage; stock ID list +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_artprov) -wxWidgets docs: -[wxArtProvider](https://docs.wxwidgets.org/3.1/classwx_art_provider.html) +* `m:wxArtProvider` + +wxWidgets docs: [wxArtProvider](https://docs.wxwidgets.org/3.2/classwx_art_provider.html) """. -include("wxe.hrl"). -export([getBitmap/1,getBitmap/2,getIcon/1,getIcon/2]). @@ -91,11 +98,10 @@ wxWidgets docs: -type wxArtProvider() :: wx:wx_object(). -export_type([wxArtProvider/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv getBitmap(Id, []) +-doc(#{equiv => getBitmap(Id, [])}). -spec getBitmap(Id) -> wxBitmap:wxBitmap() when Id::unicode:chardata(). @@ -103,12 +109,11 @@ getBitmap(Id) when ?is_chardata(Id) -> getBitmap(Id, []). -%% @doc See external documentation. -doc """ Query registered providers for bitmap with given ID. -Return: The bitmap if one of registered providers recognizes the ID or -wxNullBitmap otherwise. +Return: The bitmap if one of registered providers recognizes the ID or wxNullBitmap +otherwise. """. -spec getBitmap(Id, [Option]) -> wxBitmap:wxBitmap() when Id::unicode:chardata(), @@ -124,7 +129,7 @@ getBitmap(Id, Options) wxe_util:queue_cmd(Id_UC, Opts,?get_env(),?wxArtProvider_GetBitmap), wxe_util:rec(?wxArtProvider_GetBitmap). -%% @equiv getIcon(Id, []) +-doc(#{equiv => getIcon(Id, [])}). -spec getIcon(Id) -> wxIcon:wxIcon() when Id::unicode:chardata(). @@ -132,11 +137,7 @@ getIcon(Id) when ?is_chardata(Id) -> getIcon(Id, []). -%% @doc See external documentation. --doc """ -Same as `getBitmap/2`, but return a `m:wxIcon` object (or ?wxNullIcon on -failure). -""". +-doc "Same as `getBitmap/2`, but return a `m:wxIcon` object (or ?wxNullIcon on failure).". -spec getIcon(Id, [Option]) -> wxIcon:wxIcon() when Id::unicode:chardata(), Option :: {'client', unicode:chardata()} diff --git a/lib/wx/src/gen/wxAuiDockArt.erl b/lib/wx/src/gen/wxAuiDockArt.erl index 403b95d9944a..20c9943bc7e7 100644 --- a/lib/wx/src/gen/wxAuiDockArt.erl +++ b/lib/wx/src/gen/wxAuiDockArt.erl @@ -20,25 +20,24 @@ -module(wxAuiDockArt). -moduledoc """ -Functions for wxAuiDockArt class +`m:wxAuiDockArt` is part of the wxAUI class framework. -`m:wxAuiDockArt` is part of the wxAUI class framework. See also overview_aui. +See also overview_aui. -`m:wxAuiDockArt` is the art provider: provides all drawing functionality to the -wxAui dock manager. This allows the dock manager to have a pluggable -look-and-feel. +`m:wxAuiDockArt` is the art provider: provides all drawing functionality to the wxAui +dock manager. This allows the dock manager to have a pluggable look-and-feel. -By default, a `m:wxAuiManager` uses an instance of this class called -`wxAuiDefaultDockArt` (not implemented in wx) which provides bitmap art and a -colour scheme that is adapted to the major platforms' look. You can either -derive from that class to alter its behaviour or write a completely new dock art -class. Call `wxAuiManager:setArtProvider/2` to force wxAUI to use your new dock -art provider. +By default, a `m:wxAuiManager` uses an instance of this class called `wxAuiDefaultDockArt` +(not implemented in wx) which provides bitmap art and a colour scheme that is adapted to +the major platforms' look. You can either derive from that class to alter its behaviour or +write a completely new dock art class. Call `wxAuiManager:setArtProvider/2` to force wxAUI to use your new dock art provider. -See: `m:wxAuiManager`, `m:wxAuiPaneInfo` +See: +* `m:wxAuiManager` -wxWidgets docs: -[wxAuiDockArt](https://docs.wxwidgets.org/3.1/classwx_aui_dock_art.html) +* `m:wxAuiPaneInfo` + +wxWidgets docs: [wxAuiDockArt](https://docs.wxwidgets.org/3.2/classwx_aui_dock_art.html) """. -include("wxe.hrl"). -export([getColour/2,getFont/2,getMetric/2,setColour/3,setFont/3,setMetric/3]). @@ -48,11 +47,9 @@ wxWidgets docs: -type wxAuiDockArt() :: wx:wx_object(). -export_type([wxAuiDockArt/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Get the colour of a certain setting. @@ -66,7 +63,6 @@ getColour(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxAuiDockArt_GetColour), wxe_util:rec(?wxAuiDockArt_GetColour). -%% @doc See external documentation. -doc "Get a font setting.". -spec getFont(This, Id) -> wxFont:wxFont() when This::wxAuiDockArt(), Id::integer(). @@ -76,7 +72,6 @@ getFont(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxAuiDockArt_GetFont), wxe_util:rec(?wxAuiDockArt_GetFont). -%% @doc See external documentation. -doc """ Get the value of a certain setting. @@ -90,7 +85,6 @@ getMetric(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxAuiDockArt_GetMetric), wxe_util:rec(?wxAuiDockArt_GetMetric). -%% @doc See external documentation. -doc """ Set a certain setting with the value `colour`. @@ -103,7 +97,6 @@ setColour(#wx_ref{type=ThisT}=This,Id,Colour) ?CLASS(ThisT,wxAuiDockArt), wxe_util:queue_cmd(This,Id,wxe_util:color(Colour),?get_env(),?wxAuiDockArt_SetColour). -%% @doc See external documentation. -doc "Set a font setting.". -spec setFont(This, Id, Font) -> 'ok' when This::wxAuiDockArt(), Id::integer(), Font::wxFont:wxFont(). @@ -113,9 +106,8 @@ setFont(#wx_ref{type=ThisT}=This,Id,#wx_ref{type=FontT}=Font) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Id,Font,?get_env(),?wxAuiDockArt_SetFont). -%% @doc See external documentation. -doc """ -Set a certain setting with the value `new_val`. +Set a certain setting with the value `new\_val`. `id` can be one of the size values of `wxAuiPaneDockArtSetting`. """. diff --git a/lib/wx/src/gen/wxAuiManager.erl b/lib/wx/src/gen/wxAuiManager.erl index 5201ac7a100c..75b5aa26642f 100644 --- a/lib/wx/src/gen/wxAuiManager.erl +++ b/lib/wx/src/gen/wxAuiManager.erl @@ -20,58 +20,115 @@ -module(wxAuiManager). -moduledoc """ -Functions for wxAuiManager class - `m:wxAuiManager` is the central class of the wxAUI class framework. -`m:wxAuiManager` manages the panes associated with it for a particular -`m:wxFrame`, using a pane's `m:wxAuiPaneInfo` information to determine each -pane's docking and floating behaviour. +`m:wxAuiManager` manages the panes associated with it for a particular `m:wxFrame`, using +a pane's `m:wxAuiPaneInfo` information to determine each pane's docking and floating behaviour. -`m:wxAuiManager` uses wxWidgets' sizer mechanism to plan the layout of each -frame. It uses a replaceable dock art class to do all drawing, so all drawing is -localized in one area, and may be customized depending on an application's -specific needs. +`m:wxAuiManager` uses wxWidgets' sizer mechanism to plan the layout of each frame. It +uses a replaceable dock art class to do all drawing, so all drawing is localized in one +area, and may be customized depending on an application's specific needs. -`m:wxAuiManager` works as follows: the programmer adds panes to the class, or -makes changes to existing pane properties (dock position, floating state, show -state, etc.). To apply these changes, `m:wxAuiManager`'s `update/1` function is -called. This batch processing can be used to avoid flicker, by modifying more -than one pane at a time, and then "committing" all of the changes at once by -calling `update/1`. +`m:wxAuiManager` works as follows: the programmer adds panes to the class, or makes +changes to existing pane properties (dock position, floating state, show state, etc.). To +apply these changes, `m:wxAuiManager`'s `update/1` function is called. This batch processing can be +used to avoid flicker, by modifying more than one pane at a time, and then "committing" +all of the changes at once by calling `update/1`. Panes can be added quite easily: -Later on, the positions can be modified easily. The following will float an -existing pane in a tool window: +Later on, the positions can be modified easily. The following will float an existing pane +in a tool window: Layers, Rows and Directions, Positions -Inside wxAUI, the docking layout is figured out by checking several pane -parameters. Four of these are important for determining where a pane will end -up: +Inside wxAUI, the docking layout is figured out by checking several pane parameters. Four +of these are important for determining where a pane will end up: + +* Direction: Each docked pane has a direction, Top, Bottom, Left, Right, or Center. This is +fairly self-explanatory. The pane will be placed in the location specified by this +variable. + +* Position: More than one pane can be placed inside of a dock. Imagine two panes being +docked on the left side of a window. One pane can be placed over another. In +proportionally managed docks, the pane position indicates its sequential position, +starting with zero. So, in our scenario with two panes docked on the left side, the top +pane in the dock would have position 0, and the second one would occupy position 1. + +* Row: A row can allow for two docks to be placed next to each other. One of the most +common places for this to happen is in the toolbar. Multiple toolbar rows are allowed, the +first row being row 0, and the second row 1. Rows can also be used on vertically docked +panes. + +* Layer: A layer is akin to an onion. Layer 0 is the very center of the managed pane. Thus, +if a pane is in layer 0, it will be closest to the center window (also sometimes known as +the "content window"). Increasing layers "swallow up" all layers of a lower value. This +can look very similar to multiple rows, but is different because all panes in a lower +level yield to panes in higher levels. The best way to understand layers is by running the +wxAUI sample. -Styles +## Styles This class supports the following styles: +* wxAUI_MGR_ALLOW_FLOATING: Allow a pane to be undocked to take the form of a `m:wxMiniFrame`. + +* wxAUI_MGR_ALLOW_ACTIVE_PANE: Change the color of the title bar of the pane when it is +activated. + +* wxAUI_MGR_TRANSPARENT_DRAG: Make the pane transparent during its movement. + +* wxAUI_MGR_TRANSPARENT_HINT: The possible location for docking is indicated by a +translucent area. + +* wxAUI_MGR_VENETIAN_BLINDS_HINT: The possible location for docking is indicated by +gradually appearing partially transparent hint. + +* wxAUI_MGR_RECTANGLE_HINT: The possible location for docking is indicated by a rectangular +outline. + +* wxAUI_MGR_HINT_FADE: The translucent area where the pane could be docked appears +gradually. + +* wxAUI_MGR_NO_VENETIAN_BLINDS_FADE: Used in complement of wxAUI_MGR_VENETIAN_BLINDS_HINT +to show the docking hint immediately. + +* wxAUI_MGR_LIVE_RESIZE: When a docked pane is resized, its content is refreshed in live +(instead of moving the border alone and refreshing the content at the end). + +* wxAUI_MGR_DEFAULT: Default behaviour, combines: wxAUI_MGR_ALLOW_FLOATING | +wxAUI_MGR_TRANSPARENT_HINT | wxAUI_MGR_HINT_FADE | wxAUI_MGR_NO_VENETIAN_BLINDS_FADE. + See: -[Overview aui](https://docs.wxwidgets.org/3.1/overview_aui.html#overview_aui), -`m:wxAuiNotebook`, `m:wxAuiDockArt`, `m:wxAuiPaneInfo` +* [Overview aui](https://docs.wxwidgets.org/3.2/overview_aui.html#overview_aui) + +* `m:wxAuiNotebook` + +* `m:wxAuiDockArt` + +* `m:wxAuiPaneInfo` -This class is derived (and can use functions) from: `m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxAuiManager](https://docs.wxwidgets.org/3.1/classwx_aui_manager.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxAuiManager](https://docs.wxwidgets.org/3.2/classwx_aui_manager.html) ## Events -Event types emitted from this class: [`aui_pane_button`](`m:wxAuiManagerEvent`), -[`aui_pane_close`](`m:wxAuiManagerEvent`), -[`aui_pane_maximize`](`m:wxAuiManagerEvent`), -[`aui_pane_restore`](`m:wxAuiManagerEvent`), -[`aui_pane_activated`](`m:wxAuiManagerEvent`), -[`aui_render`](`m:wxAuiManagerEvent`) +Event types emitted from this class: + +* [`aui_pane_button`](`m:wxAuiManagerEvent`) + +* [`aui_pane_close`](`m:wxAuiManagerEvent`) + +* [`aui_pane_maximize`](`m:wxAuiManagerEvent`) + +* [`aui_pane_restore`](`m:wxAuiManagerEvent`) + +* [`aui_pane_activated`](`m:wxAuiManagerEvent`) + +* [`aui_render`](`m:wxAuiManagerEvent`) """. -include("wxe.hrl"). -export([addPane/2,addPane/3,addPane/4,destroy/1,detachPane/2,getAllPanes/1, @@ -86,18 +143,16 @@ Event types emitted from this class: [`aui_pane_button`](`m:wxAuiManagerEvent`), -type wxAuiManager() :: wx:wx_object(). -export_type([wxAuiManager/0]). -%% @hidden -doc false. parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxAuiManager(). new() -> new([]). -%% @doc See external documentation. -doc "Constructor.". -spec new([Option]) -> wxAuiManager() when Option :: {'managed_wnd', wxWindow:wxWindow()} @@ -111,7 +166,7 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxAuiManager_new), wxe_util:rec(?wxAuiManager_new). -%% @equiv addPane(This,Window, []) +-doc(#{equiv => addPane(This,Window, [])}). -spec addPane(This, Window) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(). @@ -119,19 +174,13 @@ addPane(This,Window) when is_record(This, wx_ref),is_record(Window, wx_ref) -> addPane(This,Window, []). -%% @doc See external documentation. -%%
Also:
-%% addPane(This, Window, Pane_info) -> boolean() when
-%% This::wxAuiManager(), Window::wxWindow:wxWindow(), Pane_info::wxAuiPaneInfo:wxAuiPaneInfo().
-%% -doc """ `addPane/4` tells the frame manager to start managing a child window. -There are several versions of this function. The first version allows the full -spectrum of pane parameter possibilities. The second version is used for simpler -user interfaces which do not require as much configuration. The last version -allows a drop position to be specified, which will determine where the pane will -be added. +There are several versions of this function. The first version allows the full spectrum +of pane parameter possibilities. The second version is used for simpler user interfaces +which do not require as much configuration. The last version allows a drop position to be +specified, which will determine where the pane will be added. """. -spec addPane(This, Window, [Option]) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(), @@ -156,7 +205,7 @@ addPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,#wx_ref{type=Pane_ wxe_util:queue_cmd(This,Window,Pane_info,?get_env(),?wxAuiManager_AddPane_2_1), wxe_util:rec(?wxAuiManager_AddPane_2_1). -%% @doc See external documentation. +-doc "". -spec addPane(This, Window, Pane_info, Drop_pos) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(), Pane_info::wxAuiPaneInfo:wxAuiPaneInfo(), Drop_pos::{X::integer(), Y::integer()}. addPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,#wx_ref{type=Pane_infoT}=Pane_info,{Drop_posX,Drop_posY} = Drop_pos) @@ -167,12 +216,10 @@ addPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,#wx_ref{type=Pane_ wxe_util:queue_cmd(This,Window,Pane_info,Drop_pos,?get_env(),?wxAuiManager_AddPane_3), wxe_util:rec(?wxAuiManager_AddPane_3). -%% @doc See external documentation. -doc """ Tells the `m:wxAuiManager` to stop managing the pane specified by window. -The window, if in a floated frame, is reparented to the frame managed by -`m:wxAuiManager`. +The window, if in a floated frame, is reparented to the frame managed by `m:wxAuiManager`. """. -spec detachPane(This, Window) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(). @@ -182,7 +229,6 @@ detachPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(This,Window,?get_env(),?wxAuiManager_DetachPane), wxe_util:rec(?wxAuiManager_DetachPane). -%% @doc See external documentation. -doc "Returns an array of all panes managed by the frame manager.". -spec getAllPanes(This) -> [wxAuiPaneInfo:wxAuiPaneInfo()] when This::wxAuiManager(). @@ -191,7 +237,6 @@ getAllPanes(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_GetAllPanes), wxe_util:rec(?wxAuiManager_GetAllPanes). -%% @doc See external documentation. -doc """ Returns the current art provider being used. @@ -204,7 +249,6 @@ getArtProvider(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_GetArtProvider), wxe_util:rec(?wxAuiManager_GetArtProvider). -%% @doc See external documentation. -doc """ Returns the current dock constraint values. @@ -217,7 +261,6 @@ getDockSizeConstraint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_GetDockSizeConstraint), wxe_util:rec(?wxAuiManager_GetDockSizeConstraint). -%% @doc See external documentation. -doc "Returns the current ?wxAuiManagerOption's flags.". -spec getFlags(This) -> integer() when This::wxAuiManager(). @@ -226,7 +269,6 @@ getFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_GetFlags), wxe_util:rec(?wxAuiManager_GetFlags). -%% @doc See external documentation. -doc "Returns the frame currently being managed by `m:wxAuiManager`.". -spec getManagedWindow(This) -> wxWindow:wxWindow() when This::wxAuiManager(). @@ -235,16 +277,15 @@ getManagedWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_GetManagedWindow), wxe_util:rec(?wxAuiManager_GetManagedWindow). -%% @doc See external documentation. -doc """ Calling this method will return the `m:wxAuiManager` for a given window. -The `window` parameter should specify any child window or sub-child window of -the frame or window managed by `m:wxAuiManager`. +The `window` parameter should specify any child window or sub-child window of the frame +or window managed by `m:wxAuiManager`. -The `window` parameter need not be managed by the manager itself, nor does it -even need to be a child or sub-child of a managed window. It must however be -inside the window hierarchy underneath the managed window. +The `window` parameter need not be managed by the manager itself, nor does it even need +to be a child or sub-child of a managed window. It must however be inside the window +hierarchy underneath the managed window. """. -spec getManager(Window) -> wxAuiManager() when Window::wxWindow:wxWindow(). @@ -253,20 +294,15 @@ getManager(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxAuiManager_GetManager), wxe_util:rec(?wxAuiManager_GetManager). -%% @doc See external documentation. -%%
Also:
-%% getPane(This, Window) -> wxAuiPaneInfo:wxAuiPaneInfo() when
-%% This::wxAuiManager(), Window::wxWindow:wxWindow().
-%% -doc """ -`getPane/2` is used to lookup a `m:wxAuiPaneInfo` object either by window -pointer or by pane name, which acts as a unique id for a window pane. - -The returned `m:wxAuiPaneInfo` object may then be modified to change a pane's -look, state or position. After one or more modifications to `m:wxAuiPaneInfo`, -`update/1` should be called to commit the changes to the user interface. If the -lookup failed (meaning the pane could not be found in the manager), a call to -the returned `m:wxAuiPaneInfo`'s IsOk() method will return false. +`getPane/2` is used to lookup a `m:wxAuiPaneInfo` object either by window pointer or by +pane name, which acts as a unique id for a window pane. + +The returned `m:wxAuiPaneInfo` object may then be modified to change a pane's look, state +or position. After one or more modifications to `m:wxAuiPaneInfo`, `update/1` should be called to +commit the changes to the user interface. If the lookup failed (meaning the pane could not +be found in the manager), a call to the returned `m:wxAuiPaneInfo`'s IsOk() method will +return false. """. -spec getPane(This, Name) -> wxAuiPaneInfo:wxAuiPaneInfo() when This::wxAuiManager(), Name::unicode:chardata(); @@ -284,7 +320,6 @@ getPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(This,Window,?get_env(),?wxAuiManager_GetPane_1_1), wxe_util:rec(?wxAuiManager_GetPane_1_1). -%% @doc See external documentation. -doc "`hideHint/1` hides any docking hint that may be visible.". -spec hideHint(This) -> 'ok' when This::wxAuiManager(). @@ -292,7 +327,7 @@ hideHint(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_HideHint). -%% @equiv insertPane(This,Window,Insert_location, []) +-doc(#{equiv => insertPane(This,Window,Insert_location, [])}). -spec insertPane(This, Window, Insert_location) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(), Insert_location::wxAuiPaneInfo:wxAuiPaneInfo(). @@ -300,18 +335,16 @@ insertPane(This,Window,Insert_location) when is_record(This, wx_ref),is_record(Window, wx_ref),is_record(Insert_location, wx_ref) -> insertPane(This,Window,Insert_location, []). -%% @doc See external documentation. -doc """ -This method is used to insert either a previously unmanaged pane window into the -frame manager, or to insert a currently managed pane somewhere else. +This method is used to insert either a previously unmanaged pane window into the frame +manager, or to insert a currently managed pane somewhere else. -`insertPane/4` will push all panes, rows, or docks aside and insert the window -into the position specified by `insert_location`. +`insertPane/4` will push all panes, rows, or docks aside and insert the window into the position +specified by `insert_location`. -Because `insert_location` can specify either a pane, dock row, or dock layer, -the `insert_level` parameter is used to disambiguate this. The parameter -`insert_level` can take a value of wxAUI_INSERT_PANE, wxAUI_INSERT_ROW or -wxAUI_INSERT_DOCK. +Because `insert_location` can specify either a pane, dock row, or dock layer, the `insert_level` +parameter is used to disambiguate this. The parameter `insert_level` can take a value of +wxAUI_INSERT_PANE, wxAUI_INSERT_ROW or wxAUI_INSERT_DOCK. """. -spec insertPane(This, Window, Insert_location, [Option]) -> boolean() when This::wxAuiManager(), Window::wxWindow:wxWindow(), Insert_location::wxAuiPaneInfo:wxAuiPaneInfo(), @@ -327,15 +360,14 @@ insertPane(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,#wx_ref{type=In wxe_util:queue_cmd(This,Window,Insert_location, Opts,?get_env(),?wxAuiManager_InsertPane), wxe_util:rec(?wxAuiManager_InsertPane). -%% @doc See external documentation. -doc """ -`loadPaneInfo/3` is similar to LoadPerspective, with the exception that it only -loads information about a single pane. +`loadPaneInfo/3` is similar to LoadPerspective, with the exception that it only loads +information about a single pane. -This method writes the serialized data into the passed pane. Pointers to UI -elements are not modified. +This method writes the serialized data into the passed pane. Pointers to UI elements are +not modified. -Note: This operation also changes the name in the pane information\! +Note: This operation also changes the name in the pane information! See: `loadPerspective/3` @@ -352,7 +384,7 @@ loadPaneInfo(#wx_ref{type=ThisT}=This,Pane_part,#wx_ref{type=PaneT}=Pane) ?CLASS(PaneT,wxAuiPaneInfo), wxe_util:queue_cmd(This,Pane_part_UC,Pane,?get_env(),?wxAuiManager_LoadPaneInfo). -%% @equiv loadPerspective(This,Perspective, []) +-doc(#{equiv => loadPerspective(This,Perspective, [])}). -spec loadPerspective(This, Perspective) -> boolean() when This::wxAuiManager(), Perspective::unicode:chardata(). @@ -360,17 +392,15 @@ loadPerspective(This,Perspective) when is_record(This, wx_ref),?is_chardata(Perspective) -> loadPerspective(This,Perspective, []). -%% @doc See external documentation. -doc """ Loads a saved perspective. A perspective is the layout state of an AUI managed window. -All currently existing panes that have an object in "perspective" with the same -name ("equivalent") will receive the layout parameters of the object in -"perspective". Existing panes that do not have an equivalent in "perspective" -remain unchanged, objects in "perspective" having no equivalent in the manager -are ignored. +All currently existing panes that have an object in "perspective" with the same name +("equivalent") will receive the layout parameters of the object in "perspective". Existing +panes that do not have an equivalent in "perspective" remain unchanged, objects in +"perspective" having no equivalent in the manager are ignored. See: `loadPaneInfo/3` @@ -391,14 +421,12 @@ loadPerspective(#wx_ref{type=ThisT}=This,Perspective, Options) wxe_util:queue_cmd(This,Perspective_UC, Opts,?get_env(),?wxAuiManager_LoadPerspective), wxe_util:rec(?wxAuiManager_LoadPerspective). -%% @doc See external documentation. -doc """ -`savePaneInfo/2` is similar to SavePerspective, with the exception that it only -saves information about a single pane. +`savePaneInfo/2` is similar to SavePerspective, with the exception that it only saves +information about a single pane. -Return: The serialized layout parameters of the pane are returned within the -string. Information about the pointers to UI elements stored in the pane are not -serialized. +Return: The serialized layout parameters of the pane are returned within the string. +Information about the pointers to UI elements stored in the pane are not serialized. See: `loadPaneInfo/3` @@ -414,11 +442,9 @@ savePaneInfo(#wx_ref{type=ThisT}=This,#wx_ref{type=PaneT}=Pane) -> wxe_util:queue_cmd(This,Pane,?get_env(),?wxAuiManager_SavePaneInfo), wxe_util:rec(?wxAuiManager_SavePaneInfo). -%% @doc See external documentation. -doc """ -Saves the entire user interface layout into an encoded `wxString` (not -implemented in wx), which can then be stored by the application (probably using -wxConfig). +Saves the entire user interface layout into an encoded `wxString` (not implemented in +wx), which can then be stored by the application (probably using wxConfig). See: `loadPerspective/3` @@ -433,13 +459,12 @@ savePerspective(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_SavePerspective), wxe_util:rec(?wxAuiManager_SavePerspective). -%% @doc See external documentation. -doc """ -Instructs `m:wxAuiManager` to use art provider specified by parameter -`art_provider` for all drawing calls. +Instructs `m:wxAuiManager` to use art provider specified by parameter `art\_provider` for +all drawing calls. -This allows pluggable look-and-feel features. The previous art provider object, -if any, will be deleted by `m:wxAuiManager`. +This allows pluggable look-and-feel features. The previous art provider object, if any, +will be deleted by `m:wxAuiManager`. See: `m:wxAuiDockArt` """. @@ -450,20 +475,17 @@ setArtProvider(#wx_ref{type=ThisT}=This,#wx_ref{type=Art_providerT}=Art_provider ?CLASS(Art_providerT,wxAuiDockArt), wxe_util:queue_cmd(This,Art_provider,?get_env(),?wxAuiManager_SetArtProvider). -%% @doc See external documentation. -doc """ -When a user creates a new dock by dragging a window into a docked position, -often times the large size of the window will create a dock that is unwieldy -large. - -`m:wxAuiManager` by default limits the size of any new dock to 1/3 of the window -size. For horizontal docks, this would be 1/3 of the window height. For vertical -docks, 1/3 of the width. - -Calling this function will adjust this constraint value. The numbers must be -between 0.0 and 1.0. For instance, calling SetDockSizeContraint with 0.5, 0.5 -will cause new docks to be limited to half of the size of the entire managed -window. +When a user creates a new dock by dragging a window into a docked position, often times +the large size of the window will create a dock that is unwieldy large. + +`m:wxAuiManager` by default limits the size of any new dock to 1/3 of the window size. +For horizontal docks, this would be 1/3 of the window height. For vertical docks, 1/3 of +the width. + +Calling this function will adjust this constraint value. The numbers must be between 0.0 +and 1.0. For instance, calling SetDockSizeContraint with 0.5, 0.5 will cause new docks to +be limited to half of the size of the entire managed window. """. -spec setDockSizeConstraint(This, Widthpct, Heightpct) -> 'ok' when This::wxAuiManager(), Widthpct::number(), Heightpct::number(). @@ -472,12 +494,10 @@ setDockSizeConstraint(#wx_ref{type=ThisT}=This,Widthpct,Heightpct) ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,Widthpct,Heightpct,?get_env(),?wxAuiManager_SetDockSizeConstraint). -%% @doc See external documentation. -doc """ This method is used to specify ?wxAuiManagerOption's flags. -`flags` specifies options which allow the frame management behaviour to be -modified. +`flags` specifies options which allow the frame management behaviour to be modified. """. -spec setFlags(This, Flags) -> 'ok' when This::wxAuiManager(), Flags::integer(). @@ -486,13 +506,11 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,Flags,?get_env(),?wxAuiManager_SetFlags). -%% @doc See external documentation. -doc """ -Called to specify the frame or window which is to be managed by -`m:wxAuiManager`. +Called to specify the frame or window which is to be managed by `m:wxAuiManager`. -Frame management is not restricted to just frames. Child windows or custom -controls are also allowed. +Frame management is not restricted to just frames. Child windows or custom controls are +also allowed. """. -spec setManagedWindow(This, Managed_wnd) -> 'ok' when This::wxAuiManager(), Managed_wnd::wxWindow:wxWindow(). @@ -501,13 +519,12 @@ setManagedWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=Managed_wndT}=Managed_wnd ?CLASS(Managed_wndT,wxWindow), wxe_util:queue_cmd(This,Managed_wnd,?get_env(),?wxAuiManager_SetManagedWindow). -%% @doc See external documentation. -doc """ -This function is used by controls to explicitly show a hint window at the -specified rectangle. +This function is used by controls to explicitly show a hint window at the specified +rectangle. -It is rarely called, and is mostly used by controls implementing custom pane -drag/drop behaviour. The specified rectangle should be in screen coordinates. +It is rarely called, and is mostly used by controls implementing custom pane drag/drop +behaviour. The specified rectangle should be in screen coordinates. """. -spec showHint(This, Rect) -> 'ok' when This::wxAuiManager(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -516,14 +533,12 @@ showHint(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,Rect,?get_env(),?wxAuiManager_ShowHint). -%% @doc See external documentation. -doc """ Dissociate the managed window from the manager. -This function may be called before the managed frame or window is destroyed, -but, since wxWidgets 3.1.4, it's unnecessary to call it explicitly, as it will -be called automatically when this window is destroyed, as well as when the -manager itself is. +This function may be called before the managed frame or window is destroyed, but, since +wxWidgets 3.1.4, it's unnecessary to call it explicitly, as it will be called +automatically when this window is destroyed, as well as when the manager itself is. """. -spec unInit(This) -> 'ok' when This::wxAuiManager(). @@ -531,16 +546,13 @@ unInit(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_UnInit). -%% @doc See external documentation. -doc """ -This method is called after any number of changes are made to any of the managed -panes. +This method is called after any number of changes are made to any of the managed panes. -`update/1` must be invoked after `addPane/4` or `insertPane/4` are called in -order to "realize" or "commit" the changes. In addition, any number of changes -may be made to `m:wxAuiPaneInfo` structures (retrieved with `getPane/2`), but to -realize the changes, `update/1` must be called. This construction allows pane -flicker to be avoided by updating the whole layout at one time. +`update/1` must be invoked after `addPane/4` or `insertPane/4` are called in order to "realize" or "commit" the changes. In +addition, any number of changes may be made to `m:wxAuiPaneInfo` structures (retrieved +with `getPane/2`), but to realize the changes, `update/1` must be called. This construction allows pane flicker +to be avoided by updating the whole layout at one time. """. -spec update(This) -> 'ok' when This::wxAuiManager(). @@ -548,26 +560,20 @@ update(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxAuiManager), wxe_util:queue_cmd(This,?get_env(),?wxAuiManager_Update). -%% @doc Destroys this object, do not use object again --doc "Dtor.". +-doc "Destroys the object". -spec destroy(This::wxAuiManager()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAuiManager), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxAuiManagerEvent.erl b/lib/wx/src/gen/wxAuiManagerEvent.erl index d2992390d2a6..6989bef5d04a 100644 --- a/lib/wx/src/gen/wxAuiManagerEvent.erl +++ b/lib/wx/src/gen/wxAuiManagerEvent.erl @@ -20,24 +20,24 @@ -module(wxAuiManagerEvent). -moduledoc """ -Functions for wxAuiManagerEvent class - Event used to indicate various actions taken with `m:wxAuiManager`. See `m:wxAuiManager` for available event types. -See: `m:wxAuiManager`, `m:wxAuiPaneInfo` +See: +* `m:wxAuiManager` + +* `m:wxAuiPaneInfo` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxAuiManagerEvent](https://docs.wxwidgets.org/3.1/classwx_aui_manager_event.html) +wxWidgets docs: [wxAuiManagerEvent](https://docs.wxwidgets.org/3.2/classwx_aui_manager_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxAuiManagerEventType`](`t:wxAuiManagerEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxAuiManagerEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([canVeto/1,getButton/1,getDC/1,getManager/1,getPane/1,getVeto/1,setButton/2, @@ -51,12 +51,10 @@ this type. -include("wx.hrl"). -type wxAuiManagerEventType() :: 'aui_pane_button' | 'aui_pane_close' | 'aui_pane_maximize' | 'aui_pane_restore' | 'aui_pane_activated' | 'aui_render' | 'aui_find_manager'. -export_type([wxAuiManagerEvent/0, wxAuiManager/0, wxAuiManagerEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Sets the `m:wxAuiManager` this event is associated with.". -spec setManager(This, Manager) -> 'ok' when This::wxAuiManagerEvent(), Manager::wxAuiManager:wxAuiManager(). @@ -65,7 +63,6 @@ setManager(#wx_ref{type=ThisT}=This,#wx_ref{type=ManagerT}=Manager) -> ?CLASS(ManagerT,wxAuiManager), wxe_util:queue_cmd(This,Manager,?get_env(),?wxAuiManagerEvent_SetManager). -%% @doc See external documentation. -doc "Return: The `m:wxAuiManager` this event is associated with.". -spec getManager(This) -> wxAuiManager:wxAuiManager() when This::wxAuiManagerEvent(). @@ -74,7 +71,6 @@ getManager(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManagerEvent_GetManager), wxe_util:rec(?wxAuiManagerEvent_GetManager). -%% @doc See external documentation. -doc "Sets the pane this event is associated with.". -spec setPane(This, Pane) -> 'ok' when This::wxAuiManagerEvent(), Pane::wxAuiPaneInfo:wxAuiPaneInfo(). @@ -83,7 +79,6 @@ setPane(#wx_ref{type=ThisT}=This,#wx_ref{type=PaneT}=Pane) -> ?CLASS(PaneT,wxAuiPaneInfo), wxe_util:queue_cmd(This,Pane,?get_env(),?wxAuiManagerEvent_SetPane). -%% @doc See external documentation. -doc "Return: The pane this event is associated with.". -spec getPane(This) -> wxAuiPaneInfo:wxAuiPaneInfo() when This::wxAuiManagerEvent(). @@ -92,7 +87,6 @@ getPane(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManagerEvent_GetPane), wxe_util:rec(?wxAuiManagerEvent_GetPane). -%% @doc See external documentation. -doc "Sets the ID of the button clicked that triggered this event.". -spec setButton(This, Button) -> 'ok' when This::wxAuiManagerEvent(), Button::integer(). @@ -101,7 +95,6 @@ setButton(#wx_ref{type=ThisT}=This,Button) ?CLASS(ThisT,wxAuiManagerEvent), wxe_util:queue_cmd(This,Button,?get_env(),?wxAuiManagerEvent_SetButton). -%% @doc See external documentation. -doc "Return: The ID of the button that was clicked.". -spec getButton(This) -> integer() when This::wxAuiManagerEvent(). @@ -110,7 +103,7 @@ getButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManagerEvent_GetButton), wxe_util:rec(?wxAuiManagerEvent_GetButton). -%% @doc See external documentation. +-doc "". -spec setDC(This, Pdc) -> 'ok' when This::wxAuiManagerEvent(), Pdc::wxDC:wxDC(). setDC(#wx_ref{type=ThisT}=This,#wx_ref{type=PdcT}=Pdc) -> @@ -118,7 +111,7 @@ setDC(#wx_ref{type=ThisT}=This,#wx_ref{type=PdcT}=Pdc) -> ?CLASS(PdcT,wxDC), wxe_util:queue_cmd(This,Pdc,?get_env(),?wxAuiManagerEvent_SetDC). -%% @doc See external documentation. +-doc "". -spec getDC(This) -> wxDC:wxDC() when This::wxAuiManagerEvent(). getDC(#wx_ref{type=ThisT}=This) -> @@ -126,7 +119,7 @@ getDC(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManagerEvent_GetDC), wxe_util:rec(?wxAuiManagerEvent_GetDC). -%% @equiv veto(This, []) +-doc(#{equiv => veto(This, [])}). -spec veto(This) -> 'ok' when This::wxAuiManagerEvent(). @@ -134,7 +127,6 @@ veto(This) when is_record(This, wx_ref) -> veto(This, []). -%% @doc See external documentation. -doc "Cancels the action indicated by this event if `canVeto/1` is true.". -spec veto(This, [Option]) -> 'ok' when This::wxAuiManagerEvent(), @@ -147,7 +139,6 @@ veto(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiManagerEvent_Veto). -%% @doc See external documentation. -doc """ Return: true if this event was vetoed. @@ -160,7 +151,6 @@ getVeto(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiManagerEvent_GetVeto), wxe_util:rec(?wxAuiManagerEvent_GetVeto). -%% @doc See external documentation. -doc "Sets whether or not this event can be vetoed.". -spec setCanVeto(This, Can_veto) -> 'ok' when This::wxAuiManagerEvent(), Can_veto::boolean(). @@ -169,7 +159,6 @@ setCanVeto(#wx_ref{type=ThisT}=This,Can_veto) ?CLASS(ThisT,wxAuiManagerEvent), wxe_util:queue_cmd(This,Can_veto,?get_env(),?wxAuiManagerEvent_SetCanVeto). -%% @doc See external documentation. -doc """ Return: true if this event can be vetoed. @@ -183,30 +172,21 @@ canVeto(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxAuiManagerEvent_CanVeto). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxAuiNotebook.erl b/lib/wx/src/gen/wxAuiNotebook.erl index 61a66ef98991..d5c7a62bd319 100644 --- a/lib/wx/src/gen/wxAuiNotebook.erl +++ b/lib/wx/src/gen/wxAuiNotebook.erl @@ -20,51 +20,95 @@ -module(wxAuiNotebook). -moduledoc """ -Functions for wxAuiNotebook class - -`m:wxAuiNotebook` is part of the wxAUI class framework, which represents a -notebook control, managing multiple windows with associated tabs. +`m:wxAuiNotebook` is part of the wxAUI class framework, which represents a notebook +control, managing multiple windows with associated tabs. See also overview_aui. `m:wxAuiNotebook` is a notebook control which implements many features common in -applications with dockable panes. Specifically, `m:wxAuiNotebook` implements -functionality which allows the user to rearrange tab order via drag-and-drop, -split the tab window into many different splitter configurations, and toggle -through different themes to customize the control's look and feel. +applications with dockable panes. Specifically, `m:wxAuiNotebook` implements functionality +which allows the user to rearrange tab order via drag-and-drop, split the tab window into +many different splitter configurations, and toggle through different themes to customize +the control's look and feel. -The default theme that is used is `wxAuiDefaultTabArt` (not implemented in wx), -which provides a modern, glossy look and feel. The theme can be changed by -calling `setArtProvider/2`. +The default theme that is used is `wxAuiDefaultTabArt` (not implemented in wx), which +provides a modern, glossy look and feel. The theme can be changed by calling `setArtProvider/2`. -Styles +## Styles This class supports the following styles: -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* wxAUI_NB_DEFAULT_STYLE: Defined as wxAUI_NB_TOP | wxAUI_NB_TAB_SPLIT | wxAUI_NB_TAB_MOVE +| wxAUI_NB_SCROLL_BUTTONS | wxAUI_NB_CLOSE_ON_ACTIVE_TAB | wxAUI_NB_MIDDLE_CLICK_CLOSE. + +* wxAUI_NB_TAB_SPLIT: Allows the tab control to be split by dragging a tab. + +* wxAUI_NB_TAB_MOVE: Allows a tab to be moved horizontally by dragging. + +* wxAUI_NB_TAB_EXTERNAL_MOVE: Allows a tab to be moved to another tab control. + +* wxAUI_NB_TAB_FIXED_WIDTH: With this style, all tabs have the same width. + +* wxAUI_NB_SCROLL_BUTTONS: With this style, left and right scroll buttons are displayed. + +* wxAUI_NB_WINDOWLIST_BUTTON: With this style, a drop-down list of windows is available. + +* wxAUI_NB_CLOSE_BUTTON: With this style, a close button is available on the tab bar. + +* wxAUI_NB_CLOSE_ON_ACTIVE_TAB: With this style, the close button is visible on the active +tab. + +* wxAUI_NB_CLOSE_ON_ALL_TABS: With this style, the close button is visible on all tabs. + +* wxAUI_NB_MIDDLE_CLICK_CLOSE: With this style, middle click on a tab closes the tab. + +* wxAUI_NB_TOP: With this style, tabs are drawn along the top of the notebook. + +* wxAUI_NB_BOTTOM: With this style, tabs are drawn along the bottom of the notebook. + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -wxWidgets docs: -[wxAuiNotebook](https://docs.wxwidgets.org/3.1/classwx_aui_notebook.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxAuiNotebook](https://docs.wxwidgets.org/3.2/classwx_aui_notebook.html) ## Events Event types emitted from this class: -[`command_auinotebook_page_close`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_page_closed`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_page_changed`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_page_changing`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_button`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_begin_drag`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_end_drag`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_drag_motion`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_allow_dnd`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_drag_done`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_tab_middle_down`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_tab_middle_up`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_tab_right_down`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_tab_right_up`](`m:wxAuiNotebookEvent`), -[`command_auinotebook_bg_dclick`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_page_close`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_page_closed`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_page_changed`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_page_changing`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_button`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_begin_drag`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_end_drag`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_drag_motion`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_allow_dnd`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_drag_done`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_tab_middle_down`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_tab_middle_up`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_tab_right_down`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_tab_right_up`](`m:wxAuiNotebookEvent`) + +* [`command_auinotebook_bg_dclick`](`m:wxAuiNotebookEvent`) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,addPage/5,create/2,create/3,create/4,deletePage/2, @@ -115,21 +159,19 @@ Event types emitted from this class: -type wxAuiNotebook() :: wx:wx_object(). -export_type([wxAuiNotebook/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxAuiNotebook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxAuiNotebook_new_0), wxe_util:rec(?wxAuiNotebook_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxAuiNotebook() when Parent::wxWindow:wxWindow(). @@ -137,7 +179,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ Constructor. @@ -161,7 +202,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxAuiNotebook_new_2), wxe_util:rec(?wxAuiNotebook_new_2). -%% @equiv addPage(This,Page,Caption, []) +-doc(#{equiv => addPage(This,Page,Caption, [])}). -spec addPage(This, Page, Caption) -> boolean() when This::wxAuiNotebook(), Page::wxWindow:wxWindow(), Caption::unicode:chardata(). @@ -169,12 +210,10 @@ addPage(This,Page,Caption) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Caption) -> addPage(This,Page,Caption, []). -%% @doc See external documentation. -doc """ Adds a page. -If the `select` parameter is true, calling this will generate a page change -event. +If the `select` parameter is true, calling this will generate a page change event. """. -spec addPage(This, Page, Caption, [Option]) -> boolean() when This::wxAuiNotebook(), Page::wxWindow:wxWindow(), Caption::unicode:chardata(), @@ -192,12 +231,11 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Caption, Options) wxe_util:queue_cmd(This,Page,Caption_UC, Opts,?get_env(),?wxAuiNotebook_AddPage_3), wxe_util:rec(?wxAuiNotebook_AddPage_3). -%% @doc See external documentation. -doc """ Adds a new page. -The page must have the book control itself as the parent and must not have been -added to this control previously. +The page must have the book control itself as the parent and must not have been added to +this control previously. The call to this function may generate the page changing events. @@ -219,7 +257,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text,Select,ImageId) wxe_util:queue_cmd(This,Page,Text_UC,Select,ImageId,?get_env(),?wxAuiNotebook_AddPage_4), wxe_util:rec(?wxAuiNotebook_AddPage_4). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxAuiNotebook(), Parent::wxWindow:wxWindow(). @@ -227,15 +265,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See external documentation. -%%
Also:
-%% create(This, Parent, [Option]) -> boolean() when
-%% This::wxAuiNotebook(), Parent::wxWindow:wxWindow(),
-%% Option :: {'id', integer()}
-%% | {'pos', {X::integer(), Y::integer()}}
-%% | {'size', {W::integer(), H::integer()}}
-%% | {'style', integer()}.
-%% -doc "Creates the notebook window.". -spec create(This, Parent, Winid) -> boolean() when This::wxAuiNotebook(), Parent::wxWindow:wxWindow(), Winid::integer(); @@ -262,7 +291,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxAuiNotebook_Create_2), wxe_util:rec(?wxAuiNotebook_Create_2). -%% @doc See external documentation. -doc "Constructs the book control with the given parameters.". -spec create(This, Parent, Winid, [Option]) -> boolean() when This::wxAuiNotebook(), Parent::wxWindow:wxWindow(), Winid::integer(), @@ -281,7 +309,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Winid, Options) wxe_util:queue_cmd(This,Parent,Winid, Opts,?get_env(),?wxAuiNotebook_Create_3), wxe_util:rec(?wxAuiNotebook_Create_3). -%% @doc See external documentation. -doc """ Deletes a page at the given index. @@ -295,7 +322,6 @@ deletePage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebook_DeletePage), wxe_util:rec(?wxAuiNotebook_DeletePage). -%% @doc See external documentation. -doc "Returns the associated art provider.". -spec getArtProvider(This) -> wxAuiTabArt:wxAuiTabArt() when This::wxAuiNotebook(). @@ -304,7 +330,6 @@ getArtProvider(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiNotebook_GetArtProvider), wxe_util:rec(?wxAuiNotebook_GetArtProvider). -%% @doc See external documentation. -doc "Returns the page specified by the given index.". -spec getPage(This, Page_idx) -> wxWindow:wxWindow() when This::wxAuiNotebook(), Page_idx::integer(). @@ -314,7 +339,6 @@ getPage(#wx_ref{type=ThisT}=This,Page_idx) wxe_util:queue_cmd(This,Page_idx,?get_env(),?wxAuiNotebook_GetPage), wxe_util:rec(?wxAuiNotebook_GetPage). -%% @doc See external documentation. -doc "Returns the tab bitmap for the page.". -spec getPageBitmap(This, Page) -> wxBitmap:wxBitmap() when This::wxAuiNotebook(), Page::integer(). @@ -324,7 +348,6 @@ getPageBitmap(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebook_GetPageBitmap), wxe_util:rec(?wxAuiNotebook_GetPageBitmap). -%% @doc See external documentation. -doc "Returns the number of pages in the notebook.". -spec getPageCount(This) -> integer() when This::wxAuiNotebook(). @@ -333,7 +356,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiNotebook_GetPageCount), wxe_util:rec(?wxAuiNotebook_GetPageCount). -%% @doc See external documentation. -doc """ Returns the page index for the specified window. @@ -347,7 +369,6 @@ getPageIndex(#wx_ref{type=ThisT}=This,#wx_ref{type=Page_wndT}=Page_wnd) -> wxe_util:queue_cmd(This,Page_wnd,?get_env(),?wxAuiNotebook_GetPageIndex), wxe_util:rec(?wxAuiNotebook_GetPageIndex). -%% @doc See external documentation. -doc "Returns the tab label for the page.". -spec getPageText(This, Page) -> unicode:charlist() when This::wxAuiNotebook(), Page::integer(). @@ -357,7 +378,6 @@ getPageText(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebook_GetPageText), wxe_util:rec(?wxAuiNotebook_GetPageText). -%% @doc See external documentation. -doc "Returns the currently selected page.". -spec getSelection(This) -> integer() when This::wxAuiNotebook(). @@ -366,7 +386,7 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiNotebook_GetSelection), wxe_util:rec(?wxAuiNotebook_GetSelection). -%% @equiv insertPage(This,Page_idx,Page,Caption, []) +-doc(#{equiv => insertPage(This,Page_idx,Page,Caption, [])}). -spec insertPage(This, Page_idx, Page, Caption) -> boolean() when This::wxAuiNotebook(), Page_idx::integer(), Page::wxWindow:wxWindow(), Caption::unicode:chardata(). @@ -374,13 +394,11 @@ insertPage(This,Page_idx,Page,Caption) when is_record(This, wx_ref),is_integer(Page_idx),is_record(Page, wx_ref),?is_chardata(Caption) -> insertPage(This,Page_idx,Page,Caption, []). -%% @doc See external documentation. -doc """ -`insertPage/6` is similar to AddPage, but allows the ability to specify the -insert location. +`insertPage/6` is similar to AddPage, but allows the ability to specify the insert +location. -If the `select` parameter is true, calling this will generate a page change -event. +If the `select` parameter is true, calling this will generate a page change event. """. -spec insertPage(This, Page_idx, Page, Caption, [Option]) -> boolean() when This::wxAuiNotebook(), Page_idx::integer(), Page::wxWindow:wxWindow(), Caption::unicode:chardata(), @@ -398,7 +416,6 @@ insertPage(#wx_ref{type=ThisT}=This,Page_idx,#wx_ref{type=PageT}=Page,Caption, O wxe_util:queue_cmd(This,Page_idx,Page,Caption_UC, Opts,?get_env(),?wxAuiNotebook_InsertPage_4), wxe_util:rec(?wxAuiNotebook_InsertPage_4). -%% @doc See external documentation. -doc """ Inserts a new page at the specified position. @@ -420,7 +437,6 @@ insertPage(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=PageT}=Page,Text,Select,I wxe_util:queue_cmd(This,Index,Page,Text_UC,Select,ImageId,?get_env(),?wxAuiNotebook_InsertPage_5), wxe_util:rec(?wxAuiNotebook_InsertPage_5). -%% @doc See external documentation. -doc "Removes a page, without deleting the window pointer.". -spec removePage(This, Page) -> boolean() when This::wxAuiNotebook(), Page::integer(). @@ -430,7 +446,6 @@ removePage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebook_RemovePage), wxe_util:rec(?wxAuiNotebook_RemovePage). -%% @doc See external documentation. -doc "Sets the art provider to be used by the notebook.". -spec setArtProvider(This, Art) -> 'ok' when This::wxAuiNotebook(), Art::wxAuiTabArt:wxAuiTabArt(). @@ -439,10 +454,9 @@ setArtProvider(#wx_ref{type=ThisT}=This,#wx_ref{type=ArtT}=Art) -> ?CLASS(ArtT,wxAuiTabArt), wxe_util:queue_cmd(This,Art,?get_env(),?wxAuiNotebook_SetArtProvider). -%% @doc See external documentation. -doc """ -Sets the font for drawing the tab labels, using a bold version of the font for -selected tab labels. +Sets the font for drawing the tab labels, using a bold version of the font for selected +tab labels. """. -spec setFont(This, Font) -> boolean() when This::wxAuiNotebook(), Font::wxFont:wxFont(). @@ -452,7 +466,6 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> wxe_util:queue_cmd(This,Font,?get_env(),?wxAuiNotebook_SetFont), wxe_util:rec(?wxAuiNotebook_SetFont). -%% @doc See external documentation. -doc """ Sets the bitmap for the page. @@ -467,7 +480,6 @@ setPageBitmap(#wx_ref{type=ThisT}=This,Page,#wx_ref{type=BitmapT}=Bitmap) wxe_util:queue_cmd(This,Page,Bitmap,?get_env(),?wxAuiNotebook_SetPageBitmap), wxe_util:rec(?wxAuiNotebook_SetPageBitmap). -%% @doc See external documentation. -doc "Sets the tab label for the page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxAuiNotebook(), Page::integer(), Text::unicode:chardata(). @@ -478,7 +490,6 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:queue_cmd(This,Page,Text_UC,?get_env(),?wxAuiNotebook_SetPageText), wxe_util:rec(?wxAuiNotebook_SetPageText). -%% @doc See external documentation. -doc """ Sets the page selection. @@ -492,17 +503,15 @@ setSelection(#wx_ref{type=ThisT}=This,New_page) wxe_util:queue_cmd(This,New_page,?get_env(),?wxAuiNotebook_SetSelection), wxe_util:rec(?wxAuiNotebook_SetSelection). -%% @doc See external documentation. -doc """ Sets the tab height. -By default, the tab control height is calculated by measuring the text height -and bitmap sizes on the tab captions. Calling this method will override that -calculation and set the tab control to the specified height parameter. A call to -this method will override any call to `setUniformBitmapSize/2`. +By default, the tab control height is calculated by measuring the text height and bitmap +sizes on the tab captions. Calling this method will override that calculation and set the +tab control to the specified height parameter. A call to this method will override any +call to `setUniformBitmapSize/2`. -Specifying -1 as the height will return the control to its default auto-sizing -behaviour. +Specifying -1 as the height will return the control to its default auto-sizing behaviour. """. -spec setTabCtrlHeight(This, Height) -> 'ok' when This::wxAuiNotebook(), Height::integer(). @@ -511,13 +520,11 @@ setTabCtrlHeight(#wx_ref{type=ThisT}=This,Height) ?CLASS(ThisT,wxAuiNotebook), wxe_util:queue_cmd(This,Height,?get_env(),?wxAuiNotebook_SetTabCtrlHeight). -%% @doc See external documentation. -doc """ -Ensure that all tabs have the same height, even if some of them don't have -bitmaps. +Ensure that all tabs have the same height, even if some of them don't have bitmaps. -Passing ?wxDefaultSize as `size` undoes the effect of a previous call to this -function and instructs the control to use dynamic tab height. +Passing ?wxDefaultSize as `size` undoes the effect of a previous call to this function +and instructs the control to use dynamic tab height. """. -spec setUniformBitmapSize(This, Size) -> 'ok' when This::wxAuiNotebook(), Size::{W::integer(), H::integer()}. @@ -526,559 +533,376 @@ setUniformBitmapSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxAuiNotebook), wxe_util:queue_cmd(This,Size,?get_env(),?wxAuiNotebook_SetUniformBitmapSize). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxAuiNotebook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAuiNotebook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxAuiNotebookEvent.erl b/lib/wx/src/gen/wxAuiNotebookEvent.erl index fc128f4e68d3..3905ce557202 100644 --- a/lib/wx/src/gen/wxAuiNotebookEvent.erl +++ b/lib/wx/src/gen/wxAuiNotebookEvent.erl @@ -20,23 +20,28 @@ -module(wxAuiNotebookEvent). -moduledoc """ -Functions for wxAuiNotebookEvent class - This class is used by the events generated by `m:wxAuiNotebook`. -See: `m:wxAuiNotebook`, `m:wxBookCtrlEvent` +See: +* `m:wxAuiNotebook` + +* `m:wxBookCtrlEvent` + +This class is derived, and can use functions, from: + +* `m:wxBookCtrlEvent` + +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxBookCtrlEvent` -`m:wxNotifyEvent` `m:wxCommandEvent` `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxAuiNotebookEvent](https://docs.wxwidgets.org/3.1/classwx_aui_notebook_event.html) +wxWidgets docs: [wxAuiNotebookEvent](https://docs.wxwidgets.org/3.2/classwx_aui_notebook_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxAuiNotebookEventType`](`t:wxAuiNotebookEventType/0`) to subscribe to events -of this type. +Use `wxEvtHandler:connect/3` with `wxAuiNotebookEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getDragSource/1,getOldSelection/1,getSelection/1,setDragSource/2, @@ -52,7 +57,6 @@ of this type. -include("wx.hrl"). -type wxAuiNotebookEventType() :: 'command_auinotebook_page_close' | 'command_auinotebook_page_changed' | 'command_auinotebook_page_changing' | 'command_auinotebook_button' | 'command_auinotebook_begin_drag' | 'command_auinotebook_end_drag' | 'command_auinotebook_drag_motion' | 'command_auinotebook_allow_dnd' | 'command_auinotebook_tab_middle_down' | 'command_auinotebook_tab_middle_up' | 'command_auinotebook_tab_right_down' | 'command_auinotebook_tab_right_up' | 'command_auinotebook_page_closed' | 'command_auinotebook_drag_done' | 'command_auinotebook_bg_dclick'. -export_type([wxAuiNotebookEvent/0, wxAuiNotebook/0, wxAuiNotebookEventType/0]). -%% @hidden -doc false. parent_class(wxBookCtrlEvent) -> true; parent_class(wxNotifyEvent) -> true; @@ -60,7 +64,6 @@ parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Sets the selection member variable.". -spec setSelection(This, Page) -> 'ok' when This::wxAuiNotebookEvent(), Page::integer(). @@ -69,13 +72,11 @@ setSelection(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxAuiNotebookEvent), wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebookEvent_SetSelection). -%% @doc See external documentation. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note: under Windows, `getSelection/1` will return the same value as -`getOldSelection/1` when called from the `EVT_BOOKCTRL_PAGE_CHANGING` handler -and not the page which is going to be selected. +Note: under Windows, `getSelection/1` will return the same value as `getOldSelection/1` when called from the `EVT_BOOKCTRL_PAGE_CHANGING` +handler and not the page which is going to be selected. """. -spec getSelection(This) -> integer() when This::wxAuiNotebookEvent(). @@ -84,7 +85,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiNotebookEvent_GetSelection), wxe_util:rec(?wxAuiNotebookEvent_GetSelection). -%% @doc See external documentation. -doc "Sets the id of the page selected before the change.". -spec setOldSelection(This, Page) -> 'ok' when This::wxAuiNotebookEvent(), Page::integer(). @@ -93,9 +93,8 @@ setOldSelection(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxAuiNotebookEvent), wxe_util:queue_cmd(This,Page,?get_env(),?wxAuiNotebookEvent_SetOldSelection). -%% @doc See external documentation. -doc """ -Returns the page that was selected before the change, `wxNOT_FOUND` if none was +Returns the page that was selected before the change, `wxNOT\_FOUND` if none was selected. """. -spec getOldSelection(This) -> integer() when @@ -105,7 +104,7 @@ getOldSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiNotebookEvent_GetOldSelection), wxe_util:rec(?wxAuiNotebookEvent_GetOldSelection). -%% @doc See external documentation. +-doc "". -spec setDragSource(This, S) -> 'ok' when This::wxAuiNotebookEvent(), S::wxAuiNotebook:wxAuiNotebook(). setDragSource(#wx_ref{type=ThisT}=This,#wx_ref{type=ST}=S) -> @@ -113,7 +112,7 @@ setDragSource(#wx_ref{type=ThisT}=This,#wx_ref{type=ST}=S) -> ?CLASS(ST,wxAuiNotebook), wxe_util:queue_cmd(This,S,?get_env(),?wxAuiNotebookEvent_SetDragSource). -%% @doc See external documentation. +-doc "". -spec getDragSource(This) -> wxAuiNotebook:wxAuiNotebook() when This::wxAuiNotebookEvent(). getDragSource(#wx_ref{type=ThisT}=This) -> @@ -123,65 +122,45 @@ getDragSource(#wx_ref{type=ThisT}=This) -> %% From wxBookCtrlEvent %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxAuiPaneInfo.erl b/lib/wx/src/gen/wxAuiPaneInfo.erl index 66b0499217cb..4dc224a2720f 100644 --- a/lib/wx/src/gen/wxAuiPaneInfo.erl +++ b/lib/wx/src/gen/wxAuiPaneInfo.erl @@ -20,20 +20,21 @@ -module(wxAuiPaneInfo). -moduledoc """ -Functions for wxAuiPaneInfo class +`m:wxAuiPaneInfo` is part of the wxAUI class framework. -`m:wxAuiPaneInfo` is part of the wxAUI class framework. See also overview_aui. +See also overview_aui. -`m:wxAuiPaneInfo` specifies all the parameters for a pane. These parameters -specify where the pane is on the screen, whether it is docked or floating, or -hidden. In addition, these parameters specify the pane's docked position, -floating position, preferred size, minimum size, caption text among many other -parameters. +`m:wxAuiPaneInfo` specifies all the parameters for a pane. These parameters specify where +the pane is on the screen, whether it is docked or floating, or hidden. In addition, these +parameters specify the pane's docked position, floating position, preferred size, minimum +size, caption text among many other parameters. -See: `m:wxAuiManager`, `m:wxAuiDockArt` +See: +* `m:wxAuiManager` -wxWidgets docs: -[wxAuiPaneInfo](https://docs.wxwidgets.org/3.1/classwx_aui_pane_info.html) +* `m:wxAuiDockArt` + +wxWidgets docs: [wxAuiPaneInfo](https://docs.wxwidgets.org/3.2/classwx_aui_pane_info.html) """. -include("wxe.hrl"). -export([bestSize/2,bestSize/3,bottom/1,bottomDockable/1,bottomDockable/2,caption/2, @@ -60,17 +61,15 @@ wxWidgets docs: -type wxAuiPaneInfo() :: wx:wx_object(). -export_type([wxAuiPaneInfo/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxAuiPaneInfo(). new() -> wxe_util:queue_cmd(?get_env(), ?wxAuiPaneInfo_new_0), wxe_util:rec(?wxAuiPaneInfo_new_0). -%% @doc See external documentation. -doc "Copy constructor.". -spec new(C) -> wxAuiPaneInfo() when C::wxAuiPaneInfo(). @@ -79,12 +78,11 @@ new(#wx_ref{type=CT}=C) -> wxe_util:queue_cmd(C,?get_env(),?wxAuiPaneInfo_new_1), wxe_util:rec(?wxAuiPaneInfo_new_1). -%% @doc See external documentation. -doc """ `bestSize/3` sets the ideal size for the pane. -The docking manager will attempt to use this size as much as possible when -docking or floating the pane. +The docking manager will attempt to use this size as much as possible when docking or +floating the pane. """. -spec bestSize(This, Size) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Size::{W::integer(), H::integer()}. @@ -94,7 +92,7 @@ bestSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxAuiPaneInfo_BestSize_1), wxe_util:rec(?wxAuiPaneInfo_BestSize_1). -%% @doc See external documentation. +-doc "". -spec bestSize(This, X, Y) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), X::integer(), Y::integer(). bestSize(#wx_ref{type=ThisT}=This,X,Y) @@ -103,7 +101,6 @@ bestSize(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxAuiPaneInfo_BestSize_2), wxe_util:rec(?wxAuiPaneInfo_BestSize_2). -%% @doc See external documentation. -doc """ `bottom/1` sets the pane dock position to the bottom side of the frame. @@ -116,7 +113,7 @@ bottom(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Bottom), wxe_util:rec(?wxAuiPaneInfo_Bottom). -%% @equiv bottomDockable(This, []) +-doc(#{equiv => bottomDockable(This, [])}). -spec bottomDockable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -124,11 +121,7 @@ bottomDockable(This) when is_record(This, wx_ref) -> bottomDockable(This, []). -%% @doc See external documentation. --doc """ -`bottomDockable/2` indicates whether a pane can be docked at the bottom of the -frame. -""". +-doc "`bottomDockable/2` indicates whether a pane can be docked at the bottom of the frame.". -spec bottomDockable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Option :: {'b', boolean()}. @@ -141,7 +134,6 @@ bottomDockable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_BottomDockable), wxe_util:rec(?wxAuiPaneInfo_BottomDockable). -%% @doc See external documentation. -doc "`caption/2` sets the caption of the pane.". -spec caption(This, C) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), C::unicode:chardata(). @@ -152,7 +144,7 @@ caption(#wx_ref{type=ThisT}=This,C) wxe_util:queue_cmd(This,C_UC,?get_env(),?wxAuiPaneInfo_Caption), wxe_util:rec(?wxAuiPaneInfo_Caption). -%% @equiv captionVisible(This, []) +-doc(#{equiv => captionVisible(This, [])}). -spec captionVisible(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -160,7 +152,6 @@ captionVisible(This) when is_record(This, wx_ref) -> captionVisible(This, []). -%% @doc See external documentation. -doc """ CaptionVisible indicates that a pane caption should be visible. @@ -178,13 +169,12 @@ captionVisible(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_CaptionVisible), wxe_util:rec(?wxAuiPaneInfo_CaptionVisible). -%% @doc See external documentation. -doc """ -`Center()` (not implemented in wx) sets the pane dock position to the left side -of the frame. +`Center()` (not implemented in wx) sets the pane dock position to the left side of the +frame. -The centre pane is the space in the middle after all border panes (left, top, -right, bottom) are subtracted from the layout. This is the same thing as calling +The centre pane is the space in the middle after all border panes (left, top, right, +bottom) are subtracted from the layout. This is the same thing as calling Direction(wxAUI_DOCK_CENTRE). """. -spec centre(This) -> wxAuiPaneInfo() when @@ -194,13 +184,11 @@ centre(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Centre), wxe_util:rec(?wxAuiPaneInfo_Centre). -%% @doc See external documentation. -doc """ -`centrePane/1` specifies that the pane should adopt the default center pane -settings. +`centrePane/1` specifies that the pane should adopt the default center pane settings. -Centre panes usually do not have caption bars. This function provides an easy -way of preparing a pane to be displayed in the center dock position. +Centre panes usually do not have caption bars. This function provides an easy way of +preparing a pane to be displayed in the center dock position. """. -spec centrePane(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -209,7 +197,7 @@ centrePane(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_CentrePane), wxe_util:rec(?wxAuiPaneInfo_CentrePane). -%% @equiv closeButton(This, []) +-doc(#{equiv => closeButton(This, [])}). -spec closeButton(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -217,7 +205,6 @@ closeButton(This) when is_record(This, wx_ref) -> closeButton(This, []). -%% @doc See external documentation. -doc "`closeButton/2` indicates that a close button should be drawn for the pane.". -spec closeButton(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -231,7 +218,6 @@ closeButton(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_CloseButton), wxe_util:rec(?wxAuiPaneInfo_CloseButton). -%% @doc See external documentation. -doc "`defaultPane/1` specifies that the pane should adopt the default pane settings.". -spec defaultPane(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -240,7 +226,7 @@ defaultPane(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_DefaultPane), wxe_util:rec(?wxAuiPaneInfo_DefaultPane). -%% @equiv destroyOnClose(This, []) +-doc(#{equiv => destroyOnClose(This, [])}). -spec destroyOnClose(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -248,14 +234,12 @@ destroyOnClose(This) when is_record(This, wx_ref) -> destroyOnClose(This, []). -%% @doc See external documentation. -doc """ -`destroyOnClose/2` indicates whether a pane should be destroyed when it is -closed. +`destroyOnClose/2` indicates whether a pane should be destroyed when it is closed. -Normally a pane is simply hidden when the close button is clicked. Setting -DestroyOnClose to true will cause the window to be destroyed when the user -clicks the pane's close button. +Normally a pane is simply hidden when the close button is clicked. Setting DestroyOnClose +to true will cause the window to be destroyed when the user clicks the pane's close +button. """. -spec destroyOnClose(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -269,13 +253,11 @@ destroyOnClose(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_DestroyOnClose), wxe_util:rec(?wxAuiPaneInfo_DestroyOnClose). -%% @doc See external documentation. -doc """ `direction/2` determines the direction of the docked pane. -It is functionally the same as calling `left/1`, `right/1`, `top/1` or -`bottom/1`, except that docking direction may be specified programmatically via -the parameter. +It is functionally the same as calling `left/1`, `right/1`, `top/1` or `bottom/1`, except that docking direction may be +specified programmatically via the parameter. """. -spec direction(This, Direction) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Direction::integer(). @@ -285,7 +267,6 @@ direction(#wx_ref{type=ThisT}=This,Direction) wxe_util:queue_cmd(This,Direction,?get_env(),?wxAuiPaneInfo_Direction), wxe_util:rec(?wxAuiPaneInfo_Direction). -%% @doc See external documentation. -doc """ `dock/1` indicates that a pane should be docked. @@ -298,7 +279,7 @@ dock(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Dock), wxe_util:rec(?wxAuiPaneInfo_Dock). -%% @equiv dockable(This, []) +-doc(#{equiv => dockable(This, [])}). -spec dockable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -306,7 +287,6 @@ dockable(This) when is_record(This, wx_ref) -> dockable(This, []). -%% @doc See external documentation. -doc """ `dockable/2` specifies whether a frame can be docked or not. @@ -325,7 +305,6 @@ dockable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Dockable), wxe_util:rec(?wxAuiPaneInfo_Dockable). -%% @doc See external documentation. -doc """ `fixed/1` forces a pane to be fixed size so that it cannot be resized. @@ -338,7 +317,6 @@ fixed(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Fixed), wxe_util:rec(?wxAuiPaneInfo_Fixed). -%% @doc See external documentation. -doc """ `float/1` indicates that a pane should be floated. @@ -351,7 +329,7 @@ float(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Float), wxe_util:rec(?wxAuiPaneInfo_Float). -%% @equiv floatable(This, []) +-doc(#{equiv => floatable(This, [])}). -spec floatable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -359,10 +337,9 @@ floatable(This) when is_record(This, wx_ref) -> floatable(This, []). -%% @doc See external documentation. -doc """ -`floatable/2` sets whether the user will be able to undock a pane and turn it -into a floating window. +`floatable/2` sets whether the user will be able to undock a pane and turn it into a +floating window. """. -spec floatable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -376,7 +353,6 @@ floatable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Floatable), wxe_util:rec(?wxAuiPaneInfo_Floatable). -%% @doc See external documentation. -doc "`floatingPosition/3` sets the position of the floating pane.". -spec floatingPosition(This, Pos) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Pos::{X::integer(), Y::integer()}. @@ -386,7 +362,7 @@ floatingPosition(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxAuiPaneInfo_FloatingPosition_1), wxe_util:rec(?wxAuiPaneInfo_FloatingPosition_1). -%% @doc See external documentation. +-doc "". -spec floatingPosition(This, X, Y) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), X::integer(), Y::integer(). floatingPosition(#wx_ref{type=ThisT}=This,X,Y) @@ -395,7 +371,6 @@ floatingPosition(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxAuiPaneInfo_FloatingPosition_2), wxe_util:rec(?wxAuiPaneInfo_FloatingPosition_2). -%% @doc See external documentation. -doc "`floatingSize/3` sets the size of the floating pane.". -spec floatingSize(This, Size) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Size::{W::integer(), H::integer()}. @@ -405,7 +380,7 @@ floatingSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxAuiPaneInfo_FloatingSize_1), wxe_util:rec(?wxAuiPaneInfo_FloatingSize_1). -%% @doc See external documentation. +-doc "". -spec floatingSize(This, X, Y) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), X::integer(), Y::integer(). floatingSize(#wx_ref{type=ThisT}=This,X,Y) @@ -414,7 +389,7 @@ floatingSize(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxAuiPaneInfo_FloatingSize_2), wxe_util:rec(?wxAuiPaneInfo_FloatingSize_2). -%% @equiv gripper(This, []) +-doc(#{equiv => gripper(This, [])}). -spec gripper(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -422,7 +397,6 @@ gripper(This) when is_record(This, wx_ref) -> gripper(This, []). -%% @doc See external documentation. -doc "`gripper/2` indicates that a gripper should be drawn for the pane.". -spec gripper(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -436,7 +410,7 @@ gripper(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Gripper), wxe_util:rec(?wxAuiPaneInfo_Gripper). -%% @equiv gripperTop(This, []) +-doc(#{equiv => gripperTop(This, [])}). -spec gripperTop(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -444,7 +418,6 @@ gripperTop(This) when is_record(This, wx_ref) -> gripperTop(This, []). -%% @doc See external documentation. -doc "`gripperTop/2` indicates that a gripper should be drawn at the top of the pane.". -spec gripperTop(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -458,7 +431,6 @@ gripperTop(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_GripperTop), wxe_util:rec(?wxAuiPaneInfo_GripperTop). -%% @doc See external documentation. -doc "`hasBorder/1` returns true if the pane displays a border.". -spec hasBorder(This) -> boolean() when This::wxAuiPaneInfo(). @@ -467,7 +439,6 @@ hasBorder(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasBorder), wxe_util:rec(?wxAuiPaneInfo_HasBorder). -%% @doc See external documentation. -doc "`hasCaption/1` returns true if the pane displays a caption.". -spec hasCaption(This) -> boolean() when This::wxAuiPaneInfo(). @@ -476,7 +447,6 @@ hasCaption(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasCaption), wxe_util:rec(?wxAuiPaneInfo_HasCaption). -%% @doc See external documentation. -doc "`hasCloseButton/1` returns true if the pane displays a button to close the pane.". -spec hasCloseButton(This) -> boolean() when This::wxAuiPaneInfo(). @@ -485,11 +455,7 @@ hasCloseButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasCloseButton), wxe_util:rec(?wxAuiPaneInfo_HasCloseButton). -%% @doc See external documentation. --doc """ -`hasFlag/2` returns true if the property specified by flag is active for the -pane. -""". +-doc "`hasFlag/2` returns true if the property specified by flag is active for the pane.". -spec hasFlag(This, Flag) -> boolean() when This::wxAuiPaneInfo(), Flag::integer(). hasFlag(#wx_ref{type=ThisT}=This,Flag) @@ -498,7 +464,6 @@ hasFlag(#wx_ref{type=ThisT}=This,Flag) wxe_util:queue_cmd(This,Flag,?get_env(),?wxAuiPaneInfo_HasFlag), wxe_util:rec(?wxAuiPaneInfo_HasFlag). -%% @doc See external documentation. -doc "`hasGripper/1` returns true if the pane displays a gripper.". -spec hasGripper(This) -> boolean() when This::wxAuiPaneInfo(). @@ -507,7 +472,6 @@ hasGripper(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasGripper), wxe_util:rec(?wxAuiPaneInfo_HasGripper). -%% @doc See external documentation. -doc "`hasGripper/1` returns true if the pane displays a gripper at the top.". -spec hasGripperTop(This) -> boolean() when This::wxAuiPaneInfo(). @@ -516,11 +480,7 @@ hasGripperTop(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasGripperTop), wxe_util:rec(?wxAuiPaneInfo_HasGripperTop). -%% @doc See external documentation. --doc """ -`hasMaximizeButton/1` returns true if the pane displays a button to maximize the -pane. -""". +-doc "`hasMaximizeButton/1` returns true if the pane displays a button to maximize the pane.". -spec hasMaximizeButton(This) -> boolean() when This::wxAuiPaneInfo(). hasMaximizeButton(#wx_ref{type=ThisT}=This) -> @@ -528,11 +488,7 @@ hasMaximizeButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasMaximizeButton), wxe_util:rec(?wxAuiPaneInfo_HasMaximizeButton). -%% @doc See external documentation. --doc """ -`hasMinimizeButton/1` returns true if the pane displays a button to minimize the -pane. -""". +-doc "`hasMinimizeButton/1` returns true if the pane displays a button to minimize the pane.". -spec hasMinimizeButton(This) -> boolean() when This::wxAuiPaneInfo(). hasMinimizeButton(#wx_ref{type=ThisT}=This) -> @@ -540,7 +496,6 @@ hasMinimizeButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasMinimizeButton), wxe_util:rec(?wxAuiPaneInfo_HasMinimizeButton). -%% @doc See external documentation. -doc "`hasPinButton/1` returns true if the pane displays a button to float the pane.". -spec hasPinButton(This) -> boolean() when This::wxAuiPaneInfo(). @@ -549,7 +504,6 @@ hasPinButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_HasPinButton), wxe_util:rec(?wxAuiPaneInfo_HasPinButton). -%% @doc See external documentation. -doc "`hide/1` indicates that a pane should be hidden.". -spec hide(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -558,12 +512,9 @@ hide(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Hide), wxe_util:rec(?wxAuiPaneInfo_Hide). -%% @doc See external documentation. -doc """ -`isBottomDockable/1` returns true if the pane can be docked at the bottom of the -managed frame. - -See: `IsDockable()` (not implemented in wx) +`isBottomDockable/1` returns true if the pane can be docked at the bottom of the managed +frame. """. -spec isBottomDockable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -572,7 +523,6 @@ isBottomDockable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsBottomDockable), wxe_util:rec(?wxAuiPaneInfo_IsBottomDockable). -%% @doc See external documentation. -doc "`isDocked/1` returns true if the pane is currently docked.". -spec isDocked(This) -> boolean() when This::wxAuiPaneInfo(). @@ -581,7 +531,6 @@ isDocked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsDocked), wxe_util:rec(?wxAuiPaneInfo_IsDocked). -%% @doc See external documentation. -doc "`isFixed/1` returns true if the pane cannot be resized.". -spec isFixed(This) -> boolean() when This::wxAuiPaneInfo(). @@ -590,10 +539,9 @@ isFixed(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsFixed), wxe_util:rec(?wxAuiPaneInfo_IsFixed). -%% @doc See external documentation. -doc """ -`isFloatable/1` returns true if the pane can be undocked and displayed as a -floating window. +`isFloatable/1` returns true if the pane can be undocked and displayed as a floating +window. """. -spec isFloatable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -602,7 +550,6 @@ isFloatable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsFloatable), wxe_util:rec(?wxAuiPaneInfo_IsFloatable). -%% @doc See external documentation. -doc "`isFloating/1` returns true if the pane is floating.". -spec isFloating(This) -> boolean() when This::wxAuiPaneInfo(). @@ -611,12 +558,9 @@ isFloating(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsFloating), wxe_util:rec(?wxAuiPaneInfo_IsFloating). -%% @doc See external documentation. -doc """ -`isLeftDockable/1` returns true if the pane can be docked on the left of the -managed frame. - -See: `IsDockable()` (not implemented in wx) +`isLeftDockable/1` returns true if the pane can be docked on the left of the managed +frame. """. -spec isLeftDockable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -625,10 +569,9 @@ isLeftDockable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsLeftDockable), wxe_util:rec(?wxAuiPaneInfo_IsLeftDockable). -%% @doc See external documentation. -doc """ -IsMoveable() returns true if the docked frame can be undocked or moved to -another dock position. +IsMoveable() returns true if the docked frame can be undocked or moved to another dock +position. """. -spec isMovable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -637,7 +580,6 @@ isMovable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsMovable), wxe_util:rec(?wxAuiPaneInfo_IsMovable). -%% @doc See external documentation. -doc """ `isOk/1` returns true if the `m:wxAuiPaneInfo` structure is valid. @@ -650,7 +592,6 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsOk), wxe_util:rec(?wxAuiPaneInfo_IsOk). -%% @doc See external documentation. -doc "`isResizable/1` returns true if the pane can be resized.". -spec isResizable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -659,12 +600,9 @@ isResizable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsResizable), wxe_util:rec(?wxAuiPaneInfo_IsResizable). -%% @doc See external documentation. -doc """ -`isRightDockable/1` returns true if the pane can be docked on the right of the -managed frame. - -See: `IsDockable()` (not implemented in wx) +`isRightDockable/1` returns true if the pane can be docked on the right of the managed +frame. """. -spec isRightDockable(This) -> boolean() when This::wxAuiPaneInfo(). @@ -673,7 +611,6 @@ isRightDockable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsRightDockable), wxe_util:rec(?wxAuiPaneInfo_IsRightDockable). -%% @doc See external documentation. -doc "`isShown/1` returns true if the pane is currently shown.". -spec isShown(This) -> boolean() when This::wxAuiPaneInfo(). @@ -682,7 +619,6 @@ isShown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsShown), wxe_util:rec(?wxAuiPaneInfo_IsShown). -%% @doc See external documentation. -doc "`isToolbar/1` returns true if the pane contains a toolbar.". -spec isToolbar(This) -> boolean() when This::wxAuiPaneInfo(). @@ -691,13 +627,7 @@ isToolbar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsToolbar), wxe_util:rec(?wxAuiPaneInfo_IsToolbar). -%% @doc See external documentation. --doc """ -`isTopDockable/1` returns true if the pane can be docked at the top of the -managed frame. - -See: `IsDockable()` (not implemented in wx) -""". +-doc "`isTopDockable/1` returns true if the pane can be docked at the top of the managed frame.". -spec isTopDockable(This) -> boolean() when This::wxAuiPaneInfo(). isTopDockable(#wx_ref{type=ThisT}=This) -> @@ -705,13 +635,12 @@ isTopDockable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_IsTopDockable), wxe_util:rec(?wxAuiPaneInfo_IsTopDockable). -%% @doc See external documentation. -doc """ `layer/2` determines the layer of the docked pane. -The dock layer is similar to an onion, the inner-most layer being layer 0. Each -shell moving in the outward direction has a higher layer number. This allows for -more complex docking layout formation. +The dock layer is similar to an onion, the inner-most layer being layer 0. Each shell +moving in the outward direction has a higher layer number. This allows for more complex +docking layout formation. """. -spec layer(This, Layer) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Layer::integer(). @@ -721,7 +650,6 @@ layer(#wx_ref{type=ThisT}=This,Layer) wxe_util:queue_cmd(This,Layer,?get_env(),?wxAuiPaneInfo_Layer), wxe_util:rec(?wxAuiPaneInfo_Layer). -%% @doc See external documentation. -doc """ `left/1` sets the pane dock position to the left side of the frame. @@ -734,7 +662,7 @@ left(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Left), wxe_util:rec(?wxAuiPaneInfo_Left). -%% @equiv leftDockable(This, []) +-doc(#{equiv => leftDockable(This, [])}). -spec leftDockable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -742,11 +670,7 @@ leftDockable(This) when is_record(This, wx_ref) -> leftDockable(This, []). -%% @doc See external documentation. --doc """ -`leftDockable/2` indicates whether a pane can be docked on the left of the -frame. -""". +-doc "`leftDockable/2` indicates whether a pane can be docked on the left of the frame.". -spec leftDockable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Option :: {'b', boolean()}. @@ -759,7 +683,6 @@ leftDockable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_LeftDockable), wxe_util:rec(?wxAuiPaneInfo_LeftDockable). -%% @doc See external documentation. -doc "`maxSize/3` sets the maximum size of the pane.". -spec maxSize(This, Size) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Size::{W::integer(), H::integer()}. @@ -769,7 +692,7 @@ maxSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxAuiPaneInfo_MaxSize_1), wxe_util:rec(?wxAuiPaneInfo_MaxSize_1). -%% @doc See external documentation. +-doc "". -spec maxSize(This, X, Y) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), X::integer(), Y::integer(). maxSize(#wx_ref{type=ThisT}=This,X,Y) @@ -778,7 +701,7 @@ maxSize(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxAuiPaneInfo_MaxSize_2), wxe_util:rec(?wxAuiPaneInfo_MaxSize_2). -%% @equiv maximizeButton(This, []) +-doc(#{equiv => maximizeButton(This, [])}). -spec maximizeButton(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -786,11 +709,7 @@ maximizeButton(This) when is_record(This, wx_ref) -> maximizeButton(This, []). -%% @doc See external documentation. --doc """ -`maximizeButton/2` indicates that a maximize button should be drawn for the -pane. -""". +-doc "`maximizeButton/2` indicates that a maximize button should be drawn for the pane.". -spec maximizeButton(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Option :: {'visible', boolean()}. @@ -803,7 +722,6 @@ maximizeButton(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_MaximizeButton), wxe_util:rec(?wxAuiPaneInfo_MaximizeButton). -%% @doc See external documentation. -doc """ `minSize/3` sets the minimum size of the pane. @@ -817,7 +735,7 @@ minSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxAuiPaneInfo_MinSize_1), wxe_util:rec(?wxAuiPaneInfo_MinSize_1). -%% @doc See external documentation. +-doc "". -spec minSize(This, X, Y) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), X::integer(), Y::integer(). minSize(#wx_ref{type=ThisT}=This,X,Y) @@ -826,7 +744,7 @@ minSize(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxAuiPaneInfo_MinSize_2), wxe_util:rec(?wxAuiPaneInfo_MinSize_2). -%% @equiv minimizeButton(This, []) +-doc(#{equiv => minimizeButton(This, [])}). -spec minimizeButton(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -834,11 +752,7 @@ minimizeButton(This) when is_record(This, wx_ref) -> minimizeButton(This, []). -%% @doc See external documentation. --doc """ -`minimizeButton/2` indicates that a minimize button should be drawn for the -pane. -""". +-doc "`minimizeButton/2` indicates that a minimize button should be drawn for the pane.". -spec minimizeButton(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Option :: {'visible', boolean()}. @@ -851,7 +765,7 @@ minimizeButton(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_MinimizeButton), wxe_util:rec(?wxAuiPaneInfo_MinimizeButton). -%% @equiv movable(This, []) +-doc(#{equiv => movable(This, [])}). -spec movable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -859,7 +773,6 @@ movable(This) when is_record(This, wx_ref) -> movable(This, []). -%% @doc See external documentation. -doc "Movable indicates whether a frame can be moved.". -spec movable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -873,12 +786,11 @@ movable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Movable), wxe_util:rec(?wxAuiPaneInfo_Movable). -%% @doc See external documentation. -doc """ `name/2` sets the name of the pane so it can be referenced in lookup functions. -If a name is not specified by the user, a random name is assigned to the pane -when it is added to the manager. +If a name is not specified by the user, a random name is assigned to the pane when it is +added to the manager. """. -spec name(This, N) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), N::unicode:chardata(). @@ -889,7 +801,7 @@ name(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N_UC,?get_env(),?wxAuiPaneInfo_Name), wxe_util:rec(?wxAuiPaneInfo_Name). -%% @equiv paneBorder(This, []) +-doc(#{equiv => paneBorder(This, [])}). -spec paneBorder(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -897,7 +809,6 @@ paneBorder(This) when is_record(This, wx_ref) -> paneBorder(This, []). -%% @doc See external documentation. -doc "PaneBorder indicates that a border should be drawn for the pane.". -spec paneBorder(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -911,7 +822,7 @@ paneBorder(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_PaneBorder), wxe_util:rec(?wxAuiPaneInfo_PaneBorder). -%% @equiv pinButton(This, []) +-doc(#{equiv => pinButton(This, [])}). -spec pinButton(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -919,7 +830,6 @@ pinButton(This) when is_record(This, wx_ref) -> pinButton(This, []). -%% @doc See external documentation. -doc "`pinButton/2` indicates that a pin button should be drawn for the pane.". -spec pinButton(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -933,7 +843,6 @@ pinButton(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_PinButton), wxe_util:rec(?wxAuiPaneInfo_PinButton). -%% @doc See external documentation. -doc "`position/2` determines the position of the docked pane.". -spec position(This, Pos) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Pos::integer(). @@ -943,7 +852,7 @@ position(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxAuiPaneInfo_Position), wxe_util:rec(?wxAuiPaneInfo_Position). -%% @equiv resizable(This, []) +-doc(#{equiv => resizable(This, [])}). -spec resizable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -951,10 +860,9 @@ resizable(This) when is_record(This, wx_ref) -> resizable(This, []). -%% @doc See external documentation. -doc """ -`resizable/2` allows a pane to be resized if the parameter is true, and forces -it to be a fixed size if the parameter is false. +`resizable/2` allows a pane to be resized if the parameter is true, and forces it to be a +fixed size if the parameter is false. This is simply an antonym for `fixed/1`. """. @@ -970,7 +878,6 @@ resizable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Resizable), wxe_util:rec(?wxAuiPaneInfo_Resizable). -%% @doc See external documentation. -doc """ `right/1` sets the pane dock position to the right side of the frame. @@ -983,7 +890,7 @@ right(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Right), wxe_util:rec(?wxAuiPaneInfo_Right). -%% @equiv rightDockable(This, []) +-doc(#{equiv => rightDockable(This, [])}). -spec rightDockable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -991,11 +898,7 @@ rightDockable(This) when is_record(This, wx_ref) -> rightDockable(This, []). -%% @doc See external documentation. --doc """ -`rightDockable/2` indicates whether a pane can be docked on the right of the -frame. -""". +-doc "`rightDockable/2` indicates whether a pane can be docked on the right of the frame.". -spec rightDockable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Option :: {'b', boolean()}. @@ -1008,7 +911,6 @@ rightDockable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_RightDockable), wxe_util:rec(?wxAuiPaneInfo_RightDockable). -%% @doc See external documentation. -doc "`row/2` determines the row of the docked pane.". -spec row(This, Row) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Row::integer(). @@ -1018,13 +920,12 @@ row(#wx_ref{type=ThisT}=This,Row) wxe_util:queue_cmd(This,Row,?get_env(),?wxAuiPaneInfo_Row), wxe_util:rec(?wxAuiPaneInfo_Row). -%% @doc See external documentation. -doc """ Write the safe parts of a PaneInfo object "source" into "this". -"Safe parts" are all non-UI elements (e.g. all layout determining parameters -like the size, position etc.). "Unsafe parts" (pointers to button, frame and -window) are not modified by this write operation. +"Safe parts" are all non-UI elements (e.g. all layout determining parameters like the +size, position etc.). "Unsafe parts" (pointers to button, frame and window) are not +modified by this write operation. Remark: This method is used when loading perspectives. """. @@ -1035,11 +936,7 @@ safeSet(#wx_ref{type=ThisT}=This,#wx_ref{type=SourceT}=Source) -> ?CLASS(SourceT,wxAuiPaneInfo), wxe_util:queue_cmd(This,Source,?get_env(),?wxAuiPaneInfo_SafeSet). -%% @doc See external documentation. --doc """ -`setFlag/3` turns the property given by flag on or off with the option_state -parameter. -""". +-doc "`setFlag/3` turns the property given by flag on or off with the option\_state parameter.". -spec setFlag(This, Flag, Option_state) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), Flag::integer(), Option_state::boolean(). setFlag(#wx_ref{type=ThisT}=This,Flag,Option_state) @@ -1048,7 +945,7 @@ setFlag(#wx_ref{type=ThisT}=This,Flag,Option_state) wxe_util:queue_cmd(This,Flag,Option_state,?get_env(),?wxAuiPaneInfo_SetFlag), wxe_util:rec(?wxAuiPaneInfo_SetFlag). -%% @equiv show(This, []) +-doc(#{equiv => show(This, [])}). -spec show(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -1056,7 +953,6 @@ show(This) when is_record(This, wx_ref) -> show(This, []). -%% @doc See external documentation. -doc "`show/2` indicates that a pane should be shown.". -spec show(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -1070,11 +966,7 @@ show(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_Show), wxe_util:rec(?wxAuiPaneInfo_Show). -%% @doc See external documentation. --doc """ -`toolbarPane/1` specifies that the pane should adopt the default toolbar pane -settings. -""". +-doc "`toolbarPane/1` specifies that the pane should adopt the default toolbar pane settings.". -spec toolbarPane(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). toolbarPane(#wx_ref{type=ThisT}=This) -> @@ -1082,7 +974,6 @@ toolbarPane(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_ToolbarPane), wxe_util:rec(?wxAuiPaneInfo_ToolbarPane). -%% @doc See external documentation. -doc """ `top/1` sets the pane dock position to the top of the frame. @@ -1095,7 +986,7 @@ top(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_Top), wxe_util:rec(?wxAuiPaneInfo_Top). -%% @equiv topDockable(This, []) +-doc(#{equiv => topDockable(This, [])}). -spec topDockable(This) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(). @@ -1103,7 +994,6 @@ topDockable(This) when is_record(This, wx_ref) -> topDockable(This, []). -%% @doc See external documentation. -doc "`topDockable/2` indicates whether a pane can be docked at the top of the frame.". -spec topDockable(This, [Option]) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), @@ -1117,13 +1007,11 @@ topDockable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxAuiPaneInfo_TopDockable), wxe_util:rec(?wxAuiPaneInfo_TopDockable). -%% @doc See external documentation. -doc """ `window/2` assigns the window pointer that the `m:wxAuiPaneInfo` should use. -This normally does not need to be specified, as the window pointer is -automatically assigned to the `m:wxAuiPaneInfo` structure as soon as it is added -to the manager. +This normally does not need to be specified, as the window pointer is automatically +assigned to the `m:wxAuiPaneInfo` structure as soon as it is added to the manager. """. -spec window(This, W) -> wxAuiPaneInfo() when This::wxAuiPaneInfo(), W::wxWindow:wxWindow(). @@ -1133,7 +1021,7 @@ window(#wx_ref{type=ThisT}=This,#wx_ref{type=WT}=W) -> wxe_util:queue_cmd(This,W,?get_env(),?wxAuiPaneInfo_Window), wxe_util:rec(?wxAuiPaneInfo_Window). -%% @doc See external documentation. +-doc "". -spec getWindow(This) -> wxWindow:wxWindow() when This::wxAuiPaneInfo(). getWindow(#wx_ref{type=ThisT}=This) -> @@ -1141,7 +1029,7 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetWindow), wxe_util:rec(?wxAuiPaneInfo_GetWindow). -%% @doc See external documentation. +-doc "". -spec getFrame(This) -> wxFrame:wxFrame() when This::wxAuiPaneInfo(). getFrame(#wx_ref{type=ThisT}=This) -> @@ -1149,7 +1037,7 @@ getFrame(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetFrame), wxe_util:rec(?wxAuiPaneInfo_GetFrame). -%% @doc See external documentation. +-doc "". -spec getDirection(This) -> integer() when This::wxAuiPaneInfo(). getDirection(#wx_ref{type=ThisT}=This) -> @@ -1157,7 +1045,7 @@ getDirection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetDirection), wxe_util:rec(?wxAuiPaneInfo_GetDirection). -%% @doc See external documentation. +-doc "". -spec getLayer(This) -> integer() when This::wxAuiPaneInfo(). getLayer(#wx_ref{type=ThisT}=This) -> @@ -1165,7 +1053,7 @@ getLayer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetLayer), wxe_util:rec(?wxAuiPaneInfo_GetLayer). -%% @doc See external documentation. +-doc "". -spec getRow(This) -> integer() when This::wxAuiPaneInfo(). getRow(#wx_ref{type=ThisT}=This) -> @@ -1173,7 +1061,7 @@ getRow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetRow), wxe_util:rec(?wxAuiPaneInfo_GetRow). -%% @doc See external documentation. +-doc "". -spec getPosition(This) -> integer() when This::wxAuiPaneInfo(). getPosition(#wx_ref{type=ThisT}=This) -> @@ -1181,7 +1069,7 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetPosition), wxe_util:rec(?wxAuiPaneInfo_GetPosition). -%% @doc See external documentation. +-doc "". -spec getFloatingPosition(This) -> {X::integer(), Y::integer()} when This::wxAuiPaneInfo(). getFloatingPosition(#wx_ref{type=ThisT}=This) -> @@ -1189,7 +1077,7 @@ getFloatingPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetFloatingPosition), wxe_util:rec(?wxAuiPaneInfo_GetFloatingPosition). -%% @doc See external documentation. +-doc "". -spec getFloatingSize(This) -> {W::integer(), H::integer()} when This::wxAuiPaneInfo(). getFloatingSize(#wx_ref{type=ThisT}=This) -> @@ -1197,8 +1085,7 @@ getFloatingSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxAuiPaneInfo_GetFloatingSize), wxe_util:rec(?wxAuiPaneInfo_GetFloatingSize). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxAuiPaneInfo()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAuiPaneInfo), diff --git a/lib/wx/src/gen/wxAuiSimpleTabArt.erl b/lib/wx/src/gen/wxAuiSimpleTabArt.erl index 411975f6a223..7e98044d5c81 100644 --- a/lib/wx/src/gen/wxAuiSimpleTabArt.erl +++ b/lib/wx/src/gen/wxAuiSimpleTabArt.erl @@ -20,18 +20,17 @@ -module(wxAuiSimpleTabArt). -moduledoc """ -Functions for wxAuiSimpleTabArt class - Another standard tab art provider for `m:wxAuiNotebook`. -`m:wxAuiSimpleTabArt` is derived from `m:wxAuiTabArt` demonstrating how to write -a completely new tab art class. It can also be used as alternative to -`wxAuiDefaultTabArt` (not implemented in wx). +`m:wxAuiSimpleTabArt` is derived from `m:wxAuiTabArt` demonstrating how to write a +completely new tab art class. It can also be used as alternative to `wxAuiDefaultTabArt` +(not implemented in wx). + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxAuiTabArt` +* `m:wxAuiTabArt` -wxWidgets docs: -[wxAuiSimpleTabArt](https://docs.wxwidgets.org/3.1/classwx_aui_simple_tab_art.html) +wxWidgets docs: [wxAuiSimpleTabArt](https://docs.wxwidgets.org/3.2/classwx_aui_simple_tab_art.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -42,40 +41,32 @@ wxWidgets docs: -type wxAuiSimpleTabArt() :: wx:wx_object(). -export_type([wxAuiSimpleTabArt/0]). -%% @hidden -doc false. parent_class(wxAuiTabArt) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxAuiSimpleTabArt(). new() -> wxe_util:queue_cmd(?get_env(), ?wxAuiSimpleTabArt_new), wxe_util:rec(?wxAuiSimpleTabArt_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxAuiSimpleTabArt()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxAuiSimpleTabArt), wxe_util:queue_cmd(Obj, ?get_env(), ?wxAuiSimpleTabArt_destroy), ok. %% From wxAuiTabArt -%% @hidden -doc false. setActiveColour(This,Colour) -> wxAuiTabArt:setActiveColour(This,Colour). -%% @hidden -doc false. setColour(This,Colour) -> wxAuiTabArt:setColour(This,Colour). -%% @hidden -doc false. setSelectedFont(This,Font) -> wxAuiTabArt:setSelectedFont(This,Font). -%% @hidden -doc false. setNormalFont(This,Font) -> wxAuiTabArt:setNormalFont(This,Font). -%% @hidden -doc false. setMeasuringFont(This,Font) -> wxAuiTabArt:setMeasuringFont(This,Font). -%% @hidden -doc false. setFlags(This,Flags) -> wxAuiTabArt:setFlags(This,Flags). diff --git a/lib/wx/src/gen/wxAuiTabArt.erl b/lib/wx/src/gen/wxAuiTabArt.erl index a53096076870..c84017b1398e 100644 --- a/lib/wx/src/gen/wxAuiTabArt.erl +++ b/lib/wx/src/gen/wxAuiTabArt.erl @@ -20,25 +20,20 @@ -module(wxAuiTabArt). -moduledoc """ -Functions for wxAuiTabArt class - Tab art provider defines all the drawing functions used by `m:wxAuiNotebook`. This allows the `m:wxAuiNotebook` to have a pluggable look-and-feel. -By default, a `m:wxAuiNotebook` uses an instance of this class called -`wxAuiDefaultTabArt` (not implemented in wx) which provides bitmap art and a -colour scheme that is adapted to the major platforms' look. You can either -derive from that class to alter its behaviour or write a completely new tab art -class. +By default, a `m:wxAuiNotebook` uses an instance of this class called `wxAuiDefaultTabArt` +(not implemented in wx) which provides bitmap art and a colour scheme that is adapted to +the major platforms' look. You can either derive from that class to alter its behaviour or +write a completely new tab art class. -Another example of creating a new `m:wxAuiNotebook` tab bar is -`m:wxAuiSimpleTabArt`. +Another example of creating a new `m:wxAuiNotebook` tab bar is `m:wxAuiSimpleTabArt`. Call `wxAuiNotebook:setArtProvider/2` to make use of this new tab art. -wxWidgets docs: -[wxAuiTabArt](https://docs.wxwidgets.org/3.1/classwx_aui_tab_art.html) +wxWidgets docs: [wxAuiTabArt](https://docs.wxwidgets.org/3.2/classwx_aui_tab_art.html) """. -include("wxe.hrl"). -export([setActiveColour/2,setColour/2,setFlags/2,setMeasuringFont/2,setNormalFont/2, @@ -49,11 +44,9 @@ wxWidgets docs: -type wxAuiTabArt() :: wx:wx_object(). -export_type([wxAuiTabArt/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Sets flags.". -spec setFlags(This, Flags) -> 'ok' when This::wxAuiTabArt(), Flags::integer(). @@ -62,7 +55,6 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxAuiTabArt), wxe_util:queue_cmd(This,Flags,?get_env(),?wxAuiTabArt_SetFlags). -%% @doc See external documentation. -doc "Sets the font used for calculating measurements.". -spec setMeasuringFont(This, Font) -> 'ok' when This::wxAuiTabArt(), Font::wxFont:wxFont(). @@ -71,7 +63,6 @@ setMeasuringFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxAuiTabArt_SetMeasuringFont). -%% @doc See external documentation. -doc "Sets the normal font for drawing labels.". -spec setNormalFont(This, Font) -> 'ok' when This::wxAuiTabArt(), Font::wxFont:wxFont(). @@ -80,7 +71,6 @@ setNormalFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxAuiTabArt_SetNormalFont). -%% @doc See external documentation. -doc "Sets the font for drawing text for selected UI elements.". -spec setSelectedFont(This, Font) -> 'ok' when This::wxAuiTabArt(), Font::wxFont:wxFont(). @@ -89,7 +79,6 @@ setSelectedFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxAuiTabArt_SetSelectedFont). -%% @doc See external documentation. -doc """ Sets the colour of the inactive tabs. @@ -102,7 +91,6 @@ setColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxAuiTabArt), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxAuiTabArt_SetColour). -%% @doc See external documentation. -doc """ Sets the colour of the selected tab. diff --git a/lib/wx/src/gen/wxBitmap.erl b/lib/wx/src/gen/wxBitmap.erl index 2f301032ee17..f709bc0db3a9 100644 --- a/lib/wx/src/gen/wxBitmap.erl +++ b/lib/wx/src/gen/wxBitmap.erl @@ -20,48 +20,60 @@ -module(wxBitmap). -moduledoc """ -Functions for wxBitmap class - -This class encapsulates the concept of a platform-dependent bitmap, either -monochrome or colour or colour with alpha channel support. - -If you need direct access the bitmap data instead going through drawing to it -using `m:wxMemoryDC` you need to use the `wxPixelData` (not implemented in wx) -class (either wxNativePixelData for RGB bitmaps or wxAlphaPixelData for bitmaps -with an additionally alpha channel). - -Note that many `m:wxBitmap` functions take a `type` parameter, which is a value -of the ?wxBitmapType enumeration. The validity of those values depends however -on the platform where your program is running and from the wxWidgets -configuration. If all possible wxWidgets settings are used: - -In addition, `m:wxBitmap` can load and save all formats that `m:wxImage` can; -see `m:wxImage` for more info. Of course, you must have loaded the `m:wxImage` -handlers (see ?wxInitAllImageHandlers() and `wxImage::AddHandler` (not -implemented in wx)). Note that all available wxBitmapHandlers for a given -wxWidgets port are automatically loaded at startup so you won't need to use -`wxBitmap::AddHandler` (not implemented in wx). - -More on the difference between `m:wxImage` and `m:wxBitmap`: `m:wxImage` is just -a buffer of RGB bytes with an optional buffer for the alpha bytes. It is all -generic, platform independent and image file format independent code. It -includes generic code for scaling, resizing, clipping, and other manipulations -of the image data. OTOH, `m:wxBitmap` is intended to be a wrapper of whatever is -the native image format that is quickest/easiest to draw to a DC or to be the -target of the drawing operations performed on a `m:wxMemoryDC`. By splitting the -responsibilities between wxImage/wxBitmap like this then it's easier to use -generic code shared by all platforms and image types for generic operations and +This class encapsulates the concept of a platform-dependent bitmap, either monochrome or +colour or colour with alpha channel support. + +If you need direct access the bitmap data instead going through drawing to it using `m:wxMemoryDC` +you need to use the `wxPixelData` (not implemented in wx) class (either wxNativePixelData +for RGB bitmaps or wxAlphaPixelData for bitmaps with an additionally alpha channel). + +Note that many `m:wxBitmap` functions take a `type` parameter, which is a value of the +?wxBitmapType enumeration. The validity of those values depends however on the platform +where your program is running and from the wxWidgets configuration. If all possible +wxWidgets settings are used: + +* wxMSW supports BMP and ICO files, BMP and ICO resources; + +* wxGTK supports any file supported by gdk-pixbuf; + +* wxMac supports PICT resources; + +* wxX11 supports XPM files, XPM data, XBM data; + +In addition, `m:wxBitmap` can load and save all formats that `m:wxImage` can; see `m:wxImage` +for more info. Of course, you must have loaded the `m:wxImage` handlers (see +?wxInitAllImageHandlers() and `wxImage::AddHandler` (not implemented in wx)). Note that +all available wxBitmapHandlers for a given wxWidgets port are automatically loaded at +startup so you won't need to use `wxBitmap::AddHandler` (not implemented in wx). + +More on the difference between `m:wxImage` and `m:wxBitmap`: `m:wxImage` is just a buffer +of RGB bytes with an optional buffer for the alpha bytes. It is all generic, platform +independent and image file format independent code. It includes generic code for scaling, +resizing, clipping, and other manipulations of the image data. OTOH, `m:wxBitmap` is +intended to be a wrapper of whatever is the native image format that is quickest/easiest +to draw to a DC or to be the target of the drawing operations performed on a `m:wxMemoryDC`. +By splitting the responsibilities between wxImage/wxBitmap like this then it's easier to +use generic code shared by all platforms and image types for generic operations and platform specific code where performance or compatibility is needed. Predefined objects (include wx.hrl): ?wxNullBitmap See: -[Overview bitmap](https://docs.wxwidgets.org/3.1/overview_bitmap.html#overview_bitmap), -[Overview bitmap](https://docs.wxwidgets.org/3.1/overview_bitmap.html#overview_bitmap_supportedformats), -`wxDC:blit/6`, `m:wxIcon`, `m:wxCursor`, `m:wxMemoryDC`, `m:wxImage`, -`wxPixelData` (not implemented in wx) +* [Overview bitmap](https://docs.wxwidgets.org/3.2/overview_bitmap.html#overview_bitmap) -wxWidgets docs: [wxBitmap](https://docs.wxwidgets.org/3.1/classwx_bitmap.html) +* [Overview bitmap](https://docs.wxwidgets.org/3.2/overview_bitmap.html#overview_bitmap_supportedformats) + +* `wxDC:blit/6` + +* `m:wxIcon` + +* `m:wxCursor` + +* `m:wxMemoryDC` + +* `m:wxImage` + +wxWidgets docs: [wxBitmap](https://docs.wxwidgets.org/3.2/classwx_bitmap.html) """. -include("wxe.hrl"). -export([convertToImage/1,copyFromIcon/2,create/2,create/3,create/4,destroy/1, @@ -74,30 +86,22 @@ wxWidgets docs: [wxBitmap](https://docs.wxwidgets.org/3.1/classwx_bitmap.html) -type wxBitmap() :: wx:wx_object(). -export_type([wxBitmap/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. -Constructs a bitmap object with no data; an assignment or another member -function such as `create/4` or `loadFile/3` must be called subsequently. +Constructs a bitmap object with no data; an assignment or another member function such as `create/4` +or `loadFile/3` must be called subsequently. """. -spec new() -> wxBitmap(). new() -> wxe_util:queue_cmd(?get_env(), ?wxBitmap_new_0), wxe_util:rec(?wxBitmap_new_0). -%% @doc See external documentation. -%%
Also:
-%% new(Sz) -> wxBitmap() when
-%% Sz::{W::integer(), H::integer()};
-%% (Img) -> wxBitmap() when
-%% Img::wxImage:wxImage() | wxBitmap:wxBitmap().
-%% -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY +-doc "". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Name) -> wxBitmap() when Name::unicode:chardata(); (Sz) -> wxBitmap() when @@ -123,33 +127,20 @@ new(#wx_ref{type=ImgT}=Img) -> wxe_util:queue_cmd(wx:typeCast(Img, ImgType),?get_env(),?wxBitmap_new_2_3), wxe_util:rec(?wxBitmap_new_2_3). -%% @doc See external documentation. -%%
Also:
-%% new(Name, [Option]) -> wxBitmap() when
-%% Name::unicode:chardata(),
-%% Option :: {'type', wx:wx_enum()};
-%% (Sz, [Option]) -> wxBitmap() when
-%% Sz::{W::integer(), H::integer()},
-%% Option :: {'depth', integer()};
-%% (Img, [Option]) -> wxBitmap() when
-%% Img::wxImage:wxImage(),
-%% Option :: {'depth', integer()}.
-%% -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Creates this bitmap object from the given image. -This has to be done to actually display an image as you cannot draw an image -directly on a window. +This has to be done to actually display an image as you cannot draw an image directly on +a window. -The resulting bitmap will use the provided colour depth (or that of the current -system if depth is ?wxBITMAP_SCREEN_DEPTH) which entails that a colour reduction -may take place. +The resulting bitmap will use the provided colour depth (or that of the current system if +depth is ?wxBITMAP\_SCREEN\_DEPTH) which entails that a colour reduction may take place. -On Windows, if there is a palette present (set with SetPalette), it will be used -when creating the `m:wxBitmap` (most useful in 8-bit display mode). On other -platforms, the palette is currently ignored. +On Windows, if there is a palette present (set with SetPalette), it will be used when +creating the `m:wxBitmap` (most useful in 8-bit display mode). On other platforms, the +palette is currently ignored. """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Width, Height) -> wxBitmap() when Width::integer(), Height::integer(); (Name, [Option]) -> wxBitmap() when @@ -189,20 +180,13 @@ new(#wx_ref{type=ImgT}=Img, Options) wxe_util:queue_cmd(Img, Opts,?get_env(),?wxBitmap_new_2_2), wxe_util:rec(?wxBitmap_new_2_2). -%% @doc See external documentation. -%%
Also:
-%% new(Width, Height, [Option]) -> wxBitmap() when
-%% Width::integer(), Height::integer(),
-%% Option :: {'depth', integer()}.
-%% -doc """ Creates a new bitmap. -A depth of ?wxBITMAP_SCREEN_DEPTH indicates the depth of the current screen or -visual. +A depth of ?wxBITMAP\_SCREEN\_DEPTH indicates the depth of the current screen or visual. -Some platforms only support 1 for monochrome and ?wxBITMAP_SCREEN_DEPTH for the -current colour setting. +Some platforms only support 1 for monochrome and ?wxBITMAP\_SCREEN\_DEPTH for the current +colour setting. A depth of 32 including an alpha channel is supported under MSW, Mac and GTK+. """. @@ -223,17 +207,16 @@ new(Width,Height, Options) wxe_util:queue_cmd(Width,Height, Opts,?get_env(),?wxBitmap_new_3), wxe_util:rec(?wxBitmap_new_3). -%% @doc See external documentation. -doc """ Creates a bitmap from the given array `bits`. -You should only use this function for monochrome bitmaps (depth 1) in portable -programs: in this case the bits parameter should contain an XBM image. +You should only use this function for monochrome bitmaps (depth 1) in portable programs: +in this case the bits parameter should contain an XBM image. -For other bit depths, the behaviour is platform dependent: under Windows, the -data is passed without any changes to the underlying CreateBitmap() API. Under -other platforms, only monochrome bitmaps may be created using this constructor -and `m:wxImage` should be used for creating colour bitmaps from static data. +For other bit depths, the behaviour is platform dependent: under Windows, the data is +passed without any changes to the underlying CreateBitmap() API. Under other platforms, +only monochrome bitmaps may be created using this constructor and `m:wxImage` should be +used for creating colour bitmaps from static data. """. -spec new(Bits, Width, Height, [Option]) -> wxBitmap() when Bits::binary(), Width::integer(), Height::integer(), @@ -246,12 +229,11 @@ new(Bits,Width,Height, Options) wxe_util:queue_cmd(Bits,Width,Height, Opts,?get_env(),?wxBitmap_new_4), wxe_util:rec(?wxBitmap_new_4). -%% @doc See external documentation. -doc """ Creates an image from a platform-dependent bitmap. -This preserves mask information so that bitmaps and images can be converted back -and forth without loss in that respect. +This preserves mask information so that bitmaps and images can be converted back and +forth without loss in that respect. """. -spec convertToImage(This) -> wxImage:wxImage() when This::wxBitmap(). @@ -260,7 +242,6 @@ convertToImage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_ConvertToImage), wxe_util:rec(?wxBitmap_ConvertToImage). -%% @doc See external documentation. -doc "Creates the bitmap from an icon.". -spec copyFromIcon(This, Icon) -> boolean() when This::wxBitmap(), Icon::wxIcon:wxIcon(). @@ -270,7 +251,7 @@ copyFromIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon) -> wxe_util:queue_cmd(This,Icon,?get_env(),?wxBitmap_CopyFromIcon), wxe_util:rec(?wxBitmap_CopyFromIcon). -%% @equiv create(This,Sz, []) +-doc(#{equiv => create(This,Sz, [])}). -spec create(This, Sz) -> boolean() when This::wxBitmap(), Sz::{W::integer(), H::integer()}. @@ -278,15 +259,9 @@ create(This,{SzW,SzH} = Sz) when is_record(This, wx_ref),is_integer(SzW),is_integer(SzH) -> create(This,Sz, []). -%% @doc See external documentation. -%%
Also:
-%% create(This, Sz, [Option]) -> boolean() when
-%% This::wxBitmap(), Sz::{W::integer(), H::integer()},
-%% Option :: {'depth', integer()}.
-%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec create(This, Width, Height) -> boolean() when This::wxBitmap(), Width::integer(), Height::integer(); @@ -306,14 +281,8 @@ create(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz, Options) wxe_util:queue_cmd(This,Sz, Opts,?get_env(),?wxBitmap_Create_2), wxe_util:rec(?wxBitmap_Create_2). -%% @doc See external documentation. -%%
Also:
-%% create(This, Width, Height, Dc) -> boolean() when
-%% This::wxBitmap(), Width::integer(), Height::integer(), Dc::wxDC:wxDC().
-%% -doc """ -Create a bitmap compatible with the given DC, inheriting its magnification -factor. +Create a bitmap compatible with the given DC, inheriting its magnification factor. Return: true if the creation was successful. @@ -339,7 +308,6 @@ create(#wx_ref{type=ThisT}=This,Width,Height,#wx_ref{type=DcT}=Dc) wxe_util:queue_cmd(This,Width,Height,Dc,?get_env(),?wxBitmap_Create_3_1), wxe_util:rec(?wxBitmap_Create_3_1). -%% @doc See external documentation. -doc """ Gets the colour depth of the bitmap. @@ -352,11 +320,10 @@ getDepth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_GetDepth), wxe_util:rec(?wxBitmap_GetDepth). -%% @doc See external documentation. -doc """ Gets the height of the bitmap in pixels. -See: `getWidth/1`, `GetSize()` (not implemented in wx) +See: `getWidth/1` """. -spec getHeight(This) -> integer() when This::wxBitmap(). @@ -365,10 +332,9 @@ getHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_GetHeight), wxe_util:rec(?wxBitmap_GetHeight). -%% @doc See external documentation. -doc """ -Gets the associated palette (if any) which may have been loaded from a file or -set for the bitmap. +Gets the associated palette (if any) which may have been loaded from a file or set for +the bitmap. See: `m:wxPalette` """. @@ -379,12 +345,14 @@ getPalette(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_GetPalette), wxe_util:rec(?wxBitmap_GetPalette). -%% @doc See external documentation. -doc """ -Gets the associated mask (if any) which may have been loaded from a file or set -for the bitmap. +Gets the associated mask (if any) which may have been loaded from a file or set for the +bitmap. -See: `setMask/2`, `m:wxMask` +See: +* `setMask/2` + +* `m:wxMask` """. -spec getMask(This) -> wxMask:wxMask() when This::wxBitmap(). @@ -393,11 +361,10 @@ getMask(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_GetMask), wxe_util:rec(?wxBitmap_GetMask). -%% @doc See external documentation. -doc """ Gets the width of the bitmap in pixels. -See: `getHeight/1`, `GetSize()` (not implemented in wx) +See: `getHeight/1` """. -spec getWidth(This) -> integer() when This::wxBitmap(). @@ -406,10 +373,9 @@ getWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_GetWidth), wxe_util:rec(?wxBitmap_GetWidth). -%% @doc See external documentation. -doc """ -Returns a sub bitmap of the current one as long as the rect belongs entirely to -the bitmap. +Returns a sub bitmap of the current one as long as the rect belongs entirely to the +bitmap. This function preserves bit depth and mask information. """. @@ -421,7 +387,7 @@ getSubBitmap(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) wxe_util:queue_cmd(This,Rect,?get_env(),?wxBitmap_GetSubBitmap), wxe_util:rec(?wxBitmap_GetSubBitmap). -%% @equiv loadFile(This,Name, []) +-doc(#{equiv => loadFile(This,Name, [])}). -spec loadFile(This, Name) -> boolean() when This::wxBitmap(), Name::unicode:chardata(). @@ -429,19 +395,18 @@ loadFile(This,Name) when is_record(This, wx_ref),?is_chardata(Name) -> loadFile(This,Name, []). -%% @doc See external documentation. -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Loads a bitmap from a file or resource. Return: true if the operation succeeded, false otherwise. -Remark: A palette may be associated with the bitmap if one exists (especially -for colour Windows bitmaps), and if the code supports it. You can check if one -has been created by using the `getPalette/1` member. +Remark: A palette may be associated with the bitmap if one exists (especially for colour +Windows bitmaps), and if the code supports it. You can check if one has been created by +using the `getPalette/1` member. See: `saveFile/4` """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec loadFile(This, Name, [Option]) -> boolean() when This::wxBitmap(), Name::unicode:chardata(), Option :: {'type', wx:wx_enum()}. @@ -455,8 +420,7 @@ loadFile(#wx_ref{type=ThisT}=This,Name, Options) wxe_util:queue_cmd(This,Name_UC, Opts,?get_env(),?wxBitmap_LoadFile), wxe_util:rec(?wxBitmap_LoadFile). -%% @doc See external documentation. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxBitmap(). @@ -464,7 +428,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See external documentation. -doc "Returns true if bitmap data is present.". -spec isOk(This) -> boolean() when This::wxBitmap(). @@ -473,7 +436,7 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmap_IsOk), wxe_util:rec(?wxBitmap_IsOk). -%% @equiv saveFile(This,Name,Type, []) +-doc(#{equiv => saveFile(This,Name,Type, [])}). -spec saveFile(This, Name, Type) -> boolean() when This::wxBitmap(), Name::unicode:chardata(), Type::wx:wx_enum(). @@ -481,18 +444,16 @@ saveFile(This,Name,Type) when is_record(This, wx_ref),?is_chardata(Name),is_integer(Type) -> saveFile(This,Name,Type, []). -%% @doc See external documentation. -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Saves a bitmap in the named file. Return: true if the operation succeeded, false otherwise. -Remark: Depending on how wxWidgets has been configured, not all formats may be -available. +Remark: Depending on how wxWidgets has been configured, not all formats may be available. See: `loadFile/3` """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec saveFile(This, Name, Type, [Option]) -> boolean() when This::wxBitmap(), Name::unicode:chardata(), Type::wx:wx_enum(), Option :: {'palette', wxPalette:wxPalette()}. @@ -506,10 +467,11 @@ saveFile(#wx_ref{type=ThisT}=This,Name,Type, Options) wxe_util:queue_cmd(This,Name_UC,Type, Opts,?get_env(),?wxBitmap_SaveFile), wxe_util:rec(?wxBitmap_SaveFile). -%% @doc See external documentation. -doc """ -Deprecated: This function is deprecated since version 3.1.2, dimensions and -depth can only be set at construction time. +Deprecated: + +This function is deprecated since version 3.1.2, dimensions and depth can only be set at +construction time. Sets the depth member (does not affect the bitmap data). """. @@ -520,10 +482,11 @@ setDepth(#wx_ref{type=ThisT}=This,Depth) ?CLASS(ThisT,wxBitmap), wxe_util:queue_cmd(This,Depth,?get_env(),?wxBitmap_SetDepth). -%% @doc See external documentation. -doc """ -Deprecated: This function is deprecated since version 3.1.2, dimensions and -depth can only be set at construction time. +Deprecated: + +This function is deprecated since version 3.1.2, dimensions and depth can only be set at +construction time. Sets the height member (does not affect the bitmap data). """. @@ -534,17 +497,18 @@ setHeight(#wx_ref{type=ThisT}=This,Height) ?CLASS(ThisT,wxBitmap), wxe_util:queue_cmd(This,Height,?get_env(),?wxBitmap_SetHeight). -%% @doc See external documentation. -doc """ Sets the mask for this bitmap. Remark: The bitmap object owns the mask once this has been called. -Note: A mask can be set also for bitmap with an alpha channel but doing so under -wxMSW is not recommended because performance of drawing such bitmap is not very -good. +Note: A mask can be set also for bitmap with an alpha channel but doing so under wxMSW is +not recommended because performance of drawing such bitmap is not very good. + +See: +* `getMask/1` -See: `getMask/1`, `m:wxMask` +* `m:wxMask` """. -spec setMask(This, Mask) -> 'ok' when This::wxBitmap(), Mask::wxMask:wxMask(). @@ -553,7 +517,6 @@ setMask(#wx_ref{type=ThisT}=This,#wx_ref{type=MaskT}=Mask) -> ?CLASS(MaskT,wxMask), wxe_util:queue_cmd(This,Mask,?get_env(),?wxBitmap_SetMask). -%% @doc See external documentation. -doc """ Sets the associated palette. @@ -568,10 +531,11 @@ setPalette(#wx_ref{type=ThisT}=This,#wx_ref{type=PaletteT}=Palette) -> ?CLASS(PaletteT,wxPalette), wxe_util:queue_cmd(This,Palette,?get_env(),?wxBitmap_SetPalette). -%% @doc See external documentation. -doc """ -Deprecated: This function is deprecated since version 3.1.2, dimensions and -depth can only be set at construction time. +Deprecated: + +This function is deprecated since version 3.1.2, dimensions and depth can only be set at +construction time. Sets the width member (does not affect the bitmap data). """. @@ -582,23 +546,7 @@ setWidth(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxBitmap), wxe_util:queue_cmd(This,Width,?get_env(),?wxBitmap_SetWidth). -%% @doc Destroys this object, do not use object again --doc """ -Creates bitmap corresponding to the given cursor. - -This can be useful to display a cursor as it cannot be drawn directly on a -window. - -This constructor only exists in wxMSW and wxGTK (where it is implemented for -GTK+ 2.8 or later) only. - -Since: 3.1.0 Destructor. See overview_refcount_destruct for more info. - -If the application omits to delete the bitmap explicitly, the bitmap will be -destroyed automatically by wxWidgets when the application exits. - -Warning: Do not delete a bitmap that is selected into a memory device context. -""". +-doc "Destroys the object". -spec destroy(This::wxBitmap()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBitmap), diff --git a/lib/wx/src/gen/wxBitmapButton.erl b/lib/wx/src/gen/wxBitmapButton.erl index 564faa880dac..c1be8fca58eb 100644 --- a/lib/wx/src/gen/wxBitmapButton.erl +++ b/lib/wx/src/gen/wxBitmapButton.erl @@ -20,32 +20,46 @@ -module(wxBitmapButton). -moduledoc """ -Functions for wxBitmapButton class - A bitmap button is a control that contains a bitmap. -Notice that since wxWidgets 2.9.1 bitmap display is supported by the base -`m:wxButton` class itself and the only tiny advantage of using this class is -that it allows specifying the bitmap in its constructor, unlike `m:wxButton`. -Please see the base class documentation for more information about images -support in `m:wxButton`. +Notice that since wxWidgets 2.9.1 bitmap display is supported by the base `m:wxButton` +class itself and the only tiny advantage of using this class is that it allows specifying +the bitmap in its constructor, unlike `m:wxButton`. Please see the base class +documentation for more information about images support in `m:wxButton`. -Styles +## Styles This class supports the following styles: +* wxBU_LEFT: Left-justifies the bitmap label. + +* wxBU_TOP: Aligns the bitmap label to the top of the button. + +* wxBU_RIGHT: Right-justifies the bitmap label. + +* wxBU_BOTTOM: Aligns the bitmap label to the bottom of the button. Note that the +wxBU_EXACTFIT style supported by `m:wxButton` is not used by this class as bitmap buttons +don't have any minimal standard size by default. + See: `m:wxButton` -This class is derived (and can use functions) from: `m:wxButton` `m:wxControl` -`m:wxWindow` `m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxBitmapButton](https://docs.wxwidgets.org/3.1/classwx_bitmap_button.html) +* `m:wxButton` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxBitmapButton](https://docs.wxwidgets.org/3.2/classwx_bitmap_button.html) ## Events Event types emitted from this class: -[`command_button_clicked`](`m:wxCommandEvent`) + +* [`command_button_clicked`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,new/0,new/3,new/4,newCloseButton/2]). @@ -93,7 +107,6 @@ Event types emitted from this class: -type wxBitmapButton() :: wx:wx_object(). -export_type([wxBitmapButton/0]). -%% @hidden -doc false. parent_class(wxButton) -> true; parent_class(wxControl) -> true; @@ -101,14 +114,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxBitmapButton(). new() -> wxe_util:queue_cmd(?get_env(), ?wxBitmapButton_new_0), wxe_util:rec(?wxBitmapButton_new_0). -%% @equiv new(Parent,Id,Bitmap, []) +-doc(#{equiv => new(Parent,Id,Bitmap, [])}). -spec new(Parent, Id, Bitmap) -> wxBitmapButton() when Parent::wxWindow:wxWindow(), Id::integer(), Bitmap::wxBitmap:wxBitmap(). @@ -116,16 +128,14 @@ new(Parent,Id,Bitmap) when is_record(Parent, wx_ref),is_integer(Id),is_record(Bitmap, wx_ref) -> new(Parent,Id,Bitmap, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a button. -Remark: The bitmap parameter is normally the only bitmap you need to provide, -and wxWidgets will draw the button correctly in its different states. If you -want more control, call any of the functions `SetBitmapPressed()` (not -implemented in wx), `wxButton:setBitmapFocus/2`, `wxButton:setBitmapDisabled/2`. +Remark: The bitmap parameter is normally the only bitmap you need to provide, and +wxWidgets will draw the button correctly in its different states. If you want more +control, call any of the functions `SetBitmapPressed()` (not implemented in wx), `wxButton:setBitmapFocus/2`, `wxButton:setBitmapDisabled/2`. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new(Parent, Id, Bitmap, [Option]) -> wxBitmapButton() when Parent::wxWindow:wxWindow(), Id::integer(), Bitmap::wxBitmap:wxBitmap(), @@ -146,7 +156,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,#wx_ref{type=BitmapT}=Bitmap, Options) wxe_util:queue_cmd(Parent,Id,Bitmap, Opts,?get_env(),?wxBitmapButton_new_4), wxe_util:rec(?wxBitmapButton_new_4). -%% @equiv create(This,Parent,Id,Bitmap, []) +-doc(#{equiv => create(This,Parent,Id,Bitmap, [])}). -spec create(This, Parent, Id, Bitmap) -> boolean() when This::wxBitmapButton(), Parent::wxWindow:wxWindow(), Id::integer(), Bitmap::wxBitmap:wxBitmap(). @@ -154,7 +164,6 @@ create(This,Parent,Id,Bitmap) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_record(Bitmap, wx_ref) -> create(This,Parent,Id,Bitmap, []). -%% @doc See external documentation. -doc """ Button creation function for two-step creation. @@ -180,14 +189,12 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,#wx_ref{type=Bit wxe_util:queue_cmd(This,Parent,Id,Bitmap, Opts,?get_env(),?wxBitmapButton_Create), wxe_util:rec(?wxBitmapButton_Create). -%% @doc See external documentation. -doc """ Helper function creating a standard-looking "Close" button. -To get the best results, platform-specific code may need to be used to create a -small, title bar-like "Close" button. This function is provided to avoid the -need to test for the current platform and creates the button with as native look -as possible. +To get the best results, platform-specific code may need to be used to create a small, +title bar-like "Close" button. This function is provided to avoid the need to test for the +current platform and creates the button with as native look as possible. Return: The new button. @@ -201,584 +208,393 @@ newCloseButton(#wx_ref{type=ParentT}=Parent,Winid) wxe_util:queue_cmd(Parent,Winid,?get_env(),?wxBitmapButton_NewCloseButton), wxe_util:rec(?wxBitmapButton_NewCloseButton). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxBitmapButton()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBitmapButton), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxButton -%% @hidden -doc false. setBitmapLabel(This,Bitmap) -> wxButton:setBitmapLabel(This,Bitmap). -%% @hidden -doc false. setBitmapFocus(This,Bitmap) -> wxButton:setBitmapFocus(This,Bitmap). -%% @hidden -doc false. setBitmapDisabled(This,Bitmap) -> wxButton:setBitmapDisabled(This,Bitmap). -%% @hidden -doc false. getBitmapLabel(This) -> wxButton:getBitmapLabel(This). -%% @hidden -doc false. getBitmapFocus(This) -> wxButton:getBitmapFocus(This). -%% @hidden -doc false. getBitmapDisabled(This) -> wxButton:getBitmapDisabled(This). -%% @hidden -doc false. setLabel(This,Label) -> wxButton:setLabel(This,Label). -%% @hidden -doc false. setDefault(This) -> wxButton:setDefault(This). %% From wxControl -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxBitmapDataObject.erl b/lib/wx/src/gen/wxBitmapDataObject.erl index 4c500099252e..6d3f1127dcb7 100644 --- a/lib/wx/src/gen/wxBitmapDataObject.erl +++ b/lib/wx/src/gen/wxBitmapDataObject.erl @@ -20,26 +20,31 @@ -module(wxBitmapDataObject). -moduledoc """ -Functions for wxBitmapDataObject class - `m:wxBitmapDataObject` is a specialization of `m:wxDataObject` for bitmap data. -It can be used without change to paste data into the `m:wxClipboard` or a -`wxDropSource` (not implemented in wx). A user may wish to derive a new class -from this class for providing a bitmap on-demand in order to minimize memory -consumption when offering data in several formats, such as a bitmap and GIF. -This class may be used as is, but `getBitmap/1` may be overridden to increase -efficiency. +It can be used without change to paste data into the `m:wxClipboard` or a `wxDropSource` +(not implemented in wx). A user may wish to derive a new class from this class for +providing a bitmap on-demand in order to minimize memory consumption when offering data in +several formats, such as a bitmap and GIF. + +This class may be used as is, but `getBitmap/1` may be overridden to increase efficiency. See: -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd), -`m:wxDataObject`, `wxDataObjectSimple` (not implemented in wx), -`m:wxFileDataObject`, `m:wxTextDataObject`, `m:wxDataObject` +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) + +* `m:wxDataObject` + +* `m:wxFileDataObject` + +* `m:wxTextDataObject` + +* `m:wxDataObject` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxDataObject` +* `m:wxDataObject` -wxWidgets docs: -[wxBitmapDataObject](https://docs.wxwidgets.org/3.1/classwx_bitmap_data_object.html) +wxWidgets docs: [wxBitmapDataObject](https://docs.wxwidgets.org/3.2/classwx_bitmap_data_object.html) """. -include("wxe.hrl"). -export([destroy/1,getBitmap/1,new/0,new/1,setBitmap/2]). @@ -49,22 +54,16 @@ wxWidgets docs: -type wxBitmapDataObject() :: wx:wx_object(). -export_type([wxBitmapDataObject/0]). -%% @hidden -doc false. parent_class(wxDataObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxBitmapDataObject(). new() -> new([]). -%% @doc See external documentation. -%%
Also:
-%% new(Bitmap) -> wxBitmapDataObject() when
-%% Bitmap::wxBitmap:wxBitmap().
-%% -doc "Constructor, optionally passing a bitmap (otherwise use `setBitmap/2` later).". -spec new([Option]) -> wxBitmapDataObject() when Option :: {'bitmap', wxBitmap:wxBitmap()}; @@ -82,13 +81,11 @@ new(#wx_ref{type=BitmapT}=Bitmap) -> wxe_util:queue_cmd(Bitmap,?get_env(),?wxBitmapDataObject_new_1_1), wxe_util:rec(?wxBitmapDataObject_new_1_1). -%% @doc See external documentation. -doc """ Returns the bitmap associated with the data object. -You may wish to override this method when offering data on-demand, but this is -not required by wxWidgets' internals. Use this method to get data in bitmap form -from the `m:wxClipboard`. +You may wish to override this method when offering data on-demand, but this is not +required by wxWidgets' internals. Use this method to get data in bitmap form from the `m:wxClipboard`. """. -spec getBitmap(This) -> wxBitmap:wxBitmap() when This::wxBitmapDataObject(). @@ -97,12 +94,11 @@ getBitmap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBitmapDataObject_GetBitmap), wxe_util:rec(?wxBitmapDataObject_GetBitmap). -%% @doc See external documentation. -doc """ Sets the bitmap associated with the data object. -This method is called when the data object receives data. Usually there will be -no reason to override this function. +This method is called when the data object receives data. Usually there will be no reason +to override this function. """. -spec setBitmap(This, Bitmap) -> 'ok' when This::wxBitmapDataObject(), Bitmap::wxBitmap:wxBitmap(). @@ -111,8 +107,7 @@ setBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxBitmapDataObject_SetBitmap). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxBitmapDataObject()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBitmapDataObject), diff --git a/lib/wx/src/gen/wxBookCtrlBase.erl b/lib/wx/src/gen/wxBookCtrlBase.erl index 1bccc1c2ad9e..77bebb8ca22d 100644 --- a/lib/wx/src/gen/wxBookCtrlBase.erl +++ b/lib/wx/src/gen/wxBookCtrlBase.erl @@ -20,23 +20,35 @@ -module(wxBookCtrlBase). -moduledoc """ -Functions for wxBookCtrlBase class +A book control is a convenient way of displaying multiple pages of information, displayed +one page at a time. -A book control is a convenient way of displaying multiple pages of information, -displayed one page at a time. wxWidgets has five variants of this control: +wxWidgets has five variants of this control: -This abstract class is the parent of all these book controls, and provides their -basic interface. This is a pure virtual class so you cannot allocate it -directly. +* `m:wxChoicebook`: controlled by a `m:wxChoice` -See: -[Overview bookctrl](https://docs.wxwidgets.org/3.1/overview_bookctrl.html#overview_bookctrl) +* `m:wxListbook`: controlled by a `m:wxListCtrl` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxNotebook`: uses a row of tabs -wxWidgets docs: -[wxBookCtrlBase](https://docs.wxwidgets.org/3.1/classwx_book_ctrl_base.html) +* `m:wxTreebook`: controlled by a `m:wxTreeCtrl` + +* `m:wxToolbook`: controlled by a `m:wxToolBar` + +This abstract class is the parent of all these book controls, and provides their basic +interface. This is a pure virtual class so you cannot allocate it directly. + +See: [Overview bookctrl](https://docs.wxwidgets.org/3.2/overview_bookctrl.html#overview_bookctrl) + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxBookCtrlBase](https://docs.wxwidgets.org/3.2/classwx_book_ctrl_base.html) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,advanceSelection/1,advanceSelection/2,changeSelection/2, @@ -86,14 +98,13 @@ wxWidgets docs: -type wxBookCtrlBase() :: wx:wx_object(). -export_type([wxBookCtrlBase/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv addPage(This,Page,Text, []) +-doc(#{equiv => addPage(This,Page,Text, [])}). -spec addPage(This, Page, Text) -> boolean() when This::wxBookCtrlBase(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -101,17 +112,15 @@ addPage(This,Page,Text) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Text) -> addPage(This,Page,Text, []). -%% @doc See external documentation. -doc """ Adds a new page. -The page must have the book control itself as the parent and must not have been -added to this control previously. +The page must have the book control itself as the parent and must not have been added to +this control previously. -The call to this function will generate the page changing and page changed -events if `select` is true, but not when inserting the very first page (as there -is no previous page selection to switch from in this case and so it wouldn't -make sense to e.g. veto such event). +The call to this function will generate the page changing and page changed events if `select` +is true, but not when inserting the very first page (as there is no previous page +selection to switch from in this case and so it wouldn't make sense to e.g. veto such event). Return: true if successful, false otherwise. @@ -135,7 +144,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text, Options) wxe_util:queue_cmd(This,Page,Text_UC, Opts,?get_env(),?wxBookCtrlBase_AddPage), wxe_util:rec(?wxBookCtrlBase_AddPage). -%% @equiv insertPage(This,Index,Page,Text, []) +-doc(#{equiv => insertPage(This,Index,Page,Text, [])}). -spec insertPage(This, Index, Page, Text) -> boolean() when This::wxBookCtrlBase(), Index::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -143,7 +152,6 @@ insertPage(This,Index,Page,Text) when is_record(This, wx_ref),is_integer(Index),is_record(Page, wx_ref),?is_chardata(Text) -> insertPage(This,Index,Page,Text, []). -%% @doc See external documentation. -doc """ Inserts a new page at the specified position. @@ -169,15 +177,14 @@ insertPage(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=PageT}=Page,Text, Options wxe_util:queue_cmd(This,Index,Page,Text_UC, Opts,?get_env(),?wxBookCtrlBase_InsertPage), wxe_util:rec(?wxBookCtrlBase_InsertPage). -%% @doc See external documentation. -doc """ Deletes the specified page, and the associated window. -The call to this function generates the page changing events when deleting the -currently selected page or a page preceding it in the index order, but it does -`not` send any events when deleting the last page: while in this case the -selection also changes, it becomes invalid and for compatibility reasons the -control never generates events with the invalid selection index. +The call to this function generates the page changing events when deleting the currently +selected page or a page preceding it in the index order, but it does `not` send any events +when deleting the last page: while in this case the selection also changes, it becomes +invalid and for compatibility reasons the control never generates events with the invalid +selection index. """. -spec deletePage(This, Page) -> boolean() when This::wxBookCtrlBase(), Page::integer(). @@ -187,7 +194,6 @@ deletePage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlBase_DeletePage), wxe_util:rec(?wxBookCtrlBase_DeletePage). -%% @doc See external documentation. -doc """ Deletes the specified page, without deleting the associated window. @@ -201,7 +207,6 @@ removePage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlBase_RemovePage), wxe_util:rec(?wxBookCtrlBase_RemovePage). -%% @doc See external documentation. -doc "Deletes all pages.". -spec deleteAllPages(This) -> boolean() when This::wxBookCtrlBase(). @@ -210,7 +215,6 @@ deleteAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlBase_DeleteAllPages), wxe_util:rec(?wxBookCtrlBase_DeleteAllPages). -%% @doc See external documentation. -doc "Returns the window at the given page position.". -spec getPage(This, Page) -> wxWindow:wxWindow() when This::wxBookCtrlBase(), Page::integer(). @@ -220,7 +224,6 @@ getPage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlBase_GetPage), wxe_util:rec(?wxBookCtrlBase_GetPage). -%% @doc See external documentation. -doc "Returns the number of pages in the control.". -spec getPageCount(This) -> integer() when This::wxBookCtrlBase(). @@ -229,7 +232,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlBase_GetPageCount), wxe_util:rec(?wxBookCtrlBase_GetPageCount). -%% @doc See external documentation. -doc "Returns the currently selected page or NULL.". -spec getCurrentPage(This) -> wxWindow:wxWindow() when This::wxBookCtrlBase(). @@ -238,7 +240,7 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlBase_GetCurrentPage), wxe_util:rec(?wxBookCtrlBase_GetCurrentPage). -%% @equiv advanceSelection(This, []) +-doc(#{equiv => advanceSelection(This, [])}). -spec advanceSelection(This) -> 'ok' when This::wxBookCtrlBase(). @@ -246,7 +248,6 @@ advanceSelection(This) when is_record(This, wx_ref) -> advanceSelection(This, []). -%% @doc See external documentation. -doc """ Cycles through the tabs. @@ -263,12 +264,11 @@ advanceSelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxBookCtrlBase_AdvanceSelection). -%% @doc See external documentation. -doc """ Sets the selection to the given page, returning the previous selection. -Notice that the call to this function generates the page changing events, use -the `changeSelection/2` function if you don't want these events to be generated. +Notice that the call to this function generates the page changing events, use the `changeSelection/2` +function if you don't want these events to be generated. See: `getSelection/1` """. @@ -280,14 +280,12 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlBase_SetSelection), wxe_util:rec(?wxBookCtrlBase_SetSelection). -%% @doc See external documentation. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note that this method may return either the previously or newly selected page -when called from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the -platform and so `wxBookCtrlEvent:getSelection/1` should be used instead in this -case. +Note that this method may return either the previously or newly selected page when called +from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the platform and so `wxBookCtrlEvent:getSelection/1` should be +used instead in this case. """. -spec getSelection(This) -> integer() when This::wxBookCtrlBase(). @@ -296,12 +294,10 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlBase_GetSelection), wxe_util:rec(?wxBookCtrlBase_GetSelection). -%% @doc See external documentation. -doc """ Changes the selection to the given page, returning the previous selection. -This function behaves as `setSelection/2` but does `not` generate the page -changing events. +This function behaves as `setSelection/2` but does `not` generate the page changing events. See overview_events_prog for more information. """. @@ -313,15 +309,13 @@ changeSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlBase_ChangeSelection), wxe_util:rec(?wxBookCtrlBase_ChangeSelection). -%% @doc See external documentation. -doc """ -Returns the index of the tab at the specified position or `wxNOT_FOUND` if none. +Returns the index of the tab at the specified position or `wxNOT\_FOUND` if none. -If `flags` parameter is non-NULL, the position of the point inside the tab is -returned as well. +If `flags` parameter is non-NULL, the position of the point inside the tab is returned as well. -Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at -the specified position. +Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at the +specified position. """. -spec hitTest(This, Pt) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -332,7 +326,6 @@ hitTest(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxBookCtrlBase_HitTest), wxe_util:rec(?wxBookCtrlBase_HitTest). -%% @doc See external documentation. -doc "Returns the string for the given page.". -spec getPageText(This, NPage) -> unicode:charlist() when This::wxBookCtrlBase(), NPage::integer(). @@ -342,7 +335,6 @@ getPageText(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxBookCtrlBase_GetPageText), wxe_util:rec(?wxBookCtrlBase_GetPageText). -%% @doc See external documentation. -doc "Sets the text for the given page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxBookCtrlBase(), Page::integer(), Text::unicode:chardata(). @@ -354,554 +346,371 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:rec(?wxBookCtrlBase_SetPageText). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxBookCtrlEvent.erl b/lib/wx/src/gen/wxBookCtrlEvent.erl index f4d2f0ce8d31..115ca32a8e28 100644 --- a/lib/wx/src/gen/wxBookCtrlEvent.erl +++ b/lib/wx/src/gen/wxBookCtrlEvent.erl @@ -20,33 +20,41 @@ -module(wxBookCtrlEvent). -moduledoc """ -Functions for wxBookCtrlEvent class +This class represents the events generated by book controls (`m:wxNotebook`, `m:wxListbook`, `m:wxChoicebook`, `m:wxTreebook`, `m:wxAuiNotebook`). -This class represents the events generated by book controls (`m:wxNotebook`, -`m:wxListbook`, `m:wxChoicebook`, `m:wxTreebook`, `m:wxAuiNotebook`). +The PAGE_CHANGING events are sent before the current page is changed. It allows the +program to examine the current page (which can be retrieved with `getOldSelection/1`) and to veto the page +change by calling `wxNotifyEvent:veto/1` if, for example, the current values in the controls of the old page are invalid. -The PAGE_CHANGING events are sent before the current page is changed. It allows -the program to examine the current page (which can be retrieved with -`getOldSelection/1`) and to veto the page change by calling -`wxNotifyEvent:veto/1` if, for example, the current values in the controls of -the old page are invalid. +The PAGE_CHANGED events are sent after the page has been changed and the program cannot +veto it any more, it just informs it about the page change. -The PAGE_CHANGED events are sent after the page has been changed and the program -cannot veto it any more, it just informs it about the page change. +To summarize, if the program is interested in validating the page values before allowing +the user to change it, it should process the PAGE_CHANGING event, otherwise PAGE_CHANGED +is probably enough. In any case, it is probably unnecessary to process both events at once. -To summarize, if the program is interested in validating the page values before -allowing the user to change it, it should process the PAGE_CHANGING event, -otherwise PAGE_CHANGED is probably enough. In any case, it is probably -unnecessary to process both events at once. +See: +* `m:wxNotebook` -See: `m:wxNotebook`, `m:wxListbook`, `m:wxChoicebook`, `m:wxTreebook`, -`m:wxToolbook`, `m:wxAuiNotebook` +* `m:wxListbook` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +* `m:wxChoicebook` -wxWidgets docs: -[wxBookCtrlEvent](https://docs.wxwidgets.org/3.1/classwx_book_ctrl_event.html) +* `m:wxTreebook` + +* `m:wxToolbook` + +* `m:wxAuiNotebook` + +This class is derived, and can use functions, from: + +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxBookCtrlEvent](https://docs.wxwidgets.org/3.2/classwx_book_ctrl_event.html) """. -include("wxe.hrl"). -export([getOldSelection/1,getSelection/1,setOldSelection/2,setSelection/2]). @@ -61,16 +69,14 @@ wxWidgets docs: -include("wx.hrl"). -type wxBookCtrlEventType() :: 'command_notebook_page_changed' | 'command_notebook_page_changing' | 'choicebook_page_changed' | 'choicebook_page_changing' | 'treebook_page_changed' | 'treebook_page_changing' | 'toolbook_page_changed' | 'toolbook_page_changing' | 'listbook_page_changed' | 'listbook_page_changing'. -export_type([wxBookCtrlEvent/0, wxBookCtrl/0, wxBookCtrlEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns the page that was selected before the change, `wxNOT_FOUND` if none was +Returns the page that was selected before the change, `wxNOT\_FOUND` if none was selected. """. -spec getOldSelection(This) -> integer() when @@ -80,13 +86,11 @@ getOldSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlEvent_GetOldSelection), wxe_util:rec(?wxBookCtrlEvent_GetOldSelection). -%% @doc See external documentation. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note: under Windows, `getSelection/1` will return the same value as -`getOldSelection/1` when called from the `EVT_BOOKCTRL_PAGE_CHANGING` handler -and not the page which is going to be selected. +Note: under Windows, `getSelection/1` will return the same value as `getOldSelection/1` when called from the `EVT_BOOKCTRL_PAGE_CHANGING` +handler and not the page which is going to be selected. """. -spec getSelection(This) -> integer() when This::wxBookCtrlEvent(). @@ -95,7 +99,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBookCtrlEvent_GetSelection), wxe_util:rec(?wxBookCtrlEvent_GetSelection). -%% @doc See external documentation. -doc "Sets the id of the page selected before the change.". -spec setOldSelection(This, Page) -> 'ok' when This::wxBookCtrlEvent(), Page::integer(). @@ -104,7 +107,6 @@ setOldSelection(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxBookCtrlEvent), wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlEvent_SetOldSelection). -%% @doc See external documentation. -doc "Sets the selection member variable.". -spec setSelection(This, Page) -> 'ok' when This::wxBookCtrlEvent(), Page::integer(). @@ -114,65 +116,45 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxBookCtrlEvent_SetSelection). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxBoxSizer.erl b/lib/wx/src/gen/wxBoxSizer.erl index e2d5b41e85ba..37d0d953d1f3 100644 --- a/lib/wx/src/gen/wxBoxSizer.erl +++ b/lib/wx/src/gen/wxBoxSizer.erl @@ -20,21 +20,21 @@ -module(wxBoxSizer). -moduledoc """ -Functions for wxBoxSizer class - -The basic idea behind a box sizer is that windows will most often be laid out in -rather simple basic geometry, typically in a row or a column or several -hierarchies of either. +The basic idea behind a box sizer is that windows will most often be laid out in rather +simple basic geometry, typically in a row or a column or several hierarchies of either. For more information, please see overview_sizer_box. -See: `m:wxSizer`, -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer) +See: +* `m:wxSizer` + +* [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxSizer` +* `m:wxSizer` -wxWidgets docs: -[wxBoxSizer](https://docs.wxwidgets.org/3.1/classwx_box_sizer.html) +wxWidgets docs: [wxBoxSizer](https://docs.wxwidgets.org/3.2/classwx_box_sizer.html) """. -include("wxe.hrl"). -export([destroy/1,getOrientation/1,new/1]). @@ -52,17 +52,15 @@ wxWidgets docs: -type wxBoxSizer() :: wx:wx_object(). -export_type([wxBoxSizer/0]). -%% @hidden -doc false. parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Constructor for a `m:wxBoxSizer`. -`orient` may be either of wxVERTICAL or wxHORIZONTAL for creating either a -column sizer or a row sizer. +`orient` may be either of wxVERTICAL or wxHORIZONTAL for creating either a column sizer +or a row sizer. """. -spec new(Orient) -> wxBoxSizer() when Orient::integer(). @@ -71,7 +69,6 @@ new(Orient) wxe_util:queue_cmd(Orient,?get_env(),?wxBoxSizer_new), wxe_util:rec(?wxBoxSizer_new). -%% @doc See external documentation. -doc "Returns the orientation of the box sizer, either wxVERTICAL or wxHORIZONTAL.". -spec getOrientation(This) -> integer() when This::wxBoxSizer(). @@ -80,158 +77,108 @@ getOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBoxSizer_GetOrientation), wxe_util:rec(?wxBoxSizer_GetOrientation). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxBoxSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBoxSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. calcMin(This) -> wxSizer:calcMin(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). -%% @hidden -doc false. add(This,Width,Height, Options) -> wxSizer:add(This,Width,Height, Options). -%% @hidden -doc false. add(This,Width,Height) -> wxSizer:add(This,Width,Height). -%% @hidden -doc false. add(This,Window) -> wxSizer:add(This,Window). diff --git a/lib/wx/src/gen/wxBrush.erl b/lib/wx/src/gen/wxBrush.erl index 7c1de6d1ccd7..0cc772986a70 100644 --- a/lib/wx/src/gen/wxBrush.erl +++ b/lib/wx/src/gen/wxBrush.erl @@ -20,37 +20,61 @@ -module(wxBrush). -moduledoc """ -Functions for wxBrush class +A brush is a drawing tool for filling in areas. -A brush is a drawing tool for filling in areas. It is used for painting the -background of rectangles, ellipses, etc. It has a colour and a style. +It is used for painting the background of rectangles, ellipses, etc. It has a colour and +a style. -On a monochrome display, wxWidgets shows all brushes as white unless the colour -is really black. +On a monochrome display, wxWidgets shows all brushes as white unless the colour is really black. -Do not initialize objects on the stack before the program commences, since other -required structures may not have been set up yet. Instead, define global -pointers to objects and create them in `wxApp::OnInit` (not implemented in wx) -or when required. +Do not initialize objects on the stack before the program commences, since other required +structures may not have been set up yet. Instead, define global pointers to objects and +create them in `wxApp::OnInit` (not implemented in wx) or when required. -An application may wish to create brushes with different characteristics -dynamically, and there is the consequent danger that a large number of duplicate -brushes will be created. Therefore an application may wish to get a pointer to a -brush by using the global list of brushes ?wxTheBrushList, and calling the -member function `wxBrushList::FindOrCreateBrush()` (not implemented in wx). +An application may wish to create brushes with different characteristics dynamically, and +there is the consequent danger that a large number of duplicate brushes will be created. +Therefore an application may wish to get a pointer to a brush by using the global list of +brushes ?wxTheBrushList, and calling the member function `wxBrushList::FindOrCreateBrush()` +(not implemented in wx). -This class uses reference counting and copy-on-write internally so that -assignments between two instances of this class are very cheap. You can -therefore use actual objects instead of pointers without efficiency problems. If -an instance of this class is changed it will create its own data internally so -that other instances, which previously shared the data using the reference -counting, are not affected. +This class uses reference counting and copy-on-write internally so that assignments +between two instances of this class are very cheap. You can therefore use actual objects +instead of pointers without efficiency problems. If an instance of this class is changed +it will create its own data internally so that other instances, which previously shared +the data using the reference counting, are not affected. Predefined objects (include wx.hrl): -See: `wxBrushList` (not implemented in wx), `m:wxDC`, `wxDC:setBrush/2` +* ?wxNullBrush -wxWidgets docs: [wxBrush](https://docs.wxwidgets.org/3.1/classwx_brush.html) +* ?wxBLACK\_BRUSH + +* ?wxBLUE\_BRUSH + +* ?wxCYAN\_BRUSH + +* ?wxGREEN\_BRUSH + +* ?wxYELLOW\_BRUSH + +* ?wxGREY\_BRUSH + +* ?wxLIGHT\_GREY\_BRUSH + +* ?wxMEDIUM\_GREY\_BRUSH + +* ?wxRED\_BRUSH + +* ?wxTRANSPARENT\_BRUSH + +* ?wxWHITE\_BRUSH + +See: +* `m:wxDC` + +* `wxDC:setBrush/2` + +wxWidgets docs: [wxBrush](https://docs.wxwidgets.org/3.2/classwx_brush.html) """. -include("wxe.hrl"). -export([destroy/1,getColour/1,getStipple/1,getStyle/1,isHatch/1,isOk/1,new/0, @@ -61,11 +85,9 @@ wxWidgets docs: [wxBrush](https://docs.wxwidgets.org/3.1/classwx_brush.html) -type wxBrush() :: wx:wx_object(). -export_type([wxBrush/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. @@ -76,13 +98,8 @@ new() -> wxe_util:queue_cmd(?get_env(), ?wxBrush_new_0), wxe_util:rec(?wxBrush_new_0). -%% @doc See external documentation. -%%
Also:
-%% new(Brush) -> wxBrush() when
-%% Brush::wxBrush:wxBrush() | wxBitmap:wxBitmap().
-%% -%%
Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -doc "Copy constructor, uses reference counting.". +%% Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -spec new(Colour) -> wxBrush() when Colour::wx:wx_colour(); (Brush) -> wxBrush() when @@ -102,9 +119,8 @@ new(#wx_ref{type=BrushT}=Brush) -> wxe_util:queue_cmd(wx:typeCast(Brush, BrushType),?get_env(),?wxBrush_new_1), wxe_util:rec(?wxBrush_new_1). -%% @doc See external documentation. -%%
Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -doc "Constructs a brush from a colour object and `style`.". +%% Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -spec new(Colour, [Option]) -> wxBrush() when Colour::wx:wx_colour(), Option :: {'style', wx:wx_enum()}. @@ -116,7 +132,6 @@ new(Colour, Options) wxe_util:queue_cmd(wxe_util:color(Colour), Opts,?get_env(),?wxBrush_new_2), wxe_util:rec(?wxBrush_new_2). -%% @doc See external documentation. -doc """ Returns a reference to the brush colour. @@ -129,12 +144,11 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBrush_GetColour), wxe_util:rec(?wxBrush_GetColour). -%% @doc See external documentation. -doc """ Gets a pointer to the stipple bitmap. -If the brush does not have a `wxBRUSHSTYLE_STIPPLE` style, this bitmap may be -non-NULL but uninitialised (i.e. `m:wxBitmap`:`isOk/1` returns false). +If the brush does not have a `wxBRUSHSTYLE_STIPPLE` style, this bitmap may be non-NULL +but uninitialised (i.e. `m:wxBitmap`:`isOk/1` returns false). See: `setStipple/2` """. @@ -145,13 +159,17 @@ getStipple(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBrush_GetStipple), wxe_util:rec(?wxBrush_GetStipple). -%% @doc See external documentation. -%%
Res = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -doc """ Returns the brush style, one of the ?wxBrushStyle values. -See: `setStyle/2`, `setColour/4`, `setStipple/2` +See: +* `setStyle/2` + +* `setColour/4` + +* `setStipple/2` """. +%% Res = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -spec getStyle(This) -> wx:wx_enum() when This::wxBrush(). getStyle(#wx_ref{type=ThisT}=This) -> @@ -159,7 +177,6 @@ getStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBrush_GetStyle), wxe_util:rec(?wxBrush_GetStyle). -%% @doc See external documentation. -doc """ Returns true if the style of the brush is any of hatched fills. @@ -172,13 +189,11 @@ isHatch(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBrush_IsHatch), wxe_util:rec(?wxBrush_IsHatch). -%% @doc See external documentation. -doc """ Returns true if the brush is initialised. -Notice that an uninitialized brush object can't be queried for any brush -properties and all calls to the accessor methods on it will result in an assert -failure. +Notice that an uninitialized brush object can't be queried for any brush properties and +all calls to the accessor methods on it will result in an assert failure. """. -spec isOk(This) -> boolean() when This::wxBrush(). @@ -187,7 +202,6 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxBrush_IsOk), wxe_util:rec(?wxBrush_IsOk). -%% @doc See external documentation. -doc """ Sets the brush colour using red, green and blue values. @@ -200,7 +214,7 @@ setColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxBrush), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxBrush_SetColour_1). -%% @doc See external documentation. +-doc "". -spec setColour(This, Red, Green, Blue) -> 'ok' when This::wxBrush(), Red::integer(), Green::integer(), Blue::integer(). setColour(#wx_ref{type=ThisT}=This,Red,Green,Blue) @@ -208,13 +222,11 @@ setColour(#wx_ref{type=ThisT}=This,Red,Green,Blue) ?CLASS(ThisT,wxBrush), wxe_util:queue_cmd(This,Red,Green,Blue,?get_env(),?wxBrush_SetColour_3). -%% @doc See external documentation. -doc """ Sets the stipple bitmap. -Remark: The style will be set to `wxBRUSHSTYLE_STIPPLE`, unless the bitmap has a -mask associated to it, in which case the style will be set to -`wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE`. +Remark: The style will be set to `wxBRUSHSTYLE_STIPPLE`, unless the bitmap has a mask +associated to it, in which case the style will be set to `wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE`. See: `m:wxBitmap` """. @@ -225,13 +237,12 @@ setStipple(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxBrush_SetStipple). -%% @doc See external documentation. -%%
Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -doc """ Sets the brush style. See: `getStyle/1` """. +%% Style = ?wxBRUSHSTYLE_INVALID | ?wxBRUSHSTYLE_SOLID | ?wxBRUSHSTYLE_TRANSPARENT | ?wxBRUSHSTYLE_STIPPLE_MASK_OPAQUE | ?wxBRUSHSTYLE_STIPPLE_MASK | ?wxBRUSHSTYLE_STIPPLE | ?wxBRUSHSTYLE_BDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSSDIAG_HATCH | ?wxBRUSHSTYLE_FDIAGONAL_HATCH | ?wxBRUSHSTYLE_CROSS_HATCH | ?wxBRUSHSTYLE_HORIZONTAL_HATCH | ?wxBRUSHSTYLE_VERTICAL_HATCH | ?wxBRUSHSTYLE_FIRST_HATCH | ?wxBRUSHSTYLE_LAST_HATCH -spec setStyle(This, Style) -> 'ok' when This::wxBrush(), Style::wx:wx_enum(). setStyle(#wx_ref{type=ThisT}=This,Style) @@ -239,17 +250,7 @@ setStyle(#wx_ref{type=ThisT}=This,Style) ?CLASS(ThisT,wxBrush), wxe_util:queue_cmd(This,Style,?get_env(),?wxBrush_SetStyle). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See overview_refcount_destruct for more info. - -Remark: Although all remaining brushes are deleted when the application exits, -the application should try to clean up all brushes itself. This is because -wxWidgets cannot know if a pointer to the brush object is stored in an -application data structure, and there is a risk of double deletion. -""". +-doc "Destroys the object". -spec destroy(This::wxBrush()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBrush), diff --git a/lib/wx/src/gen/wxBufferedDC.erl b/lib/wx/src/gen/wxBufferedDC.erl index cc702f244313..91090dd20f32 100644 --- a/lib/wx/src/gen/wxBufferedDC.erl +++ b/lib/wx/src/gen/wxBufferedDC.erl @@ -20,39 +20,42 @@ -module(wxBufferedDC). -moduledoc """ -Functions for wxBufferedDC class +This class provides a simple way to avoid flicker: when drawing on it, everything is in +fact first drawn on an in-memory buffer (a `m:wxBitmap`) and then copied to the screen, +using the associated `m:wxDC`, only once, when this object is destroyed. -This class provides a simple way to avoid flicker: when drawing on it, -everything is in fact first drawn on an in-memory buffer (a `m:wxBitmap`) and -then copied to the screen, using the associated `m:wxDC`, only once, when this -object is destroyed. `m:wxBufferedDC` itself is typically associated with -`m:wxClientDC`, if you want to use it in your `EVT_PAINT` handler, you should -look at `m:wxBufferedPaintDC` instead. +`m:wxBufferedDC` itself is typically associated with `m:wxClientDC`, if you want to use +it in your `EVT_PAINT` handler, you should look at `m:wxBufferedPaintDC` instead. -When used like this, a valid `DC` must be specified in the constructor while the -`buffer` bitmap doesn't have to be explicitly provided, by default this class -will allocate the bitmap of required size itself. However using a dedicated -bitmap can speed up the redrawing process by eliminating the repeated creation -and destruction of a possibly big bitmap. Otherwise, `m:wxBufferedDC` can be -used in the same way as any other device context. +When used like this, a valid `DC` must be specified in the constructor while the `buffer` +bitmap doesn't have to be explicitly provided, by default this class will allocate the +bitmap of required size itself. However using a dedicated bitmap can speed up the +redrawing process by eliminating the repeated creation and destruction of a possibly big +bitmap. Otherwise, `m:wxBufferedDC` can be used in the same way as any other device context. -Another possible use for `m:wxBufferedDC` is to use it to maintain a backing -store for the window contents. In this case, the associated `DC` may be NULL but -a valid backing store bitmap should be specified. +Another possible use for `m:wxBufferedDC` is to use it to maintain a backing store for +the window contents. In this case, the associated `DC` may be NULL but a valid backing +store bitmap should be specified. -Finally, please note that GTK+ 2.0 as well as macOS provide double buffering -themselves natively. You can either use `wxWindow:isDoubleBuffered/1` to -determine whether you need to use buffering or not, or use -`wxAutoBufferedPaintDC` (not implemented in wx) to avoid needless double -buffering on the systems which already do it automatically. +Finally, please note that GTK+ 2.0 as well as macOS provide double buffering themselves +natively. You can either use `wxWindow:isDoubleBuffered/1` to determine whether you need to use buffering or not, or +use `wxAutoBufferedPaintDC` (not implemented in wx) to avoid needless double buffering on +the systems which already do it automatically. -See: `m:wxDC`, `m:wxMemoryDC`, `m:wxBufferedPaintDC`, `wxAutoBufferedPaintDC` -(not implemented in wx) +See: +* `m:wxDC` -This class is derived (and can use functions) from: `m:wxMemoryDC` `m:wxDC` +* `m:wxMemoryDC` -wxWidgets docs: -[wxBufferedDC](https://docs.wxwidgets.org/3.1/classwx_buffered_d_c.html) +* `m:wxBufferedPaintDC` + +This class is derived, and can use functions, from: + +* `m:wxMemoryDC` + +* `m:wxDC` + +wxWidgets docs: [wxBufferedDC](https://docs.wxwidgets.org/3.2/classwx_buffered_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,init/2,init/3,init/4,new/0,new/1,new/2,new/3]). @@ -82,25 +85,22 @@ wxWidgets docs: -type wxBufferedDC() :: wx:wx_object(). -export_type([wxBufferedDC/0]). -%% @hidden -doc false. parent_class(wxMemoryDC) -> true; parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. -You must call one of the `init/4` methods later in order to use the device -context. +You must call one of the `init/4` methods later in order to use the device context. """. -spec new() -> wxBufferedDC(). new() -> wxe_util:queue_cmd(?get_env(), ?wxBufferedDC_new_0), wxe_util:rec(?wxBufferedDC_new_0). -%% @equiv new(Dc, []) +-doc(#{equiv => new(Dc, [])}). -spec new(Dc) -> wxBufferedDC() when Dc::wxDC:wxDC(). @@ -108,13 +108,6 @@ new(Dc) when is_record(Dc, wx_ref) -> new(Dc, []). -%% @doc See external documentation. -%%
Also:
-%% new(Dc, [Option]) -> wxBufferedDC() when
-%% Dc::wxDC:wxDC(),
-%% Option :: {'buffer', wxBitmap:wxBitmap()}
-%% | {'style', integer()}.
-%% -doc """ Creates a buffer for the provided dc. @@ -140,7 +133,6 @@ new(#wx_ref{type=DcT}=Dc, Options) wxe_util:queue_cmd(Dc, Opts,?get_env(),?wxBufferedDC_new_2), wxe_util:rec(?wxBufferedDC_new_2). -%% @doc See external documentation. -doc """ Creates a buffer for the provided `dc`. @@ -158,7 +150,7 @@ new(#wx_ref{type=DcT}=Dc,{AreaW,AreaH} = Area, Options) wxe_util:queue_cmd(Dc,Area, Opts,?get_env(),?wxBufferedDC_new_3), wxe_util:rec(?wxBufferedDC_new_3). -%% @equiv init(This,Dc, []) +-doc(#{equiv => init(This,Dc, [])}). -spec init(This, Dc) -> 'ok' when This::wxBufferedDC(), Dc::wxDC:wxDC(). @@ -166,13 +158,7 @@ init(This,Dc) when is_record(This, wx_ref),is_record(Dc, wx_ref) -> init(This,Dc, []). -%% @doc See external documentation. -%%
Also:
-%% init(This, Dc, [Option]) -> 'ok' when
-%% This::wxBufferedDC(), Dc::wxDC:wxDC(),
-%% Option :: {'buffer', wxBitmap:wxBitmap()}
-%% | {'style', integer()}.
-%% +-doc "". -spec init(This, Dc, Area) -> 'ok' when This::wxBufferedDC(), Dc::wxDC:wxDC(), Area::{W::integer(), H::integer()}; (This, Dc, [Option]) -> 'ok' when @@ -193,7 +179,6 @@ init(#wx_ref{type=ThisT}=This,#wx_ref{type=DcT}=Dc, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Dc, Opts,?get_env(),?wxBufferedDC_Init_2). -%% @doc See external documentation. -doc """ Initializes the object created using the default constructor. @@ -211,297 +196,199 @@ init(#wx_ref{type=ThisT}=This,#wx_ref{type=DcT}=Dc,{AreaW,AreaH} = Area, Options Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Dc,Area, Opts,?get_env(),?wxBufferedDC_Init_3). -%% @doc Destroys this object, do not use object again --doc """ -Copies everything drawn on the DC so far to the underlying DC associated with -this object, if any. -""". +-doc "Destroys the object". -spec destroy(This::wxBufferedDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBufferedDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxMemoryDC -%% @hidden -doc false. selectObjectAsSource(This,Bitmap) -> wxMemoryDC:selectObjectAsSource(This,Bitmap). -%% @hidden -doc false. selectObject(This,Bitmap) -> wxMemoryDC:selectObject(This,Bitmap). %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxBufferedPaintDC.erl b/lib/wx/src/gen/wxBufferedPaintDC.erl index 757ad5f6d097..e5fa56575c65 100644 --- a/lib/wx/src/gen/wxBufferedPaintDC.erl +++ b/lib/wx/src/gen/wxBufferedPaintDC.erl @@ -20,26 +20,31 @@ -module(wxBufferedPaintDC). -moduledoc """ -Functions for wxBufferedPaintDC class +This is a subclass of `m:wxBufferedDC` which can be used inside of an `EVT\_PAINT()` +event handler to achieve double-buffered drawing. -This is a subclass of `m:wxBufferedDC` which can be used inside of an -`EVT_PAINT()` event handler to achieve double-buffered drawing. Just use this -class instead of `m:wxPaintDC` and make sure `wxWindow:setBackgroundStyle/2` is -called with wxBG_STYLE_PAINT somewhere in the class initialization code, and -that's all you have to do to (mostly) avoid flicker. The only thing to watch out -for is that if you are using this class together with `wxScrolled` (not -implemented in wx), you probably do `not` want to call -`wxScrolledWindow:prepareDC/2` on it as it already does this internally for the -real underlying `m:wxPaintDC`. +Just use this class instead of `m:wxPaintDC` and make sure `wxWindow:setBackgroundStyle/2` is called with +wxBG_STYLE_PAINT somewhere in the class initialization code, and that's all you have to do +to (mostly) avoid flicker. The only thing to watch out for is that if you are using this +class together with `wxScrolled` (not implemented in wx), you probably do `not` want to +call `wxScrolledWindow:prepareDC/2` on it as it already does this internally for the real underlying `m:wxPaintDC`. -See: `m:wxDC`, `m:wxBufferedDC`, `wxAutoBufferedPaintDC` (not implemented in -wx), `m:wxPaintDC` +See: +* `m:wxDC` -This class is derived (and can use functions) from: `m:wxBufferedDC` -`m:wxMemoryDC` `m:wxDC` +* `m:wxBufferedDC` -wxWidgets docs: -[wxBufferedPaintDC](https://docs.wxwidgets.org/3.1/classwx_buffered_paint_d_c.html) +* `m:wxPaintDC` + +This class is derived, and can use functions, from: + +* `m:wxBufferedDC` + +* `m:wxMemoryDC` + +* `m:wxDC` + +wxWidgets docs: [wxBufferedPaintDC](https://docs.wxwidgets.org/3.2/classwx_buffered_paint_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/1,new/2,new/3]). @@ -69,14 +74,13 @@ wxWidgets docs: -type wxBufferedPaintDC() :: wx:wx_object(). -export_type([wxBufferedPaintDC/0]). -%% @hidden -doc false. parent_class(wxBufferedDC) -> true; parent_class(wxMemoryDC) -> true; parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Window, []) +-doc(#{equiv => new(Window, [])}). -spec new(Window) -> wxBufferedPaintDC() when Window::wxWindow:wxWindow(). @@ -84,12 +88,7 @@ new(Window) when is_record(Window, wx_ref) -> new(Window, []). -%% @doc See external documentation. -%%
Also:
-%% new(Window, [Option]) -> wxBufferedPaintDC() when
-%% Window::wxWindow:wxWindow(),
-%% Option :: {'style', integer()}.
-%% +-doc "". -spec new(Window, Buffer) -> wxBufferedPaintDC() when Window::wxWindow:wxWindow(), Buffer::wxBitmap:wxBitmap(); (Window, [Option]) -> wxBufferedPaintDC() when @@ -108,15 +107,14 @@ new(#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(Window, Opts,?get_env(),?wxBufferedPaintDC_new_2), wxe_util:rec(?wxBufferedPaintDC_new_2). -%% @doc See external documentation. -doc """ -As with `m:wxBufferedDC`, you may either provide the bitmap to be used for -buffering or let this object create one internally (in the latter case, the size -of the client part of the window is used). +As with `m:wxBufferedDC`, you may either provide the bitmap to be used for buffering or +let this object create one internally (in the latter case, the size of the client part of +the window is used). -Pass wxBUFFER_CLIENT_AREA for the `style` parameter to indicate that just the -client area of the window is buffered, or wxBUFFER_VIRTUAL_AREA to indicate that -the buffer bitmap covers the virtual area. +Pass wxBUFFER_CLIENT_AREA for the `style` parameter to indicate that just the client area +of the window is buffered, or wxBUFFER_VIRTUAL_AREA to indicate that the buffer bitmap +covers the virtual area. """. -spec new(Window, Buffer, [Option]) -> wxBufferedPaintDC() when Window::wxWindow:wxWindow(), Buffer::wxBitmap:wxBitmap(), @@ -131,307 +129,206 @@ new(#wx_ref{type=WindowT}=Window,#wx_ref{type=BufferT}=Buffer, Options) wxe_util:queue_cmd(Window,Buffer, Opts,?get_env(),?wxBufferedPaintDC_new_3), wxe_util:rec(?wxBufferedPaintDC_new_3). -%% @doc Destroys this object, do not use object again --doc """ -Copies everything drawn on the DC so far to the window associated with this -object, using a `m:wxPaintDC`. -""". +-doc "Destroys the object". -spec destroy(This::wxBufferedPaintDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxBufferedPaintDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBufferedDC -%% @hidden -doc false. init(This,Dc,Area, Options) -> wxBufferedDC:init(This,Dc,Area, Options). -%% @hidden -doc false. init(This,Dc,Area) -> wxBufferedDC:init(This,Dc,Area). -%% @hidden -doc false. init(This,Dc) -> wxBufferedDC:init(This,Dc). %% From wxMemoryDC -%% @hidden -doc false. selectObjectAsSource(This,Bitmap) -> wxMemoryDC:selectObjectAsSource(This,Bitmap). -%% @hidden -doc false. selectObject(This,Bitmap) -> wxMemoryDC:selectObject(This,Bitmap). %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxButton.erl b/lib/wx/src/gen/wxButton.erl index 6eae9df7e66e..0a45162fa506 100644 --- a/lib/wx/src/gen/wxButton.erl +++ b/lib/wx/src/gen/wxButton.erl @@ -20,64 +20,102 @@ -module(wxButton). -moduledoc """ -Functions for wxButton class - -A button is a control that contains a text string, and is one of the most common -elements of a GUI. - -It may be placed on a `m:wxDialog` or on a `m:wxPanel` panel, or indeed on -almost any other window. - -By default, i.e. if none of the alignment styles are specified, the label is -centered both horizontally and vertically. If the button has both a label and a -bitmap, the alignment styles above specify the location of the rectangle -combining both the label and the bitmap and the bitmap position set with -`wxButton::SetBitmapPosition()` (not implemented in wx) defines the relative -position of the bitmap with respect to the label (however currently non-default -alignment combinations are not implemented on all platforms). - -Since version 2.9.1 `m:wxButton` supports showing both text and an image -(currently only when using wxMSW, wxGTK or wxOSX/Cocoa ports), see `SetBitmap()` -(not implemented in wx) and `setBitmapLabel/2`, `setBitmapDisabled/2` &c -methods. In the previous wxWidgets versions this functionality was only -available in (the now trivial) `m:wxBitmapButton` class which was only capable -of showing an image without text. - -A button may have either a single image for all states or different images for -the following states (different images are not currently supported under macOS -where the normal image is used for all states): - -All of the bitmaps must be of the same size and the normal bitmap must be set -first (to a valid bitmap), before setting any other ones. Also, if the size of -the bitmaps is changed later, you need to change the size of the normal bitmap -before setting any other bitmaps with the new size (and you do need to reset all -of them as their original values can be lost when the normal bitmap size -changes). - -The position of the image inside the button be configured using -`SetBitmapPosition()` (not implemented in wx). By default the image is on the -left of the text. +A button is a control that contains a text string, and is one of the most common elements +of a GUI. + +It may be placed on a `m:wxDialog` or on a `m:wxPanel` panel, or indeed on almost any +other window. + +By default, i.e. if none of the alignment styles are specified, the label is centered +both horizontally and vertically. If the button has both a label and a bitmap, the +alignment styles above specify the location of the rectangle combining both the label and +the bitmap and the bitmap position set with `wxButton::SetBitmapPosition()` (not +implemented in wx) defines the relative position of the bitmap with respect to the label +(however currently non-default alignment combinations are not implemented on all platforms). + +Since version 2.9.1 `m:wxButton` supports showing both text and an image (currently only +when using wxMSW, wxGTK or wxOSX/Cocoa ports), see `SetBitmap()` (not implemented in wx) +and `setBitmapLabel/2`, `setBitmapDisabled/2` &c methods. In the previous wxWidgets versions this functionality was only +available in (the now trivial) `m:wxBitmapButton` class which was only capable of showing +an image without text. + +A button may have either a single image for all states or different images for the +following states (different images are not currently supported under macOS where the +normal image is used for all states): + +* `normal:` the default state + +* `disabled:` bitmap shown when the button is disabled. + +* `pressed:` bitmap shown when the button is pushed (e.g. while the user keeps the mouse +button pressed on it) + +* `focus:` bitmap shown when the button has keyboard focus (but is not pressed as in this +case the button is in the pressed state) + +* `current:` bitmap shown when the mouse is over the button (but it is not pressed although +it may have focus). Notice that if current bitmap is not specified but the current +platform UI uses hover images for the buttons (such as Windows or GTK+), then the focus +bitmap is used for hover state as well. This makes it possible to set focus bitmap only to +get reasonably good behaviour on all platforms. + +All of the bitmaps must be of the same size and the normal bitmap must be set first (to +a valid bitmap), before setting any other ones. Also, if the size of the bitmaps is +changed later, you need to change the size of the normal bitmap before setting any other +bitmaps with the new size (and you do need to reset all of them as their original values +can be lost when the normal bitmap size changes). + +The position of the image inside the button be configured using `SetBitmapPosition()` +(not implemented in wx). By default the image is on the left of the text. Please also notice that GTK+ uses a global setting called `gtk-button-images` to -determine if the images should be shown in the buttons at all. If it is off -(which is the case in e.g. Gnome 2.28 by default), no images will be shown, -consistently with the native behaviour. +determine if the images should be shown in the buttons at all. If it is off (which is the +case in e.g. Gnome 2.28 by default), no images will be shown, consistently with the native behaviour. -Styles +## Styles This class supports the following styles: +* wxBU_LEFT: Left-justifies the label. Windows and GTK+ only. + +* wxBU_TOP: Aligns the label to the top of the button. Windows and GTK+ only. + +* wxBU_RIGHT: Right-justifies the bitmap label. Windows and GTK+ only. + +* wxBU_BOTTOM: Aligns the label to the bottom of the button. Windows and GTK+ only. + +* wxBU_EXACTFIT: By default, all buttons are made of at least the standard button size, +even if their contents is small enough to fit into a smaller size. This is done for +consistency as most platforms use buttons of the same size in the native dialogs, but can +be overridden by specifying this flag. If it is given, the button will be made just big +enough for its contents. Notice that under MSW the button will still have at least the +standard height, even with this style, if it has a non-empty label. + +* wxBU_NOTEXT: Disables the display of the text label in the button even if it has one or +its id is one of the standard stock ids with an associated label: without using this style +a button which is only supposed to show a bitmap but uses a standard id would display a +label too. + +* wxBORDER_NONE: Creates a button without border. This is currently implemented in MSW, +GTK2 and OSX/Cocoa. + See: `m:wxBitmapButton` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -wxWidgets docs: [wxButton](https://docs.wxwidgets.org/3.1/classwx_button.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxButton](https://docs.wxwidgets.org/3.2/classwx_button.html) ## Events Event types emitted from this class: -[`command_button_clicked`](`m:wxCommandEvent`) + +* [`command_button_clicked`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getBitmapDisabled/1,getBitmapFocus/1,getBitmapLabel/1, @@ -126,21 +164,19 @@ Event types emitted from this class: -type wxButton() :: wx:wx_object(). -export_type([wxButton/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxButton(). new() -> wxe_util:queue_cmd(?get_env(), ?wxButton_new_0), wxe_util:rec(?wxButton_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxButton() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -148,22 +184,20 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a button. -The preferred way to create standard buttons is to use default value of `label`. -If no label is supplied and `id` is one of standard IDs from this list, a -standard label will be used. In other words, if you use a predefined `wxID_XXX` -constant, just omit the label completely rather than specifying it. In -particular, help buttons (the ones with `id` of `wxID_HELP`) under macOS can't -display any label at all and while `m:wxButton` will detect if the standard -"Help" label is used and ignore it, using any other label will prevent the -button from correctly appearing as a help button and so should be avoided. +The preferred way to create standard buttons is to use default value of `label`. If no +label is supplied and `id` is one of standard IDs from this list, a standard label will be +used. In other words, if you use a predefined `wxID_XXX` constant, just omit the label +completely rather than specifying it. In particular, help buttons (the ones with `id` of `wxID_HELP`) +under macOS can't display any label at all and while `m:wxButton` will detect if the +standard "Help" label is used and ignore it, using any other label will prevent the button +from correctly appearing as a help button and so should be avoided. In addition to that, the button will be decorated with stock icons under GTK+ 2. -See: `create/4`, `wxValidator` (not implemented in wx) +See: `create/4` """. -spec new(Parent, Id, [Option]) -> wxButton() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -185,7 +219,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxButton_new_3), wxe_util:rec(?wxButton_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxButton(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -193,7 +227,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Button creation function for two-step creation. @@ -220,23 +253,22 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxButton_Create), wxe_util:rec(?wxButton_Create). -%% @doc See external documentation. -doc """ Returns the default size for the buttons. -It is advised to make all the dialog buttons of the same size and this function -allows retrieving the (platform, and current font dependent) size which should -be the best suited for this. +It is advised to make all the dialog buttons of the same size and this function allows +retrieving the (platform, and current font dependent) size which should be the best suited +for this. -The optional `win` argument is new since wxWidgets 3.1.3 and allows to get a -per-monitor DPI specific size. +The optional `win` argument is new since wxWidgets 3.1.3 and allows to get a per-monitor +DPI specific size. """. -spec getDefaultSize() -> {W::integer(), H::integer()}. getDefaultSize() -> wxe_util:queue_cmd(?get_env(), ?wxButton_GetDefaultSize_STAT_0), wxe_util:rec(?wxButton_GetDefaultSize_STAT_0). -%% @doc See external documentation. +-doc "". -spec getDefaultSize(Win) -> {W::integer(), H::integer()} when Win::wxWindow:wxWindow(). getDefaultSize(#wx_ref{type=WinT}=Win) -> @@ -244,18 +276,16 @@ getDefaultSize(#wx_ref{type=WinT}=Win) -> wxe_util:queue_cmd(Win,?get_env(),?wxButton_GetDefaultSize_STAT_1), wxe_util:rec(?wxButton_GetDefaultSize_STAT_1). -%% @doc See external documentation. -doc """ This sets the button to be the default item in its top-level window (e.g. the panel or the dialog box containing it). -As normal, pressing return causes the default button to be depressed when the -return key is pressed. +As normal, pressing return causes the default button to be depressed when the return key +is pressed. -See also `wxWindow:setFocus/1` which sets the keyboard focus for windows and -text panel items, and `wxTopLevelWindow::SetDefaultItem()` (not implemented in -wx). +See also `wxWindow:setFocus/1` which sets the keyboard focus for windows and text panel items, and `wxTopLevelWindow::SetDefaultItem()` +(not implemented in wx). Remark: Under Windows, only dialog box buttons respond to this function. @@ -268,7 +298,6 @@ setDefault(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxButton_SetDefault), wxe_util:rec(?wxButton_SetDefault). -%% @doc See external documentation. -doc "Sets the string label for the button.". -spec setLabel(This, Label) -> 'ok' when This::wxButton(), Label::unicode:chardata(). @@ -278,7 +307,6 @@ setLabel(#wx_ref{type=ThisT}=This,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Label_UC,?get_env(),?wxButton_SetLabel). -%% @doc See external documentation. -doc """ Returns the bitmap for the disabled state, which may be invalid. @@ -293,7 +321,6 @@ getBitmapDisabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxButton_GetBitmapDisabled), wxe_util:rec(?wxButton_GetBitmapDisabled). -%% @doc See external documentation. -doc """ Returns the bitmap for the focused state, which may be invalid. @@ -308,14 +335,13 @@ getBitmapFocus(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxButton_GetBitmapFocus), wxe_util:rec(?wxButton_GetBitmapFocus). -%% @doc See external documentation. -doc """ Returns the bitmap for the normal state. -This is exactly the same as `GetBitmap()` (not implemented in wx) but uses a -name backwards-compatible with `m:wxBitmapButton`. +This is exactly the same as `GetBitmap()` (not implemented in wx) but uses a name +backwards-compatible with `m:wxBitmapButton`. -See: `SetBitmap()` (not implemented in wx), `setBitmapLabel/2` +See: `setBitmapLabel/2` Since: 2.9.1 (available in `m:wxBitmapButton` only in previous versions) """. @@ -326,18 +352,20 @@ getBitmapLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxButton_GetBitmapLabel), wxe_util:rec(?wxButton_GetBitmapLabel). -%% @doc See external documentation. -doc """ Sets the bitmap for the disabled button appearance. -If `bitmap` is invalid, the disabled bitmap is set to the automatically -generated greyed out version of the normal bitmap, i.e. the same bitmap as is -used by default if this method is not called at all. Use `SetBitmap()` (not -implemented in wx) with an invalid bitmap to remove the bitmap completely (for -all states). +If `bitmap` is invalid, the disabled bitmap is set to the automatically generated greyed +out version of the normal bitmap, i.e. the same bitmap as is used by default if this +method is not called at all. Use `SetBitmap()` (not implemented in wx) with an invalid +bitmap to remove the bitmap completely (for all states). + +See: +* `getBitmapDisabled/1` -See: `getBitmapDisabled/1`, `setBitmapLabel/2`, `SetBitmapPressed()` (not -implemented in wx), `setBitmapFocus/2` +* `setBitmapLabel/2` + +* `setBitmapFocus/2` Since: 2.9.1 (available in `m:wxBitmapButton` only in previous versions) """. @@ -348,14 +376,17 @@ setBitmapDisabled(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxButton_SetBitmapDisabled). -%% @doc See external documentation. -doc """ Sets the bitmap for the button appearance when it has the keyboard focus. If `bitmap` is invalid, the normal bitmap will be used in the focused state. -See: `getBitmapFocus/1`, `setBitmapLabel/2`, `SetBitmapPressed()` (not -implemented in wx), `setBitmapDisabled/2` +See: +* `getBitmapFocus/1` + +* `setBitmapLabel/2` + +* `setBitmapDisabled/2` Since: 2.9.1 (available in `m:wxBitmapButton` only in previous versions) """. @@ -366,14 +397,13 @@ setBitmapFocus(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxButton_SetBitmapFocus). -%% @doc See external documentation. -doc """ Sets the bitmap label for the button. -Remark: This is the bitmap used for the unselected state, and for all other -states if no other bitmaps are provided. +Remark: This is the bitmap used for the unselected state, and for all other states if no +other bitmaps are provided. -See: `SetBitmap()` (not implemented in wx), `getBitmapLabel/1` +See: `getBitmapLabel/1` Since: 2.9.1 (available in `m:wxBitmapButton` only in previous versions) """. @@ -384,559 +414,376 @@ setBitmapLabel(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxButton_SetBitmapLabel). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxButton()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxButton), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxCalendarCtrl.erl b/lib/wx/src/gen/wxCalendarCtrl.erl index 9124c769ac58..17aea04e60f4 100644 --- a/lib/wx/src/gen/wxCalendarCtrl.erl +++ b/lib/wx/src/gen/wxCalendarCtrl.erl @@ -20,59 +20,81 @@ -module(wxCalendarCtrl). -moduledoc """ -Functions for wxCalendarCtrl class +The calendar control allows the user to pick a date. -The calendar control allows the user to pick a date. The user can move the -current selection using the keyboard and select the date (generating -`EVT_CALENDAR` event) by pressing `` or double clicking it. +The user can move the current selection using the keyboard and select the date +(generating `EVT_CALENDAR` event) by pressing `` or double clicking it. -Generic calendar has advanced possibilities for the customization of its -display, described below. If you want to use these possibilities on every -platform, use wxGenericCalendarCtrl instead of `m:wxCalendarCtrl`. +Generic calendar has advanced possibilities for the customization of its display, +described below. If you want to use these possibilities on every platform, use +wxGenericCalendarCtrl instead of `m:wxCalendarCtrl`. -All global settings (such as colours and fonts used) can, of course, be changed. -But also, the display style for each day in the month can be set independently -using `m:wxCalendarDateAttr` class. +All global settings (such as colours and fonts used) can, of course, be changed. But +also, the display style for each day in the month can be set independently using `m:wxCalendarDateAttr` +class. -An item without custom attributes is drawn with the default colours and font and -without border, but setting custom attributes with `setAttr/3` allows modifying -its appearance. Just create a custom attribute object and set it for the day you -want to be displayed specially (note that the control will take ownership of the -pointer, i.e. it will delete it itself). A day may be marked as being a holiday, -even if it is not recognized as one by [`wx_datetime()`](`t:wx:wx_datetime/0`) -using the `wxCalendarDateAttr:setHoliday/2` method. +An item without custom attributes is drawn with the default colours and font and without +border, but setting custom attributes with `setAttr/3` allows modifying its appearance. Just create a +custom attribute object and set it for the day you want to be displayed specially (note +that the control will take ownership of the pointer, i.e. it will delete it itself). A day +may be marked as being a holiday, even if it is not recognized as one by `wx_datetime()` using the `wxCalendarDateAttr:setHoliday/2` method. -As the attributes are specified for each day, they may change when the month is -changed, so you will often want to update them in `EVT_CALENDAR_PAGE_CHANGED` -event handler. +As the attributes are specified for each day, they may change when the month is changed, +so you will often want to update them in `EVT_CALENDAR_PAGE_CHANGED` event handler. -If neither the `wxCAL_SUNDAY_FIRST` or `wxCAL_MONDAY_FIRST` style is given, the -first day of the week is determined from operating system's settings, if -possible. The native wxGTK calendar chooses the first weekday based on locale, -and these styles have no effect on it. +If neither the `wxCAL_SUNDAY_FIRST` or `wxCAL_MONDAY_FIRST` style is given, the first day +of the week is determined from operating system's settings, if possible. The native wxGTK +calendar chooses the first weekday based on locale, and these styles have no effect on it. -Styles +## Styles This class supports the following styles: -Note: Changing the selected date will trigger an EVT_CALENDAR_DAY, MONTH or YEAR -event as well as an EVT_CALENDAR_SEL_CHANGED event. +* wxCAL_SUNDAY_FIRST: Show Sunday as the first day in the week (not in wxGTK) + +* wxCAL_MONDAY_FIRST: Show Monday as the first day in the week (not in wxGTK) + +* wxCAL_SHOW_HOLIDAYS: Highlight holidays in the calendar (only generic) + +* wxCAL_NO_YEAR_CHANGE: Disable the year changing (deprecated, only generic) + +* wxCAL_NO_MONTH_CHANGE: Disable the month (and, implicitly, the year) changing + +* wxCAL_SHOW_SURROUNDING_WEEKS: Show the neighbouring weeks in the previous and next months +(only generic, always on for the native controls) + +* wxCAL_SEQUENTIAL_MONTH_SELECTION: Use alternative, more compact, style for the month and +year selection controls. (only generic) + +* wxCAL_SHOW_WEEK_NUMBERS: Show week numbers on the left side of the calendar. (not in +generic) See: -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_calendar), -`m:wxCalendarDateAttr`, `m:wxCalendarEvent`, `m:wxDatePickerCtrl` +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_calendar) + +* `m:wxCalendarDateAttr` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxCalendarEvent` -wxWidgets docs: -[wxCalendarCtrl](https://docs.wxwidgets.org/3.1/classwx_calendar_ctrl.html) +* `m:wxDatePickerCtrl` + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxCalendarCtrl](https://docs.wxwidgets.org/3.2/classwx_calendar_ctrl.html) ## Events Event types emitted from this class: -[`calendar_sel_changed`](`m:wxCalendarEvent`), -[`calendar_weekday_clicked`](`m:wxCalendarEvent`) + +* [`calendar_sel_changed`](`m:wxCalendarEvent`) + +* [`calendar_weekday_clicked`](`m:wxCalendarEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,enableHolidayDisplay/1,enableHolidayDisplay/2, @@ -128,21 +150,19 @@ Event types emitted from this class: {enableYearChange,2,"not available in wxWidgets-2.9 and later"}]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxCalendarCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxCalendarCtrl_new_0), wxe_util:rec(?wxCalendarCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxCalendarCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -150,7 +170,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Does the same as `create/4` method.". -spec new(Parent, Id, [Option]) -> wxCalendarCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -170,7 +189,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxCalendarCtrl_new_3), wxe_util:rec(?wxCalendarCtrl_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxCalendarCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -178,12 +197,10 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Creates the control. -See `wxWindow:new/3` for the meaning of the parameters and the control overview -for the possible styles. +See `wxWindow:new/3` for the meaning of the parameters and the control overview for the possible styles. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxCalendarCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -204,14 +221,12 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxCalendarCtrl_Create), wxe_util:rec(?wxCalendarCtrl_Create). -%% @doc See external documentation. -doc """ Sets the current date. -The `date` parameter must be valid and in the currently valid range as set by -`SetDateRange()` (not implemented in wx), otherwise the current date is not -changed and the function returns false and, additionally, triggers an assertion -failure if the date is invalid. +The `date` parameter must be valid and in the currently valid range as set by `SetDateRange()` +(not implemented in wx), otherwise the current date is not changed and the function +returns false and, additionally, triggers an assertion failure if the date is invalid. """. -spec setDate(This, Date) -> boolean() when This::wxCalendarCtrl(), Date::wx:wx_datetime(). @@ -221,7 +236,6 @@ setDate(#wx_ref{type=ThisT}=This,{{DateY,DateMo,DateD},{DateH,DateMi,DateS}}) wxe_util:queue_cmd(This,{DateD,DateMo,DateY,DateH,DateMi,DateS},?get_env(),?wxCalendarCtrl_SetDate), wxe_util:rec(?wxCalendarCtrl_SetDate). -%% @doc See external documentation. -doc "Gets the currently selected date.". -spec getDate(This) -> wx:wx_datetime() when This::wxCalendarCtrl(). @@ -230,7 +244,7 @@ getDate(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetDate), wxe_util:rec(?wxCalendarCtrl_GetDate). -%% @equiv enableYearChange(This, []) +-doc(#{equiv => enableYearChange(This, [])}). -spec enableYearChange(This) -> 'ok' when This::wxCalendarCtrl(). @@ -238,13 +252,12 @@ enableYearChange(This) when is_record(This, wx_ref) -> enableYearChange(This, []). -%% @doc See external documentation. -doc """ Deprecated: -This function should be used instead of changing `wxCAL_NO_YEAR_CHANGE` style -bit directly. It allows or disallows the user to change the year interactively. -Only in generic `m:wxCalendarCtrl`. +This function should be used instead of changing `wxCAL_NO_YEAR_CHANGE` style bit +directly. It allows or disallows the user to change the year interactively. Only in +generic `m:wxCalendarCtrl`. """. -spec enableYearChange(This, [Option]) -> 'ok' when This::wxCalendarCtrl(), @@ -257,7 +270,7 @@ enableYearChange(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxCalendarCtrl_EnableYearChange). -%% @equiv enableMonthChange(This, []) +-doc(#{equiv => enableMonthChange(This, [])}). -spec enableMonthChange(This) -> boolean() when This::wxCalendarCtrl(). @@ -265,16 +278,14 @@ enableMonthChange(This) when is_record(This, wx_ref) -> enableMonthChange(This, []). -%% @doc See external documentation. -doc """ -This function should be used instead of changing `wxCAL_NO_MONTH_CHANGE` style -bit. +This function should be used instead of changing `wxCAL\_NO\_MONTH\_CHANGE` style bit. -It allows or disallows the user to change the month interactively. Note that if -the month cannot be changed, the year cannot be changed neither. +It allows or disallows the user to change the month interactively. Note that if the month +cannot be changed, the year cannot be changed neither. -Return: true if the value of this option really changed or false if it was -already set to the requested value. +Return: true if the value of this option really changed or false if it was already set to +the requested value. """. -spec enableMonthChange(This, [Option]) -> boolean() when This::wxCalendarCtrl(), @@ -288,7 +299,7 @@ enableMonthChange(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxCalendarCtrl_EnableMonthChange), wxe_util:rec(?wxCalendarCtrl_EnableMonthChange). -%% @equiv enableHolidayDisplay(This, []) +-doc(#{equiv => enableHolidayDisplay(This, [])}). -spec enableHolidayDisplay(This) -> 'ok' when This::wxCalendarCtrl(). @@ -296,9 +307,8 @@ enableHolidayDisplay(This) when is_record(This, wx_ref) -> enableHolidayDisplay(This, []). -%% @doc See external documentation. -doc """ -This function should be used instead of changing `wxCAL_SHOW_HOLIDAYS` style bit +This function should be used instead of changing `wxCAL\_SHOW\_HOLIDAYS` style bit directly. It enables or disables the special highlighting of the holidays. @@ -314,12 +324,11 @@ enableHolidayDisplay(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxCalendarCtrl_EnableHolidayDisplay). -%% @doc See external documentation. -doc """ Set the colours used for painting the weekdays at the top of the control. -This method is currently only implemented in generic `m:wxCalendarCtrl` and does -nothing in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and does nothing +in the native versions. """. -spec setHeaderColours(This, ColFg, ColBg) -> 'ok' when This::wxCalendarCtrl(), ColFg::wx:wx_colour(), ColBg::wx:wx_colour(). @@ -328,12 +337,11 @@ setHeaderColours(#wx_ref{type=ThisT}=This,ColFg,ColBg) ?CLASS(ThisT,wxCalendarCtrl), wxe_util:queue_cmd(This,wxe_util:color(ColFg),wxe_util:color(ColBg),?get_env(),?wxCalendarCtrl_SetHeaderColours). -%% @doc See external documentation. -doc """ Gets the foreground colour of the header part of the calendar window. -This method is currently only implemented in generic `m:wxCalendarCtrl` and -always returns `wxNullColour` in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and always +returns `wxNullColour` in the native versions. See: `setHeaderColours/3` """. @@ -344,12 +352,11 @@ getHeaderColourFg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHeaderColourFg), wxe_util:rec(?wxCalendarCtrl_GetHeaderColourFg). -%% @doc See external documentation. -doc """ Gets the background colour of the header part of the calendar window. -This method is currently only implemented in generic `m:wxCalendarCtrl` and -always returns `wxNullColour` in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and always +returns `wxNullColour` in the native versions. See: `setHeaderColours/3` """. @@ -360,12 +367,11 @@ getHeaderColourBg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHeaderColourBg), wxe_util:rec(?wxCalendarCtrl_GetHeaderColourBg). -%% @doc See external documentation. -doc """ Set the colours to be used for highlighting the currently selected date. -This method is currently only implemented in generic `m:wxCalendarCtrl` and does -nothing in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and does nothing +in the native versions. """. -spec setHighlightColours(This, ColFg, ColBg) -> 'ok' when This::wxCalendarCtrl(), ColFg::wx:wx_colour(), ColBg::wx:wx_colour(). @@ -374,14 +380,13 @@ setHighlightColours(#wx_ref{type=ThisT}=This,ColFg,ColBg) ?CLASS(ThisT,wxCalendarCtrl), wxe_util:queue_cmd(This,wxe_util:color(ColFg),wxe_util:color(ColBg),?get_env(),?wxCalendarCtrl_SetHighlightColours). -%% @doc See external documentation. -doc """ Gets the foreground highlight colour. Only in generic `m:wxCalendarCtrl`. -This method is currently only implemented in generic `m:wxCalendarCtrl` and -always returns `wxNullColour` in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and always +returns `wxNullColour` in the native versions. See: `setHighlightColours/3` """. @@ -392,14 +397,13 @@ getHighlightColourFg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHighlightColourFg), wxe_util:rec(?wxCalendarCtrl_GetHighlightColourFg). -%% @doc See external documentation. -doc """ Gets the background highlight colour. Only in generic `m:wxCalendarCtrl`. -This method is currently only implemented in generic `m:wxCalendarCtrl` and -always returns `wxNullColour` in the native versions. +This method is currently only implemented in generic `m:wxCalendarCtrl` and always +returns `wxNullColour` in the native versions. See: `setHighlightColours/3` """. @@ -410,13 +414,12 @@ getHighlightColourBg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHighlightColourBg), wxe_util:rec(?wxCalendarCtrl_GetHighlightColourBg). -%% @doc See external documentation. -doc """ Sets the colours to be used for the holidays highlighting. -This method is only implemented in the generic version of the control and does -nothing in the native ones. It should also only be called if the window style -includes `wxCAL_SHOW_HOLIDAYS` flag or `enableHolidayDisplay/2` had been called. +This method is only implemented in the generic version of the control and does nothing in +the native ones. It should also only be called if the window style includes `wxCAL_SHOW_HOLIDAYS` +flag or `enableHolidayDisplay/2` had been called. """. -spec setHolidayColours(This, ColFg, ColBg) -> 'ok' when This::wxCalendarCtrl(), ColFg::wx:wx_colour(), ColBg::wx:wx_colour(). @@ -425,12 +428,11 @@ setHolidayColours(#wx_ref{type=ThisT}=This,ColFg,ColBg) ?CLASS(ThisT,wxCalendarCtrl), wxe_util:queue_cmd(This,wxe_util:color(ColFg),wxe_util:color(ColBg),?get_env(),?wxCalendarCtrl_SetHolidayColours). -%% @doc See external documentation. -doc """ Return the foreground colour currently used for holiday highlighting. -Only useful with generic `m:wxCalendarCtrl` as native versions currently don't -support holidays display at all and always return `wxNullColour`. +Only useful with generic `m:wxCalendarCtrl` as native versions currently don't support +holidays display at all and always return `wxNullColour`. See: `setHolidayColours/3` """. @@ -441,12 +443,11 @@ getHolidayColourFg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHolidayColourFg), wxe_util:rec(?wxCalendarCtrl_GetHolidayColourFg). -%% @doc See external documentation. -doc """ Return the background colour currently used for holiday highlighting. -Only useful with generic `m:wxCalendarCtrl` as native versions currently don't -support holidays display at all and always return `wxNullColour`. +Only useful with generic `m:wxCalendarCtrl` as native versions currently don't support +holidays display at all and always return `wxNullColour`. See: `setHolidayColours/3` """. @@ -457,7 +458,6 @@ getHolidayColourBg(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarCtrl_GetHolidayColourBg), wxe_util:rec(?wxCalendarCtrl_GetHolidayColourBg). -%% @doc See external documentation. -doc """ Returns the attribute for the given date (should be in the range 1...31). @@ -471,12 +471,10 @@ getAttr(#wx_ref{type=ThisT}=This,Day) wxe_util:queue_cmd(This,Day,?get_env(),?wxCalendarCtrl_GetAttr), wxe_util:rec(?wxCalendarCtrl_GetAttr). -%% @doc See external documentation. -doc """ Associates the attribute with the specified date (in the range 1...31). -If the pointer is NULL, the items attribute is cleared. Only in generic -`m:wxCalendarCtrl`. +If the pointer is NULL, the items attribute is cleared. Only in generic `m:wxCalendarCtrl`. """. -spec setAttr(This, Day, Attr) -> 'ok' when This::wxCalendarCtrl(), Day::integer(), Attr::wxCalendarDateAttr:wxCalendarDateAttr(). @@ -486,12 +484,11 @@ setAttr(#wx_ref{type=ThisT}=This,Day,#wx_ref{type=AttrT}=Attr) ?CLASS(AttrT,wxCalendarDateAttr), wxe_util:queue_cmd(This,Day,Attr,?get_env(),?wxCalendarCtrl_SetAttr). -%% @doc See external documentation. -doc """ Marks the specified day as being a holiday in the current month. -This method is only implemented in the generic version of the control and does -nothing in the native ones. +This method is only implemented in the generic version of the control and does nothing in +the native ones. """. -spec setHoliday(This, Day) -> 'ok' when This::wxCalendarCtrl(), Day::integer(). @@ -500,7 +497,6 @@ setHoliday(#wx_ref{type=ThisT}=This,Day) ?CLASS(ThisT,wxCalendarCtrl), wxe_util:queue_cmd(This,Day,?get_env(),?wxCalendarCtrl_SetHoliday). -%% @doc See external documentation. -doc """ Clears any attributes associated with the given day (in the range 1...31). @@ -513,15 +509,14 @@ resetAttr(#wx_ref{type=ThisT}=This,Day) ?CLASS(ThisT,wxCalendarCtrl), wxe_util:queue_cmd(This,Day,?get_env(),?wxCalendarCtrl_ResetAttr). -%% @doc See external documentation. -%%
Wd = ?wxDateTime_Sun | ?wxDateTime_Mon | ?wxDateTime_Tue | ?wxDateTime_Wed | ?wxDateTime_Thu | ?wxDateTime_Fri | ?wxDateTime_Sat | ?wxDateTime_Inv_WeekDay -%%
Res = ?wxCAL_HITTEST_NOWHERE | ?wxCAL_HITTEST_HEADER | ?wxCAL_HITTEST_DAY | ?wxCAL_HITTEST_INCMONTH | ?wxCAL_HITTEST_DECMONTH | ?wxCAL_HITTEST_SURROUNDING_WEEK | ?wxCAL_HITTEST_WEEK -doc """ -Returns one of wxCalendarHitTestResult constants and fills either `date` or `wd` -pointer with the corresponding value depending on the hit test code. +Returns one of wxCalendarHitTestResult constants and fills either `date` or `wd` pointer +with the corresponding value depending on the hit test code. Not implemented in wxGTK currently. """. +%% Wd = ?wxDateTime_Sun | ?wxDateTime_Mon | ?wxDateTime_Tue | ?wxDateTime_Wed | ?wxDateTime_Thu | ?wxDateTime_Fri | ?wxDateTime_Sat | ?wxDateTime_Inv_WeekDay +%% Res = ?wxCAL_HITTEST_NOWHERE | ?wxCAL_HITTEST_HEADER | ?wxCAL_HITTEST_DAY | ?wxCAL_HITTEST_INCMONTH | ?wxCAL_HITTEST_DECMONTH | ?wxCAL_HITTEST_SURROUNDING_WEEK | ?wxCAL_HITTEST_WEEK -spec hitTest(This, Pos) -> Result when Result ::{Res ::wx:wx_enum(), Date::wx:wx_datetime(), Wd::wx:wx_enum()}, This::wxCalendarCtrl(), Pos::{X::integer(), Y::integer()}. @@ -531,562 +526,378 @@ hitTest(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxCalendarCtrl_HitTest), wxe_util:rec(?wxCalendarCtrl_HitTest). -%% @doc Destroys this object, do not use object again --doc "Destroys the control.". +-doc "Destroys the object". -spec destroy(This::wxCalendarCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCalendarCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxCalendarDateAttr.erl b/lib/wx/src/gen/wxCalendarDateAttr.erl index 16e2792e3b40..baaf63714625 100644 --- a/lib/wx/src/gen/wxCalendarDateAttr.erl +++ b/lib/wx/src/gen/wxCalendarDateAttr.erl @@ -20,15 +20,13 @@ -module(wxCalendarDateAttr). -moduledoc """ -Functions for wxCalendarDateAttr class +`m:wxCalendarDateAttr` is a custom attributes for a calendar date. -`m:wxCalendarDateAttr` is a custom attributes for a calendar date. The objects -of this class are used with `m:wxCalendarCtrl`. +The objects of this class are used with `m:wxCalendarCtrl`. See: `m:wxCalendarCtrl` -wxWidgets docs: -[wxCalendarDateAttr](https://docs.wxwidgets.org/3.1/classwx_calendar_date_attr.html) +wxWidgets docs: [wxCalendarDateAttr](https://docs.wxwidgets.org/3.2/classwx_calendar_date_attr.html) """. -include("wxe.hrl"). -export([destroy/1,getBackgroundColour/1,getBorder/1,getBorderColour/1,getFont/1, @@ -41,27 +39,17 @@ wxWidgets docs: -type wxCalendarDateAttr() :: wx:wx_object(). -export_type([wxCalendarDateAttr/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxCalendarDateAttr(). new() -> new([]). -%% @doc See external documentation. -%%
Also:
-%% new([Option]) -> wxCalendarDateAttr() when
-%% Option :: {'colText', wx:wx_colour()}
-%% | {'colBack', wx:wx_colour()}
-%% | {'colBorder', wx:wx_colour()}
-%% | {'font', wxFont:wxFont()}
-%% | {'border', wx:wx_enum()}.
-%% -%%
Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -doc "Constructor for specifying all `m:wxCalendarDateAttr` properties.". +%% Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -spec new(Border) -> wxCalendarDateAttr() when Border::wx:wx_enum(); ([Option]) -> wxCalendarDateAttr() when @@ -86,9 +74,8 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxCalendarDateAttr_new_1), wxe_util:rec(?wxCalendarDateAttr_new_1). -%% @doc See external documentation. -%%
Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -doc "Constructor using default properties except the given border.". +%% Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -spec new(Border, [Option]) -> wxCalendarDateAttr() when Border::wx:wx_enum(), Option :: {'colBorder', wx:wx_colour()}. @@ -100,7 +87,6 @@ new(Border, Options) wxe_util:queue_cmd(Border, Opts,?get_env(),?wxCalendarDateAttr_new_2), wxe_util:rec(?wxCalendarDateAttr_new_2). -%% @doc See external documentation. -doc "Sets the text (foreground) colour to use.". -spec setTextColour(This, ColText) -> 'ok' when This::wxCalendarDateAttr(), ColText::wx:wx_colour(). @@ -109,7 +95,6 @@ setTextColour(#wx_ref{type=ThisT}=This,ColText) ?CLASS(ThisT,wxCalendarDateAttr), wxe_util:queue_cmd(This,wxe_util:color(ColText),?get_env(),?wxCalendarDateAttr_SetTextColour). -%% @doc See external documentation. -doc "Sets the text background colour to use.". -spec setBackgroundColour(This, ColBack) -> 'ok' when This::wxCalendarDateAttr(), ColBack::wx:wx_colour(). @@ -118,7 +103,6 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) ?CLASS(ThisT,wxCalendarDateAttr), wxe_util:queue_cmd(This,wxe_util:color(ColBack),?get_env(),?wxCalendarDateAttr_SetBackgroundColour). -%% @doc See external documentation. -doc "Sets the border colour to use.". -spec setBorderColour(This, Col) -> 'ok' when This::wxCalendarDateAttr(), Col::wx:wx_colour(). @@ -127,7 +111,6 @@ setBorderColour(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxCalendarDateAttr), wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxCalendarDateAttr_SetBorderColour). -%% @doc See external documentation. -doc "Sets the font to use.". -spec setFont(This, Font) -> 'ok' when This::wxCalendarDateAttr(), Font::wxFont:wxFont(). @@ -136,9 +119,8 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxCalendarDateAttr_SetFont). -%% @doc See external documentation. -%%
Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -doc "Sets the border to use.". +%% Border = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -spec setBorder(This, Border) -> 'ok' when This::wxCalendarDateAttr(), Border::wx:wx_enum(). setBorder(#wx_ref{type=ThisT}=This,Border) @@ -146,7 +128,6 @@ setBorder(#wx_ref{type=ThisT}=This,Border) ?CLASS(ThisT,wxCalendarDateAttr), wxe_util:queue_cmd(This,Border,?get_env(),?wxCalendarDateAttr_SetBorder). -%% @doc See external documentation. -doc "If `holiday` is true, this calendar day will be displayed as a holiday.". -spec setHoliday(This, Holiday) -> 'ok' when This::wxCalendarDateAttr(), Holiday::boolean(). @@ -155,7 +136,6 @@ setHoliday(#wx_ref{type=ThisT}=This,Holiday) ?CLASS(ThisT,wxCalendarDateAttr), wxe_util:queue_cmd(This,Holiday,?get_env(),?wxCalendarDateAttr_SetHoliday). -%% @doc See external documentation. -doc "Returns true if a non-default text foreground colour is set.". -spec hasTextColour(This) -> boolean() when This::wxCalendarDateAttr(). @@ -164,7 +144,6 @@ hasTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_HasTextColour), wxe_util:rec(?wxCalendarDateAttr_HasTextColour). -%% @doc See external documentation. -doc "Returns true if a non-default text background colour is set.". -spec hasBackgroundColour(This) -> boolean() when This::wxCalendarDateAttr(). @@ -173,7 +152,6 @@ hasBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_HasBackgroundColour), wxe_util:rec(?wxCalendarDateAttr_HasBackgroundColour). -%% @doc See external documentation. -doc "Returns true if a non-default border colour is set.". -spec hasBorderColour(This) -> boolean() when This::wxCalendarDateAttr(). @@ -182,7 +160,6 @@ hasBorderColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_HasBorderColour), wxe_util:rec(?wxCalendarDateAttr_HasBorderColour). -%% @doc See external documentation. -doc "Returns true if a non-default font is set.". -spec hasFont(This) -> boolean() when This::wxCalendarDateAttr(). @@ -191,7 +168,6 @@ hasFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_HasFont), wxe_util:rec(?wxCalendarDateAttr_HasFont). -%% @doc See external documentation. -doc "Returns true if a non-default (i.e. any) border is set.". -spec hasBorder(This) -> boolean() when This::wxCalendarDateAttr(). @@ -200,7 +176,6 @@ hasBorder(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_HasBorder), wxe_util:rec(?wxCalendarDateAttr_HasBorder). -%% @doc See external documentation. -doc "Returns true if this calendar day is displayed as a holiday.". -spec isHoliday(This) -> boolean() when This::wxCalendarDateAttr(). @@ -209,7 +184,6 @@ isHoliday(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_IsHoliday), wxe_util:rec(?wxCalendarDateAttr_IsHoliday). -%% @doc See external documentation. -doc "Returns the text colour set for the calendar date.". -spec getTextColour(This) -> wx:wx_colour4() when This::wxCalendarDateAttr(). @@ -218,7 +192,6 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_GetTextColour), wxe_util:rec(?wxCalendarDateAttr_GetTextColour). -%% @doc See external documentation. -doc "Returns the background colour set for the calendar date.". -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxCalendarDateAttr(). @@ -227,7 +200,6 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_GetBackgroundColour), wxe_util:rec(?wxCalendarDateAttr_GetBackgroundColour). -%% @doc See external documentation. -doc "Returns the border colour set for the calendar date.". -spec getBorderColour(This) -> wx:wx_colour4() when This::wxCalendarDateAttr(). @@ -236,7 +208,6 @@ getBorderColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_GetBorderColour), wxe_util:rec(?wxCalendarDateAttr_GetBorderColour). -%% @doc See external documentation. -doc "Returns the font set for the calendar date.". -spec getFont(This) -> wxFont:wxFont() when This::wxCalendarDateAttr(). @@ -245,9 +216,8 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_GetFont), wxe_util:rec(?wxCalendarDateAttr_GetFont). -%% @doc See external documentation. -%%
Res = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -doc "Returns the border set for the calendar date.". +%% Res = ?wxCAL_BORDER_NONE | ?wxCAL_BORDER_SQUARE | ?wxCAL_BORDER_ROUND -spec getBorder(This) -> wx:wx_enum() when This::wxCalendarDateAttr(). getBorder(#wx_ref{type=ThisT}=This) -> @@ -255,8 +225,7 @@ getBorder(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarDateAttr_GetBorder), wxe_util:rec(?wxCalendarDateAttr_GetBorder). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxCalendarDateAttr()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCalendarDateAttr), diff --git a/lib/wx/src/gen/wxCalendarEvent.erl b/lib/wx/src/gen/wxCalendarEvent.erl index 4c6a8d0a6e64..5bc464b3d6b3 100644 --- a/lib/wx/src/gen/wxCalendarEvent.erl +++ b/lib/wx/src/gen/wxCalendarEvent.erl @@ -20,17 +20,19 @@ -module(wxCalendarEvent). -moduledoc """ -Functions for wxCalendarEvent class - The `m:wxCalendarEvent` class is used together with `m:wxCalendarCtrl`. See: `m:wxCalendarCtrl` -This class is derived (and can use functions) from: `m:wxDateEvent` -`m:wxCommandEvent` `m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxDateEvent` + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxCalendarEvent](https://docs.wxwidgets.org/3.1/classwx_calendar_event.html) +wxWidgets docs: [wxCalendarEvent](https://docs.wxwidgets.org/3.2/classwx_calendar_event.html) """. -include("wxe.hrl"). -export([getDate/1,getWeekDay/1]). @@ -45,21 +47,19 @@ wxWidgets docs: -include("wx.hrl"). -type wxCalendarEventType() :: 'calendar_sel_changed' | 'calendar_day_changed' | 'calendar_month_changed' | 'calendar_year_changed' | 'calendar_doubleclicked' | 'calendar_weekday_clicked'. -export_type([wxCalendarEvent/0, wxCalendar/0, wxCalendarEventType/0]). -%% @hidden -doc false. parent_class(wxDateEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -%%
Res = ?wxDateTime_Sun | ?wxDateTime_Mon | ?wxDateTime_Tue | ?wxDateTime_Wed | ?wxDateTime_Thu | ?wxDateTime_Fri | ?wxDateTime_Sat | ?wxDateTime_Inv_WeekDay -doc """ -Returns the week day on which the user clicked in `EVT_CALENDAR_WEEKDAY_CLICKED` +Returns the week day on which the user clicked in `EVT\_CALENDAR\_WEEKDAY\_CLICKED` handler. It doesn't make sense to call this function in other handlers. """. +%% Res = ?wxDateTime_Sun | ?wxDateTime_Mon | ?wxDateTime_Tue | ?wxDateTime_Wed | ?wxDateTime_Thu | ?wxDateTime_Fri | ?wxDateTime_Sat | ?wxDateTime_Inv_WeekDay -spec getWeekDay(This) -> wx:wx_enum() when This::wxCalendarEvent(). getWeekDay(#wx_ref{type=ThisT}=This) -> @@ -67,7 +67,6 @@ getWeekDay(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCalendarEvent_GetWeekDay), wxe_util:rec(?wxCalendarEvent_GetWeekDay). -%% @doc See external documentation. -doc "Returns the date.". -spec getDate(This) -> wx:wx_datetime() when This::wxCalendarEvent(). @@ -78,58 +77,40 @@ getDate(#wx_ref{type=ThisT}=This) -> %% From wxDateEvent %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxCaret.erl b/lib/wx/src/gen/wxCaret.erl index 4b4b25f08f4f..50ffef37692e 100644 --- a/lib/wx/src/gen/wxCaret.erl +++ b/lib/wx/src/gen/wxCaret.erl @@ -20,20 +20,18 @@ -module(wxCaret). -moduledoc """ -Functions for wxCaret class +A caret is a blinking cursor showing the position where the typed text will appear. -A caret is a blinking cursor showing the position where the typed text will -appear. Text controls usually have their own caret but `m:wxCaret` provides a -way to use a caret in other windows. +Text controls usually have their own caret but `m:wxCaret` provides a way to use a caret +in other windows. -Currently, the caret appears as a rectangle of the given size. In the future, it -will be possible to specify a bitmap to be used for the caret shape. +Currently, the caret appears as a rectangle of the given size. In the future, it will be +possible to specify a bitmap to be used for the caret shape. -A caret is always associated with a window and the current caret can be -retrieved using `wxWindow:getCaret/1`. The same caret can't be reused in two -different windows. +A caret is always associated with a window and the current caret can be retrieved using `wxWindow:getCaret/1`. +The same caret can't be reused in two different windows. -wxWidgets docs: [wxCaret](https://docs.wxwidgets.org/3.1/classwx_caret.html) +wxWidgets docs: [wxCaret](https://docs.wxwidgets.org/3.2/classwx_caret.html) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getBlinkTime/0,getPosition/1,getSize/1, @@ -45,11 +43,10 @@ wxWidgets docs: [wxCaret](https://docs.wxwidgets.org/3.1/classwx_caret.html) -type wxCaret() :: wx:wx_object(). -export_type([wxCaret/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new(Window, Size) -> wxCaret() when Window::wxWindow:wxWindow(), Size::{W::integer(), H::integer()}. new(#wx_ref{type=WindowT}=Window,{SizeW,SizeH} = Size) @@ -58,11 +55,7 @@ new(#wx_ref{type=WindowT}=Window,{SizeW,SizeH} = Size) wxe_util:queue_cmd(Window,Size,?get_env(),?wxCaret_new_2), wxe_util:rec(?wxCaret_new_2). -%% @doc See external documentation. --doc """ -Creates a caret with the given size (in pixels) and associates it with the -`window`. -""". +-doc "Creates a caret with the given size (in pixels) and associates it with the `window`.". -spec new(Window, Width, Height) -> wxCaret() when Window::wxWindow:wxWindow(), Width::integer(), Height::integer(). new(#wx_ref{type=WindowT}=Window,Width,Height) @@ -71,7 +64,7 @@ new(#wx_ref{type=WindowT}=Window,Width,Height) wxe_util:queue_cmd(Window,Width,Height,?get_env(),?wxCaret_new_3), wxe_util:rec(?wxCaret_new_3). -%% @doc See external documentation. +-doc "". -spec create(This, Window, Size) -> boolean() when This::wxCaret(), Window::wxWindow:wxWindow(), Size::{W::integer(), H::integer()}. create(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,{SizeW,SizeH} = Size) @@ -81,10 +74,9 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,{SizeW,SizeH} = Siz wxe_util:queue_cmd(This,Window,Size,?get_env(),?wxCaret_Create_2), wxe_util:rec(?wxCaret_Create_2). -%% @doc See external documentation. -doc """ -Creates a caret with the given size (in pixels) and associates it with the -`window` (same as the equivalent constructors). +Creates a caret with the given size (in pixels) and associates it with the `window` (same +as the equivalent constructors). """. -spec create(This, Window, Width, Height) -> boolean() when This::wxCaret(), Window::wxWindow:wxWindow(), Width::integer(), Height::integer(). @@ -95,18 +87,17 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,Width,Height) wxe_util:queue_cmd(This,Window,Width,Height,?get_env(),?wxCaret_Create_3), wxe_util:rec(?wxCaret_Create_3). -%% @doc See external documentation. -doc """ -Returns the blink time which is measured in milliseconds and is the time elapsed -between 2 inversions of the caret (blink time of the caret is the same for all -carets, so this functions is static). +Returns the blink time which is measured in milliseconds and is the time elapsed between +2 inversions of the caret (blink time of the caret is the same for all carets, so this +functions is static). """. -spec getBlinkTime() -> integer(). getBlinkTime() -> wxe_util:queue_cmd(?get_env(), ?wxCaret_GetBlinkTime), wxe_util:rec(?wxCaret_GetBlinkTime). -%% @doc See external documentation. +-doc "". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxCaret(). getPosition(#wx_ref{type=ThisT}=This) -> @@ -114,7 +105,7 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCaret_GetPosition), wxe_util:rec(?wxCaret_GetPosition). -%% @doc See external documentation. +-doc "". -spec getSize(This) -> {W::integer(), H::integer()} when This::wxCaret(). getSize(#wx_ref{type=ThisT}=This) -> @@ -122,7 +113,6 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCaret_GetSize), wxe_util:rec(?wxCaret_GetSize). -%% @doc See external documentation. -doc "Get the window the caret is associated with.". -spec getWindow(This) -> wxWindow:wxWindow() when This::wxCaret(). @@ -131,7 +121,6 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCaret_GetWindow), wxe_util:rec(?wxCaret_GetWindow). -%% @doc See external documentation. -doc "Hides the caret, same as Show(false).". -spec hide(This) -> 'ok' when This::wxCaret(). @@ -139,7 +128,6 @@ hide(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxCaret), wxe_util:queue_cmd(This,?get_env(),?wxCaret_Hide). -%% @doc See external documentation. -doc "Returns true if the caret was created successfully.". -spec isOk(This) -> boolean() when This::wxCaret(). @@ -148,11 +136,10 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCaret_IsOk), wxe_util:rec(?wxCaret_IsOk). -%% @doc See external documentation. -doc """ -Returns true if the caret is visible and false if it is permanently hidden (if -it is blinking and not shown currently but will be after the next blink, this -method still returns true). +Returns true if the caret is visible and false if it is permanently hidden (if it is +blinking and not shown currently but will be after the next blink, this method still +returns true). """. -spec isVisible(This) -> boolean() when This::wxCaret(). @@ -161,7 +148,7 @@ isVisible(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCaret_IsVisible), wxe_util:rec(?wxCaret_IsVisible). -%% @doc See external documentation. +-doc "". -spec move(This, Pt) -> 'ok' when This::wxCaret(), Pt::{X::integer(), Y::integer()}. move(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) @@ -169,7 +156,6 @@ move(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxCaret), wxe_util:queue_cmd(This,Pt,?get_env(),?wxCaret_Move_1). -%% @doc See external documentation. -doc "Move the caret to given position (in logical coordinates).". -spec move(This, X, Y) -> 'ok' when This::wxCaret(), X::integer(), Y::integer(). @@ -178,13 +164,13 @@ move(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxCaret), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxCaret_Move_2). -%% @doc See external documentation. -doc """ Sets the blink time for all the carets. -Warning: Under Windows, this function will change the blink time for all carets -permanently (until the next time it is called), even for carets in other -applications. +Warning: + +Under Windows, this function will change the blink time for all carets permanently (until +the next time it is called), even for carets in other applications. See: `getBlinkTime/0` """. @@ -194,7 +180,7 @@ setBlinkTime(Milliseconds) when is_integer(Milliseconds) -> wxe_util:queue_cmd(Milliseconds,?get_env(),?wxCaret_SetBlinkTime). -%% @doc See external documentation. +-doc "". -spec setSize(This, Size) -> 'ok' when This::wxCaret(), Size::{W::integer(), H::integer()}. setSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) @@ -202,7 +188,6 @@ setSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxCaret), wxe_util:queue_cmd(This,Size,?get_env(),?wxCaret_SetSize_1). -%% @doc See external documentation. -doc "Changes the size of the caret.". -spec setSize(This, Width, Height) -> 'ok' when This::wxCaret(), Width::integer(), Height::integer(). @@ -211,7 +196,7 @@ setSize(#wx_ref{type=ThisT}=This,Width,Height) ?CLASS(ThisT,wxCaret), wxe_util:queue_cmd(This,Width,Height,?get_env(),?wxCaret_SetSize_2). -%% @equiv show(This, []) +-doc(#{equiv => show(This, [])}). -spec show(This) -> 'ok' when This::wxCaret(). @@ -219,12 +204,11 @@ show(This) when is_record(This, wx_ref) -> show(This, []). -%% @doc See external documentation. -doc """ Shows or hides the caret. -Notice that if the caret was hidden N times, it must be shown N times as well to -reappear on the screen. +Notice that if the caret was hidden N times, it must be shown N times as well to reappear +on the screen. """. -spec show(This, [Option]) -> 'ok' when This::wxCaret(), @@ -237,8 +221,7 @@ show(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxCaret_Show). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxCaret()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCaret), diff --git a/lib/wx/src/gen/wxCheckBox.erl b/lib/wx/src/gen/wxCheckBox.erl index 019cb3f2fd0d..3d1c7a5a96b1 100644 --- a/lib/wx/src/gen/wxCheckBox.erl +++ b/lib/wx/src/gen/wxCheckBox.erl @@ -20,29 +20,46 @@ -module(wxCheckBox). -moduledoc """ -Functions for wxCheckBox class +A checkbox is a labelled box which by default is either on (checkmark is visible) or off +(no checkmark). -A checkbox is a labelled box which by default is either on (checkmark is -visible) or off (no checkmark). Optionally (when the wxCHK_3STATE style flag is -set) it can have a third state, called the mixed or undetermined state. Often -this is used as a "Does Not Apply" state. +Optionally (when the wxCHK_3STATE style flag is set) it can have a third state, called +the mixed or undetermined state. Often this is used as a "Does Not Apply" state. -Styles +## Styles This class supports the following styles: -See: `m:wxRadioButton`, `m:wxCommandEvent` +* wxCHK_2STATE: Create a 2-state checkbox. This is the default. -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* wxCHK_3STATE: Create a 3-state checkbox. Not implemented in wxGTK1. -wxWidgets docs: -[wxCheckBox](https://docs.wxwidgets.org/3.1/classwx_check_box.html) +* wxCHK_ALLOW_3RD_STATE_FOR_USER: By default a user can't set a 3-state checkbox to the +third state. It can only be done from code. Using this flags allows the user to set the +checkbox to the third state by clicking. + +* wxALIGN_RIGHT: Makes the text appear on the left of the checkbox. + +See: +* `m:wxRadioButton` + +* `m:wxCommandEvent` + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxCheckBox](https://docs.wxwidgets.org/3.2/classwx_check_box.html) ## Events Event types emitted from this class: -[`command_checkbox_clicked`](`m:wxCommandEvent`) + +* [`command_checkbox_clicked`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,get3StateValue/1,getValue/1,is3State/1, @@ -91,25 +108,23 @@ Event types emitted from this class: -type wxCheckBox() :: wx:wx_object(). -export_type([wxCheckBox/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new() -> wxCheckBox(). new() -> wxe_util:queue_cmd(?get_env(), ?wxCheckBox_new_0), wxe_util:rec(?wxCheckBox_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxCheckBox() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -117,11 +132,10 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> new(Parent,Id,Label, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a checkbox. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new(Parent, Id, Label, [Option]) -> wxCheckBox() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), @@ -142,7 +156,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(Parent,Id,Label_UC, Opts,?get_env(),?wxCheckBox_new_4), wxe_util:rec(?wxCheckBox_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxCheckBox(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -150,7 +164,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> create(This,Parent,Id,Label, []). -%% @doc See external documentation. -doc """ Creates the checkbox for two-step construction. @@ -176,7 +189,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(This,Parent,Id,Label_UC, Opts,?get_env(),?wxCheckBox_Create), wxe_util:rec(?wxCheckBox_Create). -%% @doc See external documentation. -doc """ Gets the state of a 2-state checkbox. @@ -189,13 +201,12 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCheckBox_GetValue), wxe_util:rec(?wxCheckBox_GetValue). -%% @doc See external documentation. -%%
Res = ?wxCHK_UNCHECKED | ?wxCHK_CHECKED | ?wxCHK_UNDETERMINED -doc """ Gets the state of a 3-state checkbox. Asserts when the function is used with a 2-state checkbox. """. +%% Res = ?wxCHK_UNCHECKED | ?wxCHK_CHECKED | ?wxCHK_UNDETERMINED -spec get3StateValue(This) -> wx:wx_enum() when This::wxCheckBox(). get3StateValue(#wx_ref{type=ThisT}=This) -> @@ -203,12 +214,11 @@ get3StateValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCheckBox_Get3StateValue), wxe_util:rec(?wxCheckBox_Get3StateValue). -%% @doc See external documentation. -doc """ Returns whether or not the user can set the checkbox to the third state. -Return: true if the user can set the third state of this checkbox, false if it -can only be set programmatically or if it's a 2-state checkbox. +Return: true if the user can set the third state of this checkbox, false if it can only +be set programmatically or if it's a 2-state checkbox. """. -spec is3rdStateAllowedForUser(This) -> boolean() when This::wxCheckBox(). @@ -217,12 +227,10 @@ is3rdStateAllowedForUser(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCheckBox_Is3rdStateAllowedForUser), wxe_util:rec(?wxCheckBox_Is3rdStateAllowedForUser). -%% @doc See external documentation. -doc """ Returns whether or not the checkbox is a 3-state checkbox. -Return: true if this checkbox is a 3-state checkbox, false if it's a 2-state -checkbox. +Return: true if this checkbox is a 3-state checkbox, false if it's a 2-state checkbox. """. -spec is3State(This) -> boolean() when This::wxCheckBox(). @@ -231,10 +239,9 @@ is3State(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCheckBox_Is3State), wxe_util:rec(?wxCheckBox_Is3State). -%% @doc See external documentation. -doc """ -This is just a maybe more readable synonym for `getValue/1`: just as the latter, -it returns true if the checkbox is checked and false otherwise. +This is just a maybe more readable synonym for `getValue/1`: just as the latter, it +returns true if the checkbox is checked and false otherwise. """. -spec isChecked(This) -> boolean() when This::wxCheckBox(). @@ -243,7 +250,6 @@ isChecked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCheckBox_IsChecked), wxe_util:rec(?wxCheckBox_IsChecked). -%% @doc See external documentation. -doc """ Sets the checkbox to the given state. @@ -256,8 +262,6 @@ setValue(#wx_ref{type=ThisT}=This,State) ?CLASS(ThisT,wxCheckBox), wxe_util:queue_cmd(This,State,?get_env(),?wxCheckBox_SetValue). -%% @doc See external documentation. -%%
State = ?wxCHK_UNCHECKED | ?wxCHK_CHECKED | ?wxCHK_UNDETERMINED -doc """ Sets the checkbox to the given state. @@ -266,6 +270,7 @@ This does not cause a `wxEVT_CHECKBOX` event to get emitted. Asserts when the checkbox is a 2-state checkbox and setting the state to wxCHK_UNDETERMINED. """. +%% State = ?wxCHK_UNCHECKED | ?wxCHK_CHECKED | ?wxCHK_UNDETERMINED -spec set3StateValue(This, State) -> 'ok' when This::wxCheckBox(), State::wx:wx_enum(). set3StateValue(#wx_ref{type=ThisT}=This,State) @@ -273,562 +278,378 @@ set3StateValue(#wx_ref{type=ThisT}=This,State) ?CLASS(ThisT,wxCheckBox), wxe_util:queue_cmd(This,State,?get_env(),?wxCheckBox_Set3StateValue). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the checkbox.". +-doc "Destroys the object". -spec destroy(This::wxCheckBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCheckBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxCheckListBox.erl b/lib/wx/src/gen/wxCheckListBox.erl index 81c43ee0fd78..bf684a8c984a 100644 --- a/lib/wx/src/gen/wxCheckListBox.erl +++ b/lib/wx/src/gen/wxCheckListBox.erl @@ -20,27 +20,42 @@ -module(wxCheckListBox). -moduledoc """ -Functions for wxCheckListBox class - A `m:wxCheckListBox` is like a `m:wxListBox`, but allows items to be checked or unchecked. -When using this class under Windows wxWidgets must be compiled with -wxUSE_OWNER_DRAWN set to 1. +When using this class under Windows wxWidgets must be compiled with wxUSE_OWNER_DRAWN set +to 1. + +See: +* `m:wxListBox` + +* `m:wxChoice` + +* `m:wxComboBox` + +* `m:wxListCtrl` + +* `m:wxCommandEvent` -See: `m:wxListBox`, `m:wxChoice`, `m:wxComboBox`, `m:wxListCtrl`, -`m:wxCommandEvent` +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxListBox` -`m:wxControlWithItems` `m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxListBox` -wxWidgets docs: -[wxCheckListBox](https://docs.wxwidgets.org/3.1/classwx_check_list_box.html) +* `m:wxControlWithItems` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxCheckListBox](https://docs.wxwidgets.org/3.2/classwx_check_list_box.html) ## Events Event types emitted from this class: -[`command_checklistbox_toggled`](`m:wxCommandEvent`) + +* [`command_checklistbox_toggled`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([check/2,check/3,destroy/1,isChecked/2,new/0,new/2,new/3]). @@ -91,7 +106,6 @@ Event types emitted from this class: -type wxCheckListBox() :: wx:wx_object(). -export_type([wxCheckListBox/0]). -%% @hidden -doc false. parent_class(wxListBox) -> true; parent_class(wxControlWithItems) -> true; @@ -100,14 +114,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxCheckListBox(). new() -> wxe_util:queue_cmd(?get_env(), ?wxCheckListBox_new_0), wxe_util:rec(?wxCheckListBox_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxCheckListBox() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -115,7 +128,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Constructor, creating and showing a list box.". -spec new(Parent, Id, [Option]) -> wxCheckListBox() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -137,7 +149,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxCheckListBox_new_3), wxe_util:rec(?wxCheckListBox_new_3). -%% @equiv check(This,Item, []) +-doc(#{equiv => check(This,Item, [])}). -spec check(This, Item) -> 'ok' when This::wxCheckListBox(), Item::integer(). @@ -145,12 +157,10 @@ check(This,Item) when is_record(This, wx_ref),is_integer(Item) -> check(This,Item, []). -%% @doc See external documentation. -doc """ Checks the given item. -Note that calling this method does not result in a `wxEVT_CHECKLISTBOX` event -being emitted. +Note that calling this method does not result in a `wxEVT_CHECKLISTBOX` event being emitted. """. -spec check(This, Item, [Option]) -> 'ok' when This::wxCheckListBox(), Item::integer(), @@ -163,7 +173,6 @@ check(#wx_ref{type=ThisT}=This,Item, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxCheckListBox_Check). -%% @doc See external documentation. -doc "Returns true if the given item is checked, false otherwise.". -spec isChecked(This, Item) -> boolean() when This::wxCheckListBox(), Item::integer(). @@ -173,657 +182,442 @@ isChecked(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxCheckListBox_IsChecked), wxe_util:rec(?wxCheckListBox_IsChecked). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the list box.". +-doc "Destroys the object". -spec destroy(This::wxCheckListBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCheckListBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxListBox -%% @hidden -doc false. setFirstItem(This,N) -> wxListBox:setFirstItem(This,N). -%% @hidden -doc false. hitTest(This,X,Y) -> wxListBox:hitTest(This,X,Y). -%% @hidden -doc false. hitTest(This,Point) -> wxListBox:hitTest(This,Point). -%% @hidden -doc false. set(This,Items) -> wxListBox:set(This,Items). -%% @hidden -doc false. isSelected(This,N) -> wxListBox:isSelected(This,N). -%% @hidden -doc false. insertItems(This,Items,Pos) -> wxListBox:insertItems(This,Items,Pos). -%% @hidden -doc false. getSelections(This) -> wxListBox:getSelections(This). -%% @hidden -doc false. deselect(This,N) -> wxListBox:deselect(This,N). %% From wxControlWithItems -%% @hidden -doc false. setStringSelection(This,String) -> wxControlWithItems:setStringSelection(This,String). -%% @hidden -doc false. setString(This,N,String) -> wxControlWithItems:setString(This,N,String). -%% @hidden -doc false. setSelection(This,N) -> wxControlWithItems:setSelection(This,N). -%% @hidden -doc false. select(This,N) -> wxControlWithItems:select(This,N). -%% @hidden -doc false. isEmpty(This) -> wxControlWithItems:isEmpty(This). -%% @hidden -doc false. insertStrings(This,Items,Pos,ClientsData) -> wxControlWithItems:insertStrings(This,Items,Pos,ClientsData). -%% @hidden -doc false. insertStrings(This,Items,Pos) -> wxControlWithItems:insertStrings(This,Items,Pos). -%% @hidden -doc false. insert(This,Item,Pos,ClientData) -> wxControlWithItems:insert(This,Item,Pos,ClientData). -%% @hidden -doc false. insert(This,Item,Pos) -> wxControlWithItems:insert(This,Item,Pos). -%% @hidden -doc false. getStringSelection(This) -> wxControlWithItems:getStringSelection(This). -%% @hidden -doc false. getString(This,N) -> wxControlWithItems:getString(This,N). -%% @hidden -doc false. getSelection(This) -> wxControlWithItems:getSelection(This). -%% @hidden -doc false. getCount(This) -> wxControlWithItems:getCount(This). -%% @hidden -doc false. setClientData(This,N,Data) -> wxControlWithItems:setClientData(This,N,Data). -%% @hidden -doc false. getClientData(This,N) -> wxControlWithItems:getClientData(This,N). -%% @hidden -doc false. findString(This,String, Options) -> wxControlWithItems:findString(This,String, Options). -%% @hidden -doc false. findString(This,String) -> wxControlWithItems:findString(This,String). -%% @hidden -doc false. delete(This,N) -> wxControlWithItems:delete(This,N). -%% @hidden -doc false. clear(This) -> wxControlWithItems:clear(This). -%% @hidden -doc false. appendStrings(This,Items,ClientsData) -> wxControlWithItems:appendStrings(This,Items,ClientsData). -%% @hidden -doc false. appendStrings(This,Items) -> wxControlWithItems:appendStrings(This,Items). -%% @hidden -doc false. append(This,Item,ClientData) -> wxControlWithItems:append(This,Item,ClientData). -%% @hidden -doc false. append(This,Item) -> wxControlWithItems:append(This,Item). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxChildFocusEvent.erl b/lib/wx/src/gen/wxChildFocusEvent.erl index 48e124928dfb..52004d2958d4 100644 --- a/lib/wx/src/gen/wxChildFocusEvent.erl +++ b/lib/wx/src/gen/wxChildFocusEvent.erl @@ -20,29 +20,26 @@ -module(wxChildFocusEvent). -moduledoc """ -Functions for wxChildFocusEvent class +A child focus event is sent to a (parent-)window when one of its child windows gains +focus, so that the window could restore the focus back to its corresponding child if it +loses it now and regains later. -A child focus event is sent to a (parent-)window when one of its child windows -gains focus, so that the window could restore the focus back to its -corresponding child if it loses it now and regains later. +Notice that child window is the direct child of the window receiving event. Use `wxWindow:findFocus/0` to +retrieve the window which is actually getting focus. -Notice that child window is the direct child of the window receiving event. Use -`wxWindow:findFocus/0` to retrieve the window which is actually getting focus. +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +* `m:wxCommandEvent` -wxWidgets docs: -[wxChildFocusEvent](https://docs.wxwidgets.org/3.1/classwx_child_focus_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxChildFocusEvent](https://docs.wxwidgets.org/3.2/classwx_child_focus_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxChildFocusEventType`](`t:wxChildFocusEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxChildFocusEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getWindow/1]). @@ -57,16 +54,14 @@ this type. -include("wx.hrl"). -type wxChildFocusEventType() :: 'child_focus'. -export_type([wxChildFocusEvent/0, wxChildFocus/0, wxChildFocusEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns the direct child which receives the focus, or a (grand-)parent of the -control receiving the focus. +Returns the direct child which receives the focus, or a (grand-)parent of the control +receiving the focus. To get the actually focused control use `wxWindow:findFocus/0`. """. @@ -78,58 +73,40 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxChildFocusEvent_GetWindow). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxChoice.erl b/lib/wx/src/gen/wxChoice.erl index bd83e1764532..4b2602a9ec27 100644 --- a/lib/wx/src/gen/wxChoice.erl +++ b/lib/wx/src/gen/wxChoice.erl @@ -20,27 +20,41 @@ -module(wxChoice). -moduledoc """ -Functions for wxChoice class +A choice item is used to select one of a list of strings. -A choice item is used to select one of a list of strings. Unlike a -`m:wxListBox`, only the selection is visible until the user pulls down the menu +Unlike a `m:wxListBox`, only the selection is visible until the user pulls down the menu of choices. -Styles +## Styles This class supports the following styles: -See: `m:wxListBox`, `m:wxComboBox`, `m:wxCommandEvent` +* wxCB_SORT: Sorts the entries alphabetically. -This class is derived (and can use functions) from: `m:wxControlWithItems` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +See: +* `m:wxListBox` -wxWidgets docs: [wxChoice](https://docs.wxwidgets.org/3.1/classwx_choice.html) +* `m:wxComboBox` + +* `m:wxCommandEvent` + +This class is derived, and can use functions, from: + +* `m:wxControlWithItems` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxChoice](https://docs.wxwidgets.org/3.2/classwx_choice.html) ## Events Event types emitted from this class: -[`command_choice_selected`](`m:wxCommandEvent`) + +* [`command_choice_selected`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/6,create/7,delete/2,destroy/1,getColumns/1,new/0,new/2,new/3,setColumns/1, @@ -91,7 +105,6 @@ Event types emitted from this class: -type wxChoice() :: wx:wx_object(). -export_type([wxChoice/0]). -%% @hidden -doc false. parent_class(wxControlWithItems) -> true; parent_class(wxControl) -> true; @@ -99,18 +112,17 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. -See: `create/7`, `wxValidator` (not implemented in wx) +See: `create/7` """. -spec new() -> wxChoice(). new() -> wxe_util:queue_cmd(?get_env(), ?wxChoice_new_0), wxe_util:rec(?wxChoice_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxChoice() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -118,11 +130,10 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a choice. -See: `create/7`, `wxValidator` (not implemented in wx) +See: `create/7` """. -spec new(Parent, Id, [Option]) -> wxChoice() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -144,7 +155,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxChoice_new_3), wxe_util:rec(?wxChoice_new_3). -%% @equiv create(This,Parent,Id,Pos,Size,Choices, []) +-doc(#{equiv => create(This,Parent,Id,Pos,Size,Choices, [])}). -spec create(This, Parent, Id, Pos, Size, Choices) -> boolean() when This::wxChoice(), Parent::wxWindow:wxWindow(), Id::integer(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()]. @@ -152,7 +163,7 @@ create(This,Parent,Id,{PosX,PosY} = Pos,{SizeW,SizeH} = Size,Choices) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_integer(PosX),is_integer(PosY),is_integer(SizeW),is_integer(SizeH),is_list(Choices) -> create(This,Parent,Id,Pos,Size,Choices, []). -%% @doc See external documentation. +-doc "". -spec create(This, Parent, Id, Pos, Size, Choices, [Option]) -> boolean() when This::wxChoice(), Parent::wxWindow:wxWindow(), Id::integer(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()], Option :: {'style', integer()} @@ -170,20 +181,17 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,{PosX,PosY} = Po wxe_util:queue_cmd(This,Parent,Id,Pos,Size,Choices_UCA, Opts,?get_env(),?wxChoice_Create), wxe_util:rec(?wxChoice_Create). -%% @doc See external documentation. -doc """ Deletes an item from the control. -The client data associated with the item will be also deleted if it is owned by -the control. Note that it is an error (signalled by an assert failure in debug -builds) to remove an item with the index negative or greater or equal than the -number of items in the control. +The client data associated with the item will be also deleted if it is owned by the +control. Note that it is an error (signalled by an assert failure in debug builds) to +remove an item with the index negative or greater or equal than the number of items in the control. -If there is a currently selected item below the item being deleted, i.e. if -`wxControlWithItems:getSelection/1` returns a valid index greater than or equal -to `n`, the selection is invalidated when this function is called. However if -the selected item appears before the item being deleted, the selection is -preserved unchanged. +If there is a currently selected item below the item being deleted, i.e. if `wxControlWithItems:getSelection/1` returns a +valid index greater than or equal to `n`, the selection is invalidated when this function +is called. However if the selected item appears before the item being deleted, the +selection is preserved unchanged. See: `wxControlWithItems:clear/1` """. @@ -194,12 +202,11 @@ delete(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxChoice), wxe_util:queue_cmd(This,N,?get_env(),?wxChoice_Delete). -%% @doc See external documentation. -doc """ Gets the number of columns in this choice item. -Remark: This is implemented for GTK and Motif only and always returns 1 for the -other platforms. +Remark: This is implemented for GTK and Motif only and always returns 1 for the other +platforms. """. -spec getColumns(This) -> integer() when This::wxChoice(). @@ -208,7 +215,7 @@ getColumns(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoice_GetColumns), wxe_util:rec(?wxChoice_GetColumns). -%% @equiv setColumns(This, []) +-doc(#{equiv => setColumns(This, [])}). -spec setColumns(This) -> 'ok' when This::wxChoice(). @@ -216,12 +223,11 @@ setColumns(This) when is_record(This, wx_ref) -> setColumns(This, []). -%% @doc See external documentation. -doc """ Sets the number of columns in this choice item. -Remark: This is implemented for GTK and Motif only and doesn’t do anything under -other platforms. +Remark: This is implemented for GTK and Motif only and doesn’t do anything under other +platforms. """. -spec setColumns(This, [Option]) -> 'ok' when This::wxChoice(), @@ -234,629 +240,423 @@ setColumns(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxChoice_SetColumns). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the choice item.". +-doc "Destroys the object". -spec destroy(This::wxChoice()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxChoice), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControlWithItems -%% @hidden -doc false. setStringSelection(This,String) -> wxControlWithItems:setStringSelection(This,String). -%% @hidden -doc false. setString(This,N,String) -> wxControlWithItems:setString(This,N,String). -%% @hidden -doc false. setSelection(This,N) -> wxControlWithItems:setSelection(This,N). -%% @hidden -doc false. select(This,N) -> wxControlWithItems:select(This,N). -%% @hidden -doc false. isEmpty(This) -> wxControlWithItems:isEmpty(This). -%% @hidden -doc false. insertStrings(This,Items,Pos,ClientsData) -> wxControlWithItems:insertStrings(This,Items,Pos,ClientsData). -%% @hidden -doc false. insertStrings(This,Items,Pos) -> wxControlWithItems:insertStrings(This,Items,Pos). -%% @hidden -doc false. insert(This,Item,Pos,ClientData) -> wxControlWithItems:insert(This,Item,Pos,ClientData). -%% @hidden -doc false. insert(This,Item,Pos) -> wxControlWithItems:insert(This,Item,Pos). -%% @hidden -doc false. getStringSelection(This) -> wxControlWithItems:getStringSelection(This). -%% @hidden -doc false. getString(This,N) -> wxControlWithItems:getString(This,N). -%% @hidden -doc false. getSelection(This) -> wxControlWithItems:getSelection(This). -%% @hidden -doc false. getCount(This) -> wxControlWithItems:getCount(This). -%% @hidden -doc false. setClientData(This,N,Data) -> wxControlWithItems:setClientData(This,N,Data). -%% @hidden -doc false. getClientData(This,N) -> wxControlWithItems:getClientData(This,N). -%% @hidden -doc false. findString(This,String, Options) -> wxControlWithItems:findString(This,String, Options). -%% @hidden -doc false. findString(This,String) -> wxControlWithItems:findString(This,String). -%% @hidden -doc false. clear(This) -> wxControlWithItems:clear(This). -%% @hidden -doc false. appendStrings(This,Items,ClientsData) -> wxControlWithItems:appendStrings(This,Items,ClientsData). -%% @hidden -doc false. appendStrings(This,Items) -> wxControlWithItems:appendStrings(This,Items). -%% @hidden -doc false. append(This,Item,ClientData) -> wxControlWithItems:append(This,Item,ClientData). -%% @hidden -doc false. append(This,Item) -> wxControlWithItems:append(This,Item). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxChoicebook.erl b/lib/wx/src/gen/wxChoicebook.erl index 6708b073f352..e3f18314dc42 100644 --- a/lib/wx/src/gen/wxChoicebook.erl +++ b/lib/wx/src/gen/wxChoicebook.erl @@ -20,40 +20,57 @@ -module(wxChoicebook). -moduledoc """ -Functions for wxChoicebook class - -`m:wxChoicebook` is a class similar to `m:wxNotebook`, but uses a `m:wxChoice` -control to show the labels instead of the tabs. +`m:wxChoicebook` is a class similar to `m:wxNotebook`, but uses a `m:wxChoice` control to +show the labels instead of the tabs. For usage documentation of this class, please refer to the base abstract class -wxBookCtrl. You can also use the page_samples_notebook to see `m:wxChoicebook` -in action. +wxBookCtrl. You can also use the page_samples_notebook to see `m:wxChoicebook` in action. -`m:wxChoicebook` allows the use of wxBookCtrlBase::GetControlSizer(), allowing a -program to add other controls next to the choice control. This is particularly -useful when screen space is restricted, as it often is when `m:wxChoicebook` is -being employed. +`m:wxChoicebook` allows the use of wxBookCtrlBase::GetControlSizer(), allowing a program +to add other controls next to the choice control. This is particularly useful when screen +space is restricted, as it often is when `m:wxChoicebook` is being employed. -Styles +## Styles This class supports the following styles: +* wxCHB_DEFAULT: Choose the default location for the labels depending on the current +platform (but currently it's the same everywhere, namely wxCHB_TOP). + +* wxCHB_TOP: Place labels above the page area. + +* wxCHB_LEFT: Place labels on the left side. + +* wxCHB_RIGHT: Place labels on the right side. + +* wxCHB_BOTTOM: Place labels below the page area. + See: -[Overview bookctrl](https://docs.wxwidgets.org/3.1/overview_bookctrl.html#overview_bookctrl), -`m:wxNotebook`, -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_notebook) +* [Overview bookctrl](https://docs.wxwidgets.org/3.2/overview_bookctrl.html#overview_bookctrl) + +* `m:wxNotebook` + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_notebook) + +This class is derived, and can use functions, from: + +* `m:wxBookCtrlBase` -This class is derived (and can use functions) from: `m:wxBookCtrlBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxControl` -wxWidgets docs: -[wxChoicebook](https://docs.wxwidgets.org/3.1/classwx_choicebook.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxChoicebook](https://docs.wxwidgets.org/3.2/classwx_choicebook.html) ## Events Event types emitted from this class: -[`choicebook_page_changed`](`m:wxBookCtrlEvent`), -[`choicebook_page_changing`](`m:wxBookCtrlEvent`) + +* [`choicebook_page_changed`](`m:wxBookCtrlEvent`) + +* [`choicebook_page_changing`](`m:wxBookCtrlEvent`) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,advanceSelection/1,advanceSelection/2,assignImageList/2, @@ -104,7 +121,6 @@ Event types emitted from this class: -type wxChoicebook() :: wx:wx_object(). -export_type([wxChoicebook/0]). -%% @hidden -doc false. parent_class(wxBookCtrlBase) -> true; parent_class(wxControl) -> true; @@ -112,14 +128,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Constructs a choicebook control.". -spec new() -> wxChoicebook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxChoicebook_new_0), wxe_util:rec(?wxChoicebook_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxChoicebook() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -127,7 +142,7 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. +-doc "". -spec new(Parent, Id, [Option]) -> wxChoicebook() when Parent::wxWindow:wxWindow(), Id::integer(), Option :: {'pos', {X::integer(), Y::integer()}} @@ -144,7 +159,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxChoicebook_new_3), wxe_util:rec(?wxChoicebook_new_3). -%% @equiv addPage(This,Page,Text, []) +-doc(#{equiv => addPage(This,Page,Text, [])}). -spec addPage(This, Page, Text) -> boolean() when This::wxChoicebook(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -152,17 +167,15 @@ addPage(This,Page,Text) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Text) -> addPage(This,Page,Text, []). -%% @doc See external documentation. -doc """ Adds a new page. -The page must have the book control itself as the parent and must not have been -added to this control previously. +The page must have the book control itself as the parent and must not have been added to +this control previously. -The call to this function will generate the page changing and page changed -events if `select` is true, but not when inserting the very first page (as there -is no previous page selection to switch from in this case and so it wouldn't -make sense to e.g. veto such event). +The call to this function will generate the page changing and page changed events if `select` +is true, but not when inserting the very first page (as there is no previous page +selection to switch from in this case and so it wouldn't make sense to e.g. veto such event). Return: true if successful, false otherwise. @@ -186,7 +199,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text, Options) wxe_util:queue_cmd(This,Page,Text_UC, Opts,?get_env(),?wxChoicebook_AddPage), wxe_util:rec(?wxChoicebook_AddPage). -%% @equiv advanceSelection(This, []) +-doc(#{equiv => advanceSelection(This, [])}). -spec advanceSelection(This) -> 'ok' when This::wxChoicebook(). @@ -194,7 +207,6 @@ advanceSelection(This) when is_record(This, wx_ref) -> advanceSelection(This, []). -%% @doc See external documentation. -doc """ Cycles through the tabs. @@ -211,11 +223,13 @@ advanceSelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxChoicebook_AdvanceSelection). -%% @doc See external documentation. -doc """ Sets the image list for the page control and takes ownership of the list. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec assignImageList(This, ImageList) -> 'ok' when This::wxChoicebook(), ImageList::wxImageList:wxImageList(). @@ -224,7 +238,7 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxChoicebook_AssignImageList). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxChoicebook(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -232,7 +246,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Create the choicebook control that has already been constructed with the default constructor. @@ -254,7 +267,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxChoicebook_Create), wxe_util:rec(?wxChoicebook_Create). -%% @doc See external documentation. -doc "Deletes all pages.". -spec deleteAllPages(This) -> boolean() when This::wxChoicebook(). @@ -263,7 +275,6 @@ deleteAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoicebook_DeleteAllPages), wxe_util:rec(?wxChoicebook_DeleteAllPages). -%% @doc See external documentation. -doc "Returns the currently selected page or NULL.". -spec getCurrentPage(This) -> wxWindow:wxWindow() when This::wxChoicebook(). @@ -272,11 +283,13 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoicebook_GetCurrentPage), wxe_util:rec(?wxChoicebook_GetCurrentPage). -%% @doc See external documentation. -doc """ Returns the associated image list, may be NULL. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec getImageList(This) -> wxImageList:wxImageList() when This::wxChoicebook(). @@ -285,7 +298,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoicebook_GetImageList), wxe_util:rec(?wxChoicebook_GetImageList). -%% @doc See external documentation. -doc "Returns the window at the given page position.". -spec getPage(This, Page) -> wxWindow:wxWindow() when This::wxChoicebook(), Page::integer(). @@ -295,7 +307,6 @@ getPage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxChoicebook_GetPage), wxe_util:rec(?wxChoicebook_GetPage). -%% @doc See external documentation. -doc "Returns the number of pages in the control.". -spec getPageCount(This) -> integer() when This::wxChoicebook(). @@ -304,7 +315,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoicebook_GetPageCount), wxe_util:rec(?wxChoicebook_GetPageCount). -%% @doc See external documentation. -doc "Returns the image index for the given page.". -spec getPageImage(This, NPage) -> integer() when This::wxChoicebook(), NPage::integer(). @@ -314,7 +324,6 @@ getPageImage(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxChoicebook_GetPageImage), wxe_util:rec(?wxChoicebook_GetPageImage). -%% @doc See external documentation. -doc "Returns the string for the given page.". -spec getPageText(This, NPage) -> unicode:charlist() when This::wxChoicebook(), NPage::integer(). @@ -324,14 +333,12 @@ getPageText(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxChoicebook_GetPageText), wxe_util:rec(?wxChoicebook_GetPageText). -%% @doc See external documentation. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note that this method may return either the previously or newly selected page -when called from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the -platform and so `wxBookCtrlEvent:getSelection/1` should be used instead in this -case. +Note that this method may return either the previously or newly selected page when called +from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the platform and so `wxBookCtrlEvent:getSelection/1` should be +used instead in this case. """. -spec getSelection(This) -> integer() when This::wxChoicebook(). @@ -340,15 +347,13 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxChoicebook_GetSelection), wxe_util:rec(?wxChoicebook_GetSelection). -%% @doc See external documentation. -doc """ -Returns the index of the tab at the specified position or `wxNOT_FOUND` if none. +Returns the index of the tab at the specified position or `wxNOT\_FOUND` if none. -If `flags` parameter is non-NULL, the position of the point inside the tab is -returned as well. +If `flags` parameter is non-NULL, the position of the point inside the tab is returned as well. -Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at -the specified position. +Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at the +specified position. """. -spec hitTest(This, Pt) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -359,7 +364,7 @@ hitTest(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxChoicebook_HitTest), wxe_util:rec(?wxChoicebook_HitTest). -%% @equiv insertPage(This,Index,Page,Text, []) +-doc(#{equiv => insertPage(This,Index,Page,Text, [])}). -spec insertPage(This, Index, Page, Text) -> boolean() when This::wxChoicebook(), Index::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -367,7 +372,6 @@ insertPage(This,Index,Page,Text) when is_record(This, wx_ref),is_integer(Index),is_record(Page, wx_ref),?is_chardata(Text) -> insertPage(This,Index,Page,Text, []). -%% @doc See external documentation. -doc """ Inserts a new page at the specified position. @@ -393,13 +397,15 @@ insertPage(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=PageT}=Page,Text, Options wxe_util:queue_cmd(This,Index,Page,Text_UC, Opts,?get_env(),?wxChoicebook_InsertPage), wxe_util:rec(?wxChoicebook_InsertPage). -%% @doc See external documentation. -doc """ Sets the image list to use. It does not take ownership of the image list, you must delete it yourself. -See: `m:wxImageList`, `assignImageList/2` +See: +* `m:wxImageList` + +* `assignImageList/2` """. -spec setImageList(This, ImageList) -> 'ok' when This::wxChoicebook(), ImageList::wxImageList:wxImageList(). @@ -408,7 +414,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxChoicebook_SetImageList). -%% @doc See external documentation. -doc """ Sets the width and height of the pages. @@ -421,7 +426,6 @@ setPageSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxChoicebook), wxe_util:queue_cmd(This,Size,?get_env(),?wxChoicebook_SetPageSize). -%% @doc See external documentation. -doc """ Sets the image index for the given page. @@ -435,7 +439,6 @@ setPageImage(#wx_ref{type=ThisT}=This,Page,Image) wxe_util:queue_cmd(This,Page,Image,?get_env(),?wxChoicebook_SetPageImage), wxe_util:rec(?wxChoicebook_SetPageImage). -%% @doc See external documentation. -doc "Sets the text for the given page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxChoicebook(), Page::integer(), Text::unicode:chardata(). @@ -446,12 +449,11 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:queue_cmd(This,Page,Text_UC,?get_env(),?wxChoicebook_SetPageText), wxe_util:rec(?wxChoicebook_SetPageText). -%% @doc See external documentation. -doc """ Sets the selection to the given page, returning the previous selection. -Notice that the call to this function generates the page changing events, use -the `changeSelection/2` function if you don't want these events to be generated. +Notice that the call to this function generates the page changing events, use the `changeSelection/2` +function if you don't want these events to be generated. See: `getSelection/1` """. @@ -463,12 +465,10 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxChoicebook_SetSelection), wxe_util:rec(?wxChoicebook_SetSelection). -%% @doc See external documentation. -doc """ Changes the selection to the given page, returning the previous selection. -This function behaves as `setSelection/2` but does `not` generate the page -changing events. +This function behaves as `setSelection/2` but does `not` generate the page changing events. See overview_events_prog for more information. """. @@ -480,569 +480,383 @@ changeSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxChoicebook_ChangeSelection), wxe_util:rec(?wxChoicebook_ChangeSelection). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxChoicebook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxChoicebook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBookCtrlBase -%% @hidden -doc false. removePage(This,Page) -> wxBookCtrlBase:removePage(This,Page). -%% @hidden -doc false. deletePage(This,Page) -> wxBookCtrlBase:deletePage(This,Page). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxClientDC.erl b/lib/wx/src/gen/wxClientDC.erl index 51b264bd77dc..00fd4923ee36 100644 --- a/lib/wx/src/gen/wxClientDC.erl +++ b/lib/wx/src/gen/wxClientDC.erl @@ -20,35 +20,43 @@ -module(wxClientDC). -moduledoc """ -Functions for wxClientDC class +`m:wxClientDC` is primarily useful for obtaining information about the window from +outside EVT\_PAINT() handler. -`m:wxClientDC` is primarily useful for obtaining information about the window -from outside EVT_PAINT() handler. +Typical use of this class is to obtain the extent of some text string in order to +allocate enough size for a window, e.g. -Typical use of this class is to obtain the extent of some text string in order -to allocate enough size for a window, e.g. +Note: While `m:wxClientDC` may also be used for drawing on the client area of a window +from outside an EVT_PAINT() handler in some ports, this does `not` work on all platforms +(neither wxOSX nor wxGTK with GTK 3 Wayland backend support this, so drawing using `m:wxClientDC` +simply doesn't have any effect there) and the only portable way of drawing is via `m:wxPaintDC`. +To redraw a small part of the window, use `wxWindow:refreshRect/3` to invalidate just this part and check `wxWindow:getUpdateRegion/1` in the +paint event handler to redraw this part only. -Note: While `m:wxClientDC` may also be used for drawing on the client area of a -window from outside an EVT_PAINT() handler in some ports, this does `not` work -on all platforms (neither wxOSX nor wxGTK with GTK 3 Wayland backend support -this, so drawing using `m:wxClientDC` simply doesn't have any effect there) and -the only portable way of drawing is via `m:wxPaintDC`. To redraw a small part of -the window, use `wxWindow:refreshRect/3` to invalidate just this part and check -`wxWindow:getUpdateRegion/1` in the paint event handler to redraw this part -only. +`m:wxClientDC` objects should normally be constructed as temporary stack objects, i.e. +don't store a `m:wxClientDC` object. -`m:wxClientDC` objects should normally be constructed as temporary stack -objects, i.e. don't store a `m:wxClientDC` object. +A `m:wxClientDC` object is initialized to use the same font and colours as the window it +is associated with. -A `m:wxClientDC` object is initialized to use the same font and colours as the -window it is associated with. +See: +* `m:wxDC` -See: `m:wxDC`, `m:wxMemoryDC`, `m:wxPaintDC`, `m:wxWindowDC`, `m:wxScreenDC` +* `m:wxMemoryDC` -This class is derived (and can use functions) from: `m:wxWindowDC` `m:wxDC` +* `m:wxPaintDC` -wxWidgets docs: -[wxClientDC](https://docs.wxwidgets.org/3.1/classwx_client_d_c.html) +* `m:wxWindowDC` + +* `m:wxScreenDC` + +This class is derived, and can use functions, from: + +* `m:wxWindowDC` + +* `m:wxDC` + +wxWidgets docs: [wxClientDC](https://docs.wxwidgets.org/3.2/classwx_client_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/1]). @@ -77,13 +85,11 @@ wxWidgets docs: -type wxClientDC() :: wx:wx_object(). -export_type([wxClientDC/0]). -%% @hidden -doc false. parent_class(wxWindowDC) -> true; parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Constructor. @@ -96,8 +102,7 @@ new(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxClientDC_new), wxe_util:rec(?wxClientDC_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxClientDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxClientDC), @@ -105,279 +110,187 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxWindowDC %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxClipboard.erl b/lib/wx/src/gen/wxClipboard.erl index 86320d8861b0..b79455946294 100644 --- a/lib/wx/src/gen/wxClipboard.erl +++ b/lib/wx/src/gen/wxClipboard.erl @@ -20,37 +20,33 @@ -module(wxClipboard). -moduledoc """ -Functions for wxClipboard class - A class for manipulating the clipboard. -To use the clipboard, you call member functions of the global ?wxTheClipboard -object. +To use the clipboard, you call member functions of the global ?wxTheClipboard object. See the overview_dataobject for further information. -Call `open/1` to get ownership of the clipboard. If this operation returns true, -you now own the clipboard. Call `setData/2` to put data on the clipboard, or -`getData/2` to retrieve data from the clipboard. Call `close/1` to close the -clipboard and relinquish ownership. You should keep the clipboard open only -momentarily. +Call `open/1` to get ownership of the clipboard. If this operation returns true, you now own the +clipboard. Call `setData/2` to put data on the clipboard, or `getData/2` to retrieve data from the clipboard. +Call `close/1` to close the clipboard and relinquish ownership. You should keep the clipboard open +only momentarily. For example: -Note: On GTK, the clipboard behavior can vary depending on the configuration of -the end-user's machine. In order for the clipboard data to persist after the -window closes, a clipboard manager must be installed. Some clipboard managers -will automatically flush the clipboard after each new piece of data is added, -while others will not. The @Flush() function will force the clipboard manager to -flush the data. +Note: On GTK, the clipboard behavior can vary depending on the configuration of the +end-user's machine. In order for the clipboard data to persist after the window closes, a +clipboard manager must be installed. Some clipboard managers will automatically flush the +clipboard after each new piece of data is added, while others will not. The @Flush() +function will force the clipboard manager to flush the data. See: -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd), -[Overview dataobject](https://docs.wxwidgets.org/3.1/overview_dataobject.html#overview_dataobject), -`m:wxDataObject` +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) + +* [Overview dataobject](https://docs.wxwidgets.org/3.2/overview_dataobject.html#overview_dataobject) + +* `m:wxDataObject` -wxWidgets docs: -[wxClipboard](https://docs.wxwidgets.org/3.1/classwx_clipboard.html) +wxWidgets docs: [wxClipboard](https://docs.wxwidgets.org/3.2/classwx_clipboard.html) """. -include("wxe.hrl"). -export([addData/2,clear/1,close/1,destroy/1,flush/1,get/0,getData/2,isOpened/1, @@ -61,18 +57,15 @@ wxWidgets docs: -type wxClipboard() :: wx:wx_object(). -export_type([wxClipboard/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxClipboard(). new() -> wxe_util:queue_cmd(?get_env(), ?wxClipboard_new), wxe_util:rec(?wxClipboard_new). -%% @doc See external documentation. -doc """ Call this function to add the data object to the clipboard. @@ -86,7 +79,6 @@ addData(#wx_ref{type=ThisT}=This,#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(This,Data,?get_env(),?wxClipboard_AddData), wxe_util:rec(?wxClipboard_AddData). -%% @doc See external documentation. -doc "Clears the global clipboard object and the system's clipboard if possible.". -spec clear(This) -> 'ok' when This::wxClipboard(). @@ -94,7 +86,6 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxClipboard), wxe_util:queue_cmd(This,?get_env(),?wxClipboard_Clear). -%% @doc See external documentation. -doc "Call this function to close the clipboard, having opened it with `open/1`.". -spec close(This) -> 'ok' when This::wxClipboard(). @@ -102,18 +93,16 @@ close(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxClipboard), wxe_util:queue_cmd(This,?get_env(),?wxClipboard_Close). -%% @doc See external documentation. -doc """ -Flushes the clipboard: this means that the data which is currently on clipboard -will stay available even after the application exits (possibly eating memory), -otherwise the clipboard will be emptied on exit. +Flushes the clipboard: this means that the data which is currently on clipboard will stay +available even after the application exits (possibly eating memory), otherwise the +clipboard will be emptied on exit. -Currently this method is implemented in MSW and GTK and always returns false -otherwise. +Currently this method is implemented in MSW and GTK and always returns false otherwise. -Note: On GTK, only the non-primary selection can be flushed. Calling this -function when the clipboard is using the primary selection will return false and -not make any data available after the program exits. +Note: On GTK, only the non-primary selection can be flushed. Calling this function when +the clipboard is using the primary selection will return false and not make any data +available after the program exits. Return: false if the operation is unsuccessful for any reason. """. @@ -124,10 +113,9 @@ flush(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxClipboard_Flush), wxe_util:rec(?wxClipboard_Flush). -%% @doc See external documentation. -doc """ -Call this function to fill `data` with data on the clipboard, if available in -the required format. +Call this function to fill `data` with data on the clipboard, if available in the +required format. Returns true on success. """. @@ -139,7 +127,6 @@ getData(#wx_ref{type=ThisT}=This,#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(This,Data,?get_env(),?wxClipboard_GetData), wxe_util:rec(?wxClipboard_GetData). -%% @doc See external documentation. -doc "Returns true if the clipboard has been opened.". -spec isOpened(This) -> boolean() when This::wxClipboard(). @@ -148,13 +135,11 @@ isOpened(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxClipboard_IsOpened), wxe_util:rec(?wxClipboard_IsOpened). -%% @doc See external documentation. -doc """ -Call this function to open the clipboard before calling `setData/2` and -`getData/2`. +Call this function to open the clipboard before calling `setData/2` and `getData/2`. -Call `close/1` when you have finished with the clipboard. You should keep the -clipboard open for only a very short time. +Call `close/1` when you have finished with the clipboard. You should keep the clipboard open for +only a very short time. Return: true on success. This should be tested (as in the sample shown above). """. @@ -165,18 +150,16 @@ open(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxClipboard_Open), wxe_util:rec(?wxClipboard_Open). -%% @doc See external documentation. -doc """ Call this function to set the data object to the clipboard. -The new data object replaces any previously set one, so if the application wants -to provide clipboard data in several different formats, it must use a composite -data object supporting all of the formats instead of calling this function -several times with different data objects as this would only leave data from the -last one in the clipboard. +The new data object replaces any previously set one, so if the application wants to +provide clipboard data in several different formats, it must use a composite data object +supporting all of the formats instead of calling this function several times with +different data objects as this would only leave data from the last one in the clipboard. -After this function has been called, the clipboard owns the data, so do not -delete the data explicitly. +After this function has been called, the clipboard owns the data, so do not delete the +data explicitly. """. -spec setData(This, Data) -> boolean() when This::wxClipboard(), Data::wxDataObject:wxDataObject(). @@ -186,7 +169,7 @@ setData(#wx_ref{type=ThisT}=This,#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(This,Data,?get_env(),?wxClipboard_SetData), wxe_util:rec(?wxClipboard_SetData). -%% @equiv usePrimarySelection(This, []) +-doc(#{equiv => usePrimarySelection(This, [])}). -spec usePrimarySelection(This) -> 'ok' when This::wxClipboard(). @@ -194,21 +177,19 @@ usePrimarySelection(This) when is_record(This, wx_ref) -> usePrimarySelection(This, []). -%% @doc See external documentation. -doc """ -On platforms supporting it (all X11-based ports), `m:wxClipboard` uses the -CLIPBOARD X11 selection by default. - -When this function is called with true, all subsequent clipboard operations will -use PRIMARY selection until this function is called again with false. - -On the other platforms, there is no PRIMARY selection and so all clipboard -operations will fail. This allows implementing the standard X11 handling of the -clipboard which consists in copying data to the CLIPBOARD selection only when -the user explicitly requests it (i.e. by selecting the "Copy" menu command) but -putting the currently selected text into the PRIMARY selection automatically, -without overwriting the normal clipboard contents with the currently selected -text on the other platforms. +On platforms supporting it (all X11-based ports), `m:wxClipboard` uses the CLIPBOARD X11 +selection by default. + +When this function is called with true, all subsequent clipboard operations will use +PRIMARY selection until this function is called again with false. + +On the other platforms, there is no PRIMARY selection and so all clipboard operations +will fail. This allows implementing the standard X11 handling of the clipboard which +consists in copying data to the CLIPBOARD selection only when the user explicitly requests +it (i.e. by selecting the "Copy" menu command) but putting the currently selected text +into the PRIMARY selection automatically, without overwriting the normal clipboard +contents with the currently selected text on the other platforms. """. -spec usePrimarySelection(This, [Option]) -> 'ok' when This::wxClipboard(), @@ -221,12 +202,11 @@ usePrimarySelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxClipboard_UsePrimarySelection). -%% @doc See external documentation. -%%
Format = ?wxDF_INVALID | ?wxDF_TEXT | ?wxDF_BITMAP | ?wxDF_METAFILE | ?wxDF_SYLK | ?wxDF_DIF | ?wxDF_TIFF | ?wxDF_OEMTEXT | ?wxDF_DIB | ?wxDF_PALETTE | ?wxDF_PENDATA | ?wxDF_RIFF | ?wxDF_WAVE | ?wxDF_UNICODETEXT | ?wxDF_ENHMETAFILE | ?wxDF_FILENAME | ?wxDF_LOCALE | ?wxDF_PRIVATE | ?wxDF_HTML | ?wxDF_MAX -doc """ -Returns true if there is data which matches the data format of the given data -object currently `available` on the clipboard. +Returns true if there is data which matches the data format of the given data object +currently `available` on the clipboard. """. +%% Format = ?wxDF_INVALID | ?wxDF_TEXT | ?wxDF_BITMAP | ?wxDF_METAFILE | ?wxDF_SYLK | ?wxDF_DIF | ?wxDF_TIFF | ?wxDF_OEMTEXT | ?wxDF_DIB | ?wxDF_PALETTE | ?wxDF_PENDATA | ?wxDF_RIFF | ?wxDF_WAVE | ?wxDF_UNICODETEXT | ?wxDF_ENHMETAFILE | ?wxDF_FILENAME | ?wxDF_LOCALE | ?wxDF_PRIVATE | ?wxDF_HTML | ?wxDF_MAX -spec isSupported(This, Format) -> boolean() when This::wxClipboard(), Format::wx:wx_enum(). isSupported(#wx_ref{type=ThisT}=This,Format) @@ -235,15 +215,13 @@ isSupported(#wx_ref{type=ThisT}=This,Format) wxe_util:queue_cmd(This,Format,?get_env(),?wxClipboard_IsSupported), wxe_util:rec(?wxClipboard_IsSupported). -%% @doc See external documentation. -doc "Returns the global instance (wxTheClipboard) of the clipboard object.". -spec get() -> wxClipboard(). get() -> wxe_util:queue_cmd(?get_env(), ?wxClipboard_Get), wxe_util:rec(?wxClipboard_Get). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxClipboard()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxClipboard), diff --git a/lib/wx/src/gen/wxClipboardTextEvent.erl b/lib/wx/src/gen/wxClipboardTextEvent.erl index 0cba866c0229..c4b1efee96e5 100644 --- a/lib/wx/src/gen/wxClipboardTextEvent.erl +++ b/lib/wx/src/gen/wxClipboardTextEvent.erl @@ -20,43 +20,37 @@ -module(wxClipboardTextEvent). -moduledoc """ -Functions for wxClipboardTextEvent class +This class represents the events generated by a control (typically a `m:wxTextCtrl` but +other windows can generate these events as well) when its content gets copied or cut to, +or pasted from the clipboard. -This class represents the events generated by a control (typically a -`m:wxTextCtrl` but other windows can generate these events as well) when its -content gets copied or cut to, or pasted from the clipboard. +There are three types of corresponding events `wxEVT_TEXT_COPY`, `wxEVT_TEXT_CUT` and `wxEVT_TEXT_PASTE`. -There are three types of corresponding events `wxEVT_TEXT_COPY`, -`wxEVT_TEXT_CUT` and `wxEVT_TEXT_PASTE`. +If any of these events is processed (without being skipped) by an event handler, the +corresponding operation doesn't take place which allows preventing the text from being +copied from or pasted to a control. It is also possible to examine the clipboard contents +in the PASTE event handler and transform it in some way before inserting in a control - +for example, changing its case or removing invalid characters. -If any of these events is processed (without being skipped) by an event handler, -the corresponding operation doesn't take place which allows preventing the text -from being copied from or pasted to a control. It is also possible to examine -the clipboard contents in the PASTE event handler and transform it in some way -before inserting in a control - for example, changing its case or removing -invalid characters. +Finally notice that a CUT event is always preceded by the COPY event which makes it +possible to only process the latter if it doesn't matter if the text was copied or cut. -Finally notice that a CUT event is always preceded by the COPY event which makes -it possible to only process the latter if it doesn't matter if the text was -copied or cut. - -Note: These events are currently only generated by `m:wxTextCtrl` in wxGTK and -wxOSX but are also generated by `m:wxComboBox` without wxCB_READONLY style in -wxMSW. +Note: These events are currently only generated by `m:wxTextCtrl` in wxGTK and wxOSX but +are also generated by `m:wxComboBox` without wxCB_READONLY style in wxMSW. See: `m:wxClipboard` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxClipboardTextEvent](https://docs.wxwidgets.org/3.1/classwx_clipboard_text_event.html) +wxWidgets docs: [wxClipboardTextEvent](https://docs.wxwidgets.org/3.2/classwx_clipboard_text_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxClipboardTextEventType`](`t:wxClipboardTextEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxClipboardTextEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -71,65 +65,46 @@ events of this type. -include("wx.hrl"). -type wxClipboardTextEventType() :: 'command_text_copy' | 'command_text_cut' | 'command_text_paste'. -export_type([wxClipboardTextEvent/0, wxClipboardText/0, wxClipboardTextEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxCloseEvent.erl b/lib/wx/src/gen/wxCloseEvent.erl index 8516abdc08df..0aac6a1b78a0 100644 --- a/lib/wx/src/gen/wxCloseEvent.erl +++ b/lib/wx/src/gen/wxCloseEvent.erl @@ -20,53 +20,48 @@ -module(wxCloseEvent). -moduledoc """ -Functions for wxCloseEvent class - This event class contains information about window and session close events. -The handler function for EVT_CLOSE is called when the user has tried to close a -a frame or dialog box using the window manager (X) or system menu (Windows). It -can also be invoked by the application itself programmatically, for example by -calling the `wxWindow:close/2` function. +The handler function for EVT_CLOSE is called when the user has tried to close a a frame +or dialog box using the window manager (X) or system menu (Windows). It can also be +invoked by the application itself programmatically, for example by calling the `wxWindow:close/2` function. -You should check whether the application is forcing the deletion of the window -using `canVeto/1`. If this is false, you `must` destroy the window using -`wxWindow:'Destroy'/1`. +You should check whether the application is forcing the deletion of the window using `canVeto/1`. If +this is false, you `must` destroy the window using `wxWindow:'Destroy'/1`. -If the return value is true, it is up to you whether you respond by destroying -the window. +If the return value is true, it is up to you whether you respond by destroying the window. -If you don't destroy the window, you should call `veto/2` to let the calling -code know that you did not destroy the window. This allows the -`wxWindow:close/2` function to return true or false depending on whether the -close instruction was honoured or not. +If you don't destroy the window, you should call `veto/2` to let the calling code know that you +did not destroy the window. This allows the `wxWindow:close/2` function to return true or false depending on +whether the close instruction was honoured or not. Example of a `m:wxCloseEvent` handler: -The EVT_END_SESSION event is slightly different as it is sent by the system when -the user session is ending (e.g. because of log out or shutdown) and so all -windows are being forcefully closed. At least under MSW, after the handler for -this event is executed the program is simply killed by the system. Because of -this, the default handler for this event provided by wxWidgets calls all the -usual cleanup code (including `wxApp::OnExit()` (not implemented in wx)) so that -it could still be executed and exit()s the process itself, without waiting for -being killed. If this behaviour is for some reason undesirable, make sure that -you define a handler for this event in your wxApp-derived class and do not call -`event.Skip()` in it (but be aware that the system will still kill your -application). +The EVT_END_SESSION event is slightly different as it is sent by the system when the user +session is ending (e.g. because of log out or shutdown) and so all windows are being +forcefully closed. At least under MSW, after the handler for this event is executed the +program is simply killed by the system. Because of this, the default handler for this +event provided by wxWidgets calls all the usual cleanup code (including `wxApp::OnExit()` +(not implemented in wx)) so that it could still be executed and exit()s the process +itself, without waiting for being killed. If this behaviour is for some reason +undesirable, make sure that you define a handler for this event in your wxApp-derived +class and do not call `event.Skip()` in it (but be aware that the system will still kill +your application). + +See: +* `wxWindow:close/2` + +* [Overview windowdeletion](https://docs.wxwidgets.org/3.2/overview_windowdeletion.html#overview_windowdeletion) -See: `wxWindow:close/2`, -[Overview windowdeletion](https://docs.wxwidgets.org/3.1/overview_windowdeletion.html#overview_windowdeletion) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxCloseEvent](https://docs.wxwidgets.org/3.1/classwx_close_event.html) +wxWidgets docs: [wxCloseEvent](https://docs.wxwidgets.org/3.2/classwx_close_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxCloseEventType`](`t:wxCloseEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxCloseEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([canVeto/1,getLoggingOff/1,setCanVeto/2,setLoggingOff/2,veto/1,veto/2]). @@ -79,17 +74,15 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxCloseEventType() :: 'close_window' | 'end_session' | 'query_end_session'. -export_type([wxCloseEvent/0, wxClose/0, wxCloseEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns true if you can veto a system shutdown or a window close event. -Vetoing a window close event is not possible if the calling code wishes to force -the application to exit, and so this function must be called to check this. +Vetoing a window close event is not possible if the calling code wishes to force the +application to exit, and so this function must be called to check this. """. -spec canVeto(This) -> boolean() when This::wxCloseEvent(). @@ -98,13 +91,11 @@ canVeto(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCloseEvent_CanVeto), wxe_util:rec(?wxCloseEvent_CanVeto). -%% @doc See external documentation. -doc """ -Returns true if the user is just logging off or false if the system is shutting -down. +Returns true if the user is just logging off or false if the system is shutting down. -This method can only be called for end session and query end session events, it -doesn't make sense for close window event. +This method can only be called for end session and query end session events, it doesn't +make sense for close window event. """. -spec getLoggingOff(This) -> boolean() when This::wxCloseEvent(). @@ -113,7 +104,6 @@ getLoggingOff(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCloseEvent_GetLoggingOff), wxe_util:rec(?wxCloseEvent_GetLoggingOff). -%% @doc See external documentation. -doc "Sets the 'can veto' flag.". -spec setCanVeto(This, CanVeto) -> 'ok' when This::wxCloseEvent(), CanVeto::boolean(). @@ -122,7 +112,6 @@ setCanVeto(#wx_ref{type=ThisT}=This,CanVeto) ?CLASS(ThisT,wxCloseEvent), wxe_util:queue_cmd(This,CanVeto,?get_env(),?wxCloseEvent_SetCanVeto). -%% @doc See external documentation. -doc "Sets the 'logging off' flag.". -spec setLoggingOff(This, LoggingOff) -> 'ok' when This::wxCloseEvent(), LoggingOff::boolean(). @@ -131,7 +120,7 @@ setLoggingOff(#wx_ref{type=ThisT}=This,LoggingOff) ?CLASS(ThisT,wxCloseEvent), wxe_util:queue_cmd(This,LoggingOff,?get_env(),?wxCloseEvent_SetLoggingOff). -%% @equiv veto(This, []) +-doc(#{equiv => veto(This, [])}). -spec veto(This) -> 'ok' when This::wxCloseEvent(). @@ -139,10 +128,9 @@ veto(This) when is_record(This, wx_ref) -> veto(This, []). -%% @doc See external documentation. -doc """ -Call this from your event handler to veto a system shutdown or to signal to the -calling application that a window close did not happen. +Call this from your event handler to veto a system shutdown or to signal to the calling +application that a window close did not happen. You can only veto a shutdown if `canVeto/1` returns true. """. @@ -158,30 +146,21 @@ veto(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxCloseEvent_Veto). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxColourData.erl b/lib/wx/src/gen/wxColourData.erl index 73dffb9b1888..d38ca9a7a637 100644 --- a/lib/wx/src/gen/wxColourData.erl +++ b/lib/wx/src/gen/wxColourData.erl @@ -20,15 +20,16 @@ -module(wxColourData). -moduledoc """ -Functions for wxColourData class - This class holds a variety of information related to colour dialogs. -See: [`wx_color()`](`t:wx:wx_colour/0`), `m:wxColourDialog`, -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_colour) +See: +* `wx_color()` + +* `m:wxColourDialog` + +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_colour) -wxWidgets docs: -[wxColourData](https://docs.wxwidgets.org/3.1/classwx_colour_data.html) +wxWidgets docs: [wxColourData](https://docs.wxwidgets.org/3.2/classwx_colour_data.html) """. -include("wxe.hrl"). -export([destroy/1,getChooseFull/1,getColour/1,getCustomColour/2,new/0,setChooseFull/2, @@ -39,26 +40,23 @@ wxWidgets docs: -type wxColourData() :: wx:wx_object(). -export_type([wxColourData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Constructor. -Initializes the custom colours to `wxNullColour`, the `data` colour setting to -black, and the `choose` full setting to true. +Initializes the custom colours to `wxNullColour`, the `data` colour setting to black, and +the `choose` full setting to true. """. -spec new() -> wxColourData(). new() -> wxe_util:queue_cmd(?get_env(), ?wxColourData_new), wxe_util:rec(?wxColourData_new). -%% @doc See external documentation. -doc """ -Under Windows, determines whether the Windows colour dialog will display the -full dialog with custom colour selection controls. +Under Windows, determines whether the Windows colour dialog will display the full dialog +with custom colour selection controls. Has no meaning under other platforms. @@ -71,7 +69,6 @@ getChooseFull(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxColourData_GetChooseFull), wxe_util:rec(?wxColourData_GetChooseFull). -%% @doc See external documentation. -doc """ Gets the current colour associated with the colour dialog. @@ -84,7 +81,6 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxColourData_GetColour), wxe_util:rec(?wxColourData_GetColour). -%% @doc See external documentation. -doc "Returns custom colours associated with the colour dialog.". -spec getCustomColour(This, I) -> wx:wx_colour4() when This::wxColourData(), I::integer(). @@ -94,10 +90,9 @@ getCustomColour(#wx_ref{type=ThisT}=This,I) wxe_util:queue_cmd(This,I,?get_env(),?wxColourData_GetCustomColour), wxe_util:rec(?wxColourData_GetCustomColour). -%% @doc See external documentation. -doc """ -Under Windows, tells the Windows colour dialog to display the full dialog with -custom colour selection controls. +Under Windows, tells the Windows colour dialog to display the full dialog with custom +colour selection controls. Under other platforms, has no effect. @@ -110,7 +105,6 @@ setChooseFull(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxColourData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxColourData_SetChooseFull). -%% @doc See external documentation. -doc """ Sets the default colour for the colour dialog. @@ -123,7 +117,6 @@ setColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxColourData), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxColourData_SetColour). -%% @doc See external documentation. -doc "Sets custom colours for the colour dialog.". -spec setCustomColour(This, I, Colour) -> 'ok' when This::wxColourData(), I::integer(), Colour::wx:wx_colour(). @@ -132,8 +125,7 @@ setCustomColour(#wx_ref{type=ThisT}=This,I,Colour) ?CLASS(ThisT,wxColourData), wxe_util:queue_cmd(This,I,wxe_util:color(Colour),?get_env(),?wxColourData_SetCustomColour). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxColourData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxColourData), diff --git a/lib/wx/src/gen/wxColourDialog.erl b/lib/wx/src/gen/wxColourDialog.erl index 33964b62366d..6d97e874048d 100644 --- a/lib/wx/src/gen/wxColourDialog.erl +++ b/lib/wx/src/gen/wxColourDialog.erl @@ -20,30 +20,37 @@ -module(wxColourDialog). -moduledoc """ -Functions for wxColourDialog class - This class represents the colour chooser dialog. -Starting from wxWidgets 3.1.3 and currently in the MSW port only, this dialog -generates wxEVT_COLOUR_CHANGED events while it is being shown, i.e. from inside -its `wxDialog:showModal/1` method, that notify the program about the change of -the currently selected colour and allow it to e.g. preview the effect of -selecting this colour. Note that if you react to this event, you should also -correctly revert to the previously selected colour if the dialog is cancelled by -the user. +Starting from wxWidgets 3.1.3 and currently in the MSW port only, this dialog generates +wxEVT_COLOUR_CHANGED events while it is being shown, i.e. from inside its `wxDialog:showModal/1` method, that +notify the program about the change of the currently selected colour and allow it to e.g. +preview the effect of selecting this colour. Note that if you react to this event, you +should also correctly revert to the previously selected colour if the dialog is cancelled +by the user. Example of using this class with dynamic feedback for the selected colour: See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_colour), -[`wx_color()`](`t:wx:wx_colour/0`), `m:wxColourData`, `wxColourDialogEvent` (not -implemented in wx), ?wxGetColourFromUser() +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_colour) + +* `wx_color()` + +* `m:wxColourData` + +* ?wxGetColourFromUser() + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxColourDialog](https://docs.wxwidgets.org/3.1/classwx_colour_dialog.html) +wxWidgets docs: [wxColourDialog](https://docs.wxwidgets.org/3.2/classwx_colour_dialog.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getColourData/1,new/0,new/1,new/2]). @@ -95,7 +102,6 @@ wxWidgets docs: -type wxColourDialog() :: wx:wx_object(). -export_type([wxColourDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -103,13 +109,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxColourDialog(). new() -> wxe_util:queue_cmd(?get_env(), ?wxColourDialog_new_0), wxe_util:rec(?wxColourDialog_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxColourDialog() when Parent::wxWindow:wxWindow(). @@ -117,17 +123,15 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ Constructor. -Pass a parent window, and optionally a pointer to a block of colour data, which -will be copied to the colour dialog's colour data. +Pass a parent window, and optionally a pointer to a block of colour data, which will be +copied to the colour dialog's colour data. -Custom colours from colour data object will be used in the dialog's colour -palette. Invalid entries in custom colours list will be ignored on some -platforms(GTK) or replaced with white colour on platforms where custom colours -palette has fixed size (MSW). +Custom colours from colour data object will be used in the dialog's colour palette. +Invalid entries in custom colours list will be ignored on some platforms(GTK) or replaced +with white colour on platforms where custom colours palette has fixed size (MSW). See: `m:wxColourData` """. @@ -143,7 +147,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxColourDialog_new_2), wxe_util:rec(?wxColourDialog_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxColourDialog(), Parent::wxWindow:wxWindow(). @@ -151,7 +155,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See external documentation. -doc "Same as `new/2`.". -spec create(This, Parent, [Option]) -> boolean() when This::wxColourDialog(), Parent::wxWindow:wxWindow(), @@ -166,7 +169,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxColourDialog_Create), wxe_util:rec(?wxColourDialog_Create). -%% @doc See external documentation. -doc "Returns the colour data associated with the colour dialog.". -spec getColourData(This) -> wxColourData:wxColourData() when This::wxColourDialog(). @@ -175,659 +177,443 @@ getColourData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxColourDialog_GetColourData), wxe_util:rec(?wxColourDialog_GetColourData). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxColourDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxColourDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxColourPickerCtrl.erl b/lib/wx/src/gen/wxColourPickerCtrl.erl index e47dd7741059..0b724532e5b6 100644 --- a/lib/wx/src/gen/wxColourPickerCtrl.erl +++ b/lib/wx/src/gen/wxColourPickerCtrl.erl @@ -20,30 +20,52 @@ -module(wxColourPickerCtrl). -moduledoc """ -Functions for wxColourPickerCtrl class +This control allows the user to select a colour. -This control allows the user to select a colour. The generic implementation is a -button which brings up a `m:wxColourDialog` when clicked. Native implementation -may differ but this is usually a (small) widget which give access to the -colour-chooser dialog. It is only available if `wxUSE_COLOURPICKERCTRL` is set -to 1 (the default). +The generic implementation is a button which brings up a `m:wxColourDialog` when clicked. +Native implementation may differ but this is usually a (small) widget which give access to +the colour-chooser dialog. It is only available if `wxUSE_COLOURPICKERCTRL` is set to 1 +(the default). -Styles +## Styles This class supports the following styles: -See: `m:wxColourDialog`, `m:wxColourPickerEvent` +* wxCLRP_DEFAULT_STYLE: The default style: 0. -This class is derived (and can use functions) from: `m:wxPickerBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* wxCLRP_USE_TEXTCTRL: Creates a text control to the left of the picker button which is +completely managed by the `m:wxColourPickerCtrl` and which can be used by the user to +specify a colour (see SetColour). The text control is automatically synchronized with +button's value. Use functions defined in `m:wxPickerBase` to modify the text control. -wxWidgets docs: -[wxColourPickerCtrl](https://docs.wxwidgets.org/3.1/classwx_colour_picker_ctrl.html) +* wxCLRP_SHOW_LABEL: Shows the colour in HTML form (AABBCC) as colour button label (instead +of no label at all). + +* wxCLRP_SHOW_ALPHA: Allows selecting opacity in the colour-chooser (effective under wxGTK +and wxOSX). + +See: +* `m:wxColourDialog` + +* `m:wxColourPickerEvent` + +This class is derived, and can use functions, from: + +* `m:wxPickerBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxColourPickerCtrl](https://docs.wxwidgets.org/3.2/classwx_colour_picker_ctrl.html) ## Events Event types emitted from this class: -[`command_colourpicker_changed`](`m:wxColourPickerEvent`) + +* [`command_colourpicker_changed`](`m:wxColourPickerEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getColour/1,new/0,new/2,new/3,setColour/2]). @@ -93,7 +115,6 @@ Event types emitted from this class: -type wxColourPickerCtrl() :: wx:wx_object(). -export_type([wxColourPickerCtrl/0]). -%% @hidden -doc false. parent_class(wxPickerBase) -> true; parent_class(wxControl) -> true; @@ -101,13 +122,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxColourPickerCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxColourPickerCtrl_new_0), wxe_util:rec(?wxColourPickerCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxColourPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -115,7 +136,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Initializes the object and calls `create/4` with all the parameters.". -spec new(Parent, Id, [Option]) -> wxColourPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -137,7 +157,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxColourPickerCtrl_new_3), wxe_util:rec(?wxColourPickerCtrl_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxColourPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -145,12 +165,10 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Creates a colour picker with the given arguments. -Return: true if the control was successfully created or false if creation -failed. +Return: true if the control was successfully created or false if creation failed. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxColourPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -173,7 +191,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxColourPickerCtrl_Create), wxe_util:rec(?wxColourPickerCtrl_Create). -%% @doc See external documentation. -doc "Returns the currently selected colour.". -spec getColour(This) -> wx:wx_colour4() when This::wxColourPickerCtrl(). @@ -182,11 +199,6 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxColourPickerCtrl_GetColour), wxe_util:rec(?wxColourPickerCtrl_GetColour). -%% @doc See external documentation. -%%
Also:
-%% setColour(This, Col) -> 'ok' when
-%% This::wxColourPickerCtrl(), Col::wx:wx_colour().
-%% -doc """ Sets the currently selected colour. @@ -206,605 +218,407 @@ setColour(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxColourPickerCtrl), wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxColourPickerCtrl_SetColour_1_1). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxColourPickerCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxColourPickerCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPickerBase -%% @hidden -doc false. isPickerCtrlGrowable(This) -> wxPickerBase:isPickerCtrlGrowable(This). -%% @hidden -doc false. setTextCtrlGrowable(This, Options) -> wxPickerBase:setTextCtrlGrowable(This, Options). -%% @hidden -doc false. setTextCtrlGrowable(This) -> wxPickerBase:setTextCtrlGrowable(This). -%% @hidden -doc false. setPickerCtrlGrowable(This, Options) -> wxPickerBase:setPickerCtrlGrowable(This, Options). -%% @hidden -doc false. setPickerCtrlGrowable(This) -> wxPickerBase:setPickerCtrlGrowable(This). -%% @hidden -doc false. isTextCtrlGrowable(This) -> wxPickerBase:isTextCtrlGrowable(This). -%% @hidden -doc false. getTextCtrl(This) -> wxPickerBase:getTextCtrl(This). -%% @hidden -doc false. hasTextCtrl(This) -> wxPickerBase:hasTextCtrl(This). -%% @hidden -doc false. getPickerCtrlProportion(This) -> wxPickerBase:getPickerCtrlProportion(This). -%% @hidden -doc false. getTextCtrlProportion(This) -> wxPickerBase:getTextCtrlProportion(This). -%% @hidden -doc false. setPickerCtrlProportion(This,Prop) -> wxPickerBase:setPickerCtrlProportion(This,Prop). -%% @hidden -doc false. setTextCtrlProportion(This,Prop) -> wxPickerBase:setTextCtrlProportion(This,Prop). -%% @hidden -doc false. getInternalMargin(This) -> wxPickerBase:getInternalMargin(This). -%% @hidden -doc false. setInternalMargin(This,Margin) -> wxPickerBase:setInternalMargin(This,Margin). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxColourPickerEvent.erl b/lib/wx/src/gen/wxColourPickerEvent.erl index c0e6abe15c40..13b609280834 100644 --- a/lib/wx/src/gen/wxColourPickerEvent.erl +++ b/lib/wx/src/gen/wxColourPickerEvent.erl @@ -20,23 +20,21 @@ -module(wxColourPickerEvent). -moduledoc """ -Functions for wxColourPickerEvent class - This event class is used for the events generated by `m:wxColourPickerCtrl`. See: `m:wxColourPickerCtrl` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxColourPickerEvent](https://docs.wxwidgets.org/3.1/classwx_colour_picker_event.html) +wxWidgets docs: [wxColourPickerEvent](https://docs.wxwidgets.org/3.2/classwx_colour_picker_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxColourPickerEventType`](`t:wxColourPickerEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxColourPickerEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getColour/1]). @@ -51,13 +49,11 @@ events of this type. -include("wx.hrl"). -type wxColourPickerEventType() :: 'command_colourpicker_changed'. -export_type([wxColourPickerEvent/0, wxColourPicker/0, wxColourPickerEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Retrieve the colour the user has just selected.". -spec getColour(This) -> wx:wx_colour4() when This::wxColourPickerEvent(). @@ -67,58 +63,40 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxColourPickerEvent_GetColour). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxComboBox.erl b/lib/wx/src/gen/wxComboBox.erl index 89bc0c375ada..935eb11d92a2 100644 --- a/lib/wx/src/gen/wxComboBox.erl +++ b/lib/wx/src/gen/wxComboBox.erl @@ -20,49 +20,79 @@ -module(wxComboBox). -moduledoc """ -Functions for wxComboBox class - A combobox is like a combination of an edit control and a listbox. -It can be displayed as static list with editable or read-only text field; or a -drop-down list with text field; or a drop-down list without a text field -depending on the platform and presence of wxCB_READONLY style. +It can be displayed as static list with editable or read-only text field; or a drop-down +list with text field; or a drop-down list without a text field depending on the platform +and presence of wxCB_READONLY style. -A combobox permits a single selection only. Combobox items are numbered from -zero. +A combobox permits a single selection only. Combobox items are numbered from zero. -If you need a customized combobox, have a look at `wxComboCtrl` (not implemented -in wx), `wxOwnerDrawnComboBox` (not implemented in wx), `wxComboPopup` (not -implemented in wx) and the ready-to-use `wxBitmapComboBox` (not implemented in -wx). +If you need a customized combobox, have a look at `wxComboCtrl` (not implemented in wx), `wxOwnerDrawnComboBox` +(not implemented in wx), `wxComboPopup` (not implemented in wx) and the ready-to-use `wxBitmapComboBox` +(not implemented in wx). -Please refer to `wxTextEntry` (not implemented in wx) documentation for the -description of methods operating with the text entry part of the combobox and to -`wxItemContainer` (not implemented in wx) for the methods operating with the -list of strings. Notice that at least under MSW `m:wxComboBox` doesn't behave -correctly if it contains strings differing in case only so portable programs -should avoid adding such strings to this control. +Please refer to `wxTextEntry` (not implemented in wx) documentation for the description +of methods operating with the text entry part of the combobox and to `wxItemContainer` +(not implemented in wx) for the methods operating with the list of strings. Notice that at +least under MSW `m:wxComboBox` doesn't behave correctly if it contains strings differing +in case only so portable programs should avoid adding such strings to this control. -Styles +## Styles This class supports the following styles: -See: `m:wxListBox`, `m:wxTextCtrl`, `m:wxChoice`, `m:wxCommandEvent` +* wxCB_SIMPLE: Creates a combobox with a permanently displayed list. Windows only. + +* wxCB_DROPDOWN: Creates a combobox with a drop-down list. MSW and Motif only. + +* wxCB_READONLY: A combobox with this style behaves like a `m:wxChoice` (and may look in +the same way as well, although this is platform-dependent), i.e. it allows the user to +choose from the list of options but doesn't allow to enter a value not present in the +list. + +* wxCB_SORT: Sorts the entries in the list alphabetically. + +* wxTE_PROCESS_ENTER: The control will generate the event `wxEVT_TEXT_ENTER` that can be +handled by the program. Otherwise, i.e. either if this style not specified at all, or it +is used, but there is no event handler for this event or the event handler called `wxEvent:skip/2` to +avoid overriding the default handling, pressing Enter key is either processed internally +by the control or used to activate the default button of the dialog, if any. + +See: +* `m:wxListBox` + +* `m:wxTextCtrl` + +* `m:wxChoice` + +* `m:wxCommandEvent` + +This class is derived, and can use functions, from: + +* `m:wxControlWithItems` + +* `m:wxControl` -This class is derived (and can use functions) from: `m:wxControlWithItems` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxWindow` -wxWidgets docs: -[wxComboBox](https://docs.wxwidgets.org/3.1/classwx_combo_box.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxComboBox](https://docs.wxwidgets.org/3.2/classwx_combo_box.html) ## Events Event types emitted from this class: -[`command_combobox_selected`](`m:wxCommandEvent`), -[`command_text_updated`](`m:wxCommandEvent`), -[`command_text_enter`](`m:wxCommandEvent`), -[`combobox_dropdown`](`m:wxCommandEvent`), -[`combobox_closeup`](`m:wxCommandEvent`) + +* [`command_combobox_selected`](`m:wxCommandEvent`) + +* [`command_text_updated`](`m:wxCommandEvent`) + +* [`command_text_enter`](`m:wxCommandEvent`) + +* [`combobox_dropdown`](`m:wxCommandEvent`) + +* [`combobox_closeup`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([canCopy/1,canCut/1,canPaste/1,canRedo/1,canUndo/1,copy/1,create/7,create/8, @@ -115,7 +145,6 @@ Event types emitted from this class: -type wxComboBox() :: wx:wx_object(). -export_type([wxComboBox/0]). -%% @hidden -doc false. parent_class(wxControlWithItems) -> true; parent_class(wxControl) -> true; @@ -123,14 +152,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxComboBox(). new() -> wxe_util:queue_cmd(?get_env(), ?wxComboBox_new_0), wxe_util:rec(?wxComboBox_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxComboBox() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -138,11 +166,10 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a combobox. -See: `create/8`, `wxValidator` (not implemented in wx) +See: `create/8` """. -spec new(Parent, Id, [Option]) -> wxComboBox() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -166,7 +193,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxComboBox_new_3), wxe_util:rec(?wxComboBox_new_3). -%% @equiv create(This,Parent,Id,Value,Pos,Size,Choices, []) +-doc(#{equiv => create(This,Parent,Id,Value,Pos,Size,Choices, [])}). -spec create(This, Parent, Id, Value, Pos, Size, Choices) -> boolean() when This::wxComboBox(), Parent::wxWindow:wxWindow(), Id::integer(), Value::unicode:chardata(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()]. @@ -174,7 +201,7 @@ create(This,Parent,Id,Value,{PosX,PosY} = Pos,{SizeW,SizeH} = Size,Choices) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Value),is_integer(PosX),is_integer(PosY),is_integer(SizeW),is_integer(SizeH),is_list(Choices) -> create(This,Parent,Id,Value,Pos,Size,Choices, []). -%% @doc See external documentation. +-doc "". -spec create(This, Parent, Id, Value, Pos, Size, Choices, [Option]) -> boolean() when This::wxComboBox(), Parent::wxWindow:wxWindow(), Id::integer(), Value::unicode:chardata(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()], Option :: {'style', integer()} @@ -193,7 +220,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Value,{PosX,PosY wxe_util:queue_cmd(This,Parent,Id,Value_UC,Pos,Size,Choices_UCA, Opts,?get_env(),?wxComboBox_Create), wxe_util:rec(?wxComboBox_Create). -%% @doc See external documentation. -doc "Returns true if the selection can be copied to the clipboard.". -spec canCopy(This) -> boolean() when This::wxComboBox(). @@ -202,7 +228,6 @@ canCopy(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_CanCopy), wxe_util:rec(?wxComboBox_CanCopy). -%% @doc See external documentation. -doc "Returns true if the selection can be cut to the clipboard.". -spec canCut(This) -> boolean() when This::wxComboBox(). @@ -211,13 +236,11 @@ canCut(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_CanCut), wxe_util:rec(?wxComboBox_CanCut). -%% @doc See external documentation. -doc """ -Returns true if the contents of the clipboard can be pasted into the text -control. +Returns true if the contents of the clipboard can be pasted into the text control. -On some platforms (Motif, GTK) this is an approximation and returns true if the -control is editable, false otherwise. +On some platforms (Motif, GTK) this is an approximation and returns true if the control +is editable, false otherwise. """. -spec canPaste(This) -> boolean() when This::wxComboBox(). @@ -226,11 +249,7 @@ canPaste(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_CanPaste), wxe_util:rec(?wxComboBox_CanPaste). -%% @doc See external documentation. --doc """ -Returns true if there is a redo facility available and the last operation can be -redone. -""". +-doc "Returns true if there is a redo facility available and the last operation can be redone.". -spec canRedo(This) -> boolean() when This::wxComboBox(). canRedo(#wx_ref{type=ThisT}=This) -> @@ -238,11 +257,7 @@ canRedo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_CanRedo), wxe_util:rec(?wxComboBox_CanRedo). -%% @doc See external documentation. --doc """ -Returns true if there is an undo facility available and the last operation can -be undone. -""". +-doc "Returns true if there is an undo facility available and the last operation can be undone.". -spec canUndo(This) -> boolean() when This::wxComboBox(). canUndo(#wx_ref{type=ThisT}=This) -> @@ -250,7 +265,6 @@ canUndo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_CanUndo), wxe_util:rec(?wxComboBox_CanUndo). -%% @doc See external documentation. -doc "Copies the selected text to the clipboard.". -spec copy(This) -> 'ok' when This::wxComboBox(). @@ -258,7 +272,6 @@ copy(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_Copy). -%% @doc See external documentation. -doc "Copies the selected text to the clipboard and removes it from the control.". -spec cut(This) -> 'ok' when This::wxComboBox(). @@ -266,12 +279,10 @@ cut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_Cut). -%% @doc See external documentation. -doc """ Same as `wxTextCtrl:getInsertionPoint/1`. -Note: Under wxMSW, this function always returns 0 if the combobox doesn't have -the focus. +Note: Under wxMSW, this function always returns 0 if the combobox doesn't have the focus. """. -spec getInsertionPoint(This) -> integer() when This::wxComboBox(). @@ -280,10 +291,9 @@ getInsertionPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_GetInsertionPoint), wxe_util:rec(?wxComboBox_GetInsertionPoint). -%% @doc See external documentation. -doc """ -Returns the zero based index of the last position in the text control, which is -equal to the number of characters in the control. +Returns the zero based index of the last position in the text control, which is equal to +the number of characters in the control. """. -spec getLastPosition(This) -> integer() when This::wxComboBox(). @@ -292,13 +302,12 @@ getLastPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_GetLastPosition), wxe_util:rec(?wxComboBox_GetLastPosition). -%% @doc See external documentation. -doc """ Gets the contents of the control. -Notice that for a multiline text control, the lines will be separated by -(Unix-style) `\n` characters, even under Windows where they are separated by a -`\r\n` sequence in the native control. +Notice that for a multiline text control, the lines will be separated by (Unix-style) `\n` +characters, even under Windows where they are separated by a `\r\n` sequence in the +native control. """. -spec getValue(This) -> unicode:charlist() when This::wxComboBox(). @@ -307,7 +316,6 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxComboBox_GetValue), wxe_util:rec(?wxComboBox_GetValue). -%% @doc See external documentation. -doc "Pastes text from the clipboard to the text item.". -spec paste(This) -> 'ok' when This::wxComboBox(). @@ -315,10 +323,9 @@ paste(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_Paste). -%% @doc See external documentation. -doc """ -If there is a redo facility and the last operation can be redone, redoes the -last operation. +If there is a redo facility and the last operation can be redone, redoes the last +operation. Does nothing if there is no redo facility. """. @@ -328,13 +335,11 @@ redo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_Redo). -%% @doc See external documentation. -doc """ -Replaces the text starting at the first position up to (but not including) the -character at the last position with the given text. +Replaces the text starting at the first position up to (but not including) the character +at the last position with the given text. -This function puts the current insertion point position at `to` as a side -effect. +This function puts the current insertion point position at `to` as a side effect. """. -spec replace(This, From, To, Value) -> 'ok' when This::wxComboBox(), From::integer(), To::integer(), Value::unicode:chardata(). @@ -344,13 +349,11 @@ replace(#wx_ref{type=ThisT}=This,From,To,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,From,To,Value_UC,?get_env(),?wxComboBox_Replace). -%% @doc See external documentation. -doc """ -Removes the text starting at the first given position up to (but not including) -the character at the last position. +Removes the text starting at the first given position up to (but not including) the +character at the last position. -This function puts the current insertion point position at `to` as a side -effect. +This function puts the current insertion point position at `to` as a side effect. """. -spec remove(This, From, To) -> 'ok' when This::wxComboBox(), From::integer(), To::integer(). @@ -359,7 +362,6 @@ remove(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,From,To,?get_env(),?wxComboBox_Remove). -%% @doc See external documentation. -doc "Sets the insertion point at the given position.". -spec setInsertionPoint(This, Pos) -> 'ok' when This::wxComboBox(), Pos::integer(). @@ -368,12 +370,10 @@ setInsertionPoint(#wx_ref{type=ThisT}=This,Pos) ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,Pos,?get_env(),?wxComboBox_SetInsertionPoint). -%% @doc See external documentation. -doc """ Sets the insertion point at the end of the text control. -This is equivalent to calling `setInsertionPoint/2` with `getLastPosition/1` -argument. +This is equivalent to calling `setInsertionPoint/2` with `getLastPosition/1` argument. """. -spec setInsertionPointEnd(This) -> 'ok' when This::wxComboBox(). @@ -381,15 +381,16 @@ setInsertionPointEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_SetInsertionPointEnd). -%% @doc See external documentation. -doc """ -Sets the selection to the given item `n` or removes the selection entirely if -`n` == `wxNOT_FOUND`. +Sets the selection to the given item `n` or removes the selection entirely if `n` == `wxNOT\_FOUND`. + +Note that this does not cause any command events to be emitted nor does it deselect any +other items in the controls which support multiple selections. -Note that this does not cause any command events to be emitted nor does it -deselect any other items in the controls which support multiple selections. +See: +* `wxControlWithItems:setString/3` -See: `wxControlWithItems:setString/3`, `wxControlWithItems:setStringSelection/2` +* `wxControlWithItems:setStringSelection/2` """. -spec setSelection(This, N) -> 'ok' when This::wxComboBox(), N::integer(). @@ -398,7 +399,6 @@ setSelection(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,N,?get_env(),?wxComboBox_SetSelection_1). -%% @doc See external documentation. -doc "Same as `wxTextCtrl:setSelection/3`.". -spec setSelection(This, From, To) -> 'ok' when This::wxComboBox(), From::integer(), To::integer(). @@ -407,17 +407,15 @@ setSelection(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,From,To,?get_env(),?wxComboBox_SetSelection_2). -%% @doc See external documentation. -doc """ Sets the text for the combobox text field. -For normal, editable comboboxes with a text entry field calling this method will -generate a `wxEVT_TEXT` event, consistently with `wxTextCtrl:setValue/2` -behaviour, use `wxTextCtrl:changeValue/2` if this is undesirable. +For normal, editable comboboxes with a text entry field calling this method will generate +a `wxEVT_TEXT` event, consistently with `wxTextCtrl:setValue/2` behaviour, use `wxTextCtrl:changeValue/2` if this is undesirable. -For controls with `wxCB_READONLY` style the method behaves somewhat differently: -the string must be in the combobox choices list (the check for this is -case-insensitive) and `wxEVT_TEXT` is `not` generated in this case. +For controls with `wxCB_READONLY` style the method behaves somewhat differently: the +string must be in the combobox choices list (the check for this is case-insensitive) and `wxEVT_TEXT` +is `not` generated in this case. """. -spec setValue(This, Text) -> 'ok' when This::wxComboBox(), Text::unicode:chardata(). @@ -427,10 +425,9 @@ setValue(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxComboBox_SetValue). -%% @doc See external documentation. -doc """ -If there is an undo facility and the last operation can be undone, undoes the -last operation. +If there is an undo facility and the last operation can be undone, undoes the last +operation. Does nothing if there is no undo facility. """. @@ -440,629 +437,423 @@ undo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxComboBox), wxe_util:queue_cmd(This,?get_env(),?wxComboBox_Undo). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the combobox.". +-doc "Destroys the object". -spec destroy(This::wxComboBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxComboBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControlWithItems -%% @hidden -doc false. setStringSelection(This,String) -> wxControlWithItems:setStringSelection(This,String). -%% @hidden -doc false. setString(This,N,String) -> wxControlWithItems:setString(This,N,String). -%% @hidden -doc false. select(This,N) -> wxControlWithItems:select(This,N). -%% @hidden -doc false. isEmpty(This) -> wxControlWithItems:isEmpty(This). -%% @hidden -doc false. insertStrings(This,Items,Pos,ClientsData) -> wxControlWithItems:insertStrings(This,Items,Pos,ClientsData). -%% @hidden -doc false. insertStrings(This,Items,Pos) -> wxControlWithItems:insertStrings(This,Items,Pos). -%% @hidden -doc false. insert(This,Item,Pos,ClientData) -> wxControlWithItems:insert(This,Item,Pos,ClientData). -%% @hidden -doc false. insert(This,Item,Pos) -> wxControlWithItems:insert(This,Item,Pos). -%% @hidden -doc false. getStringSelection(This) -> wxControlWithItems:getStringSelection(This). -%% @hidden -doc false. getString(This,N) -> wxControlWithItems:getString(This,N). -%% @hidden -doc false. getSelection(This) -> wxControlWithItems:getSelection(This). -%% @hidden -doc false. getCount(This) -> wxControlWithItems:getCount(This). -%% @hidden -doc false. setClientData(This,N,Data) -> wxControlWithItems:setClientData(This,N,Data). -%% @hidden -doc false. getClientData(This,N) -> wxControlWithItems:getClientData(This,N). -%% @hidden -doc false. findString(This,String, Options) -> wxControlWithItems:findString(This,String, Options). -%% @hidden -doc false. findString(This,String) -> wxControlWithItems:findString(This,String). -%% @hidden -doc false. delete(This,N) -> wxControlWithItems:delete(This,N). -%% @hidden -doc false. clear(This) -> wxControlWithItems:clear(This). -%% @hidden -doc false. appendStrings(This,Items,ClientsData) -> wxControlWithItems:appendStrings(This,Items,ClientsData). -%% @hidden -doc false. appendStrings(This,Items) -> wxControlWithItems:appendStrings(This,Items). -%% @hidden -doc false. append(This,Item,ClientData) -> wxControlWithItems:append(This,Item,ClientData). -%% @hidden -doc false. append(This,Item) -> wxControlWithItems:append(This,Item). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxCommandEvent.erl b/lib/wx/src/gen/wxCommandEvent.erl index dd920996ffe4..4b4d172b385c 100644 --- a/lib/wx/src/gen/wxCommandEvent.erl +++ b/lib/wx/src/gen/wxCommandEvent.erl @@ -20,29 +20,24 @@ -module(wxCommandEvent). -moduledoc """ -Functions for wxCommandEvent class +This event class contains information about command events, which originate from a +variety of simple controls. -This event class contains information about command events, which originate from -a variety of simple controls. +Note that wxCommandEvents and wxCommandEvent-derived event classes by default and unlike +other wxEvent-derived classes propagate upward from the source window (the window which +emits the event) up to the first parent which processes the event. Be sure to read overview_events_propagation. -Note that wxCommandEvents and wxCommandEvent-derived event classes by default -and unlike other wxEvent-derived classes propagate upward from the source window -(the window which emits the event) up to the first parent which processes the -event. Be sure to read overview_events_propagation. +More complex controls, such as `m:wxTreeCtrl`, have separate command event classes. -More complex controls, such as `m:wxTreeCtrl`, have separate command event -classes. +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxCommandEvent](https://docs.wxwidgets.org/3.1/classwx_command_event.html) +wxWidgets docs: [wxCommandEvent](https://docs.wxwidgets.org/3.2/classwx_command_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxCommandEventType`](`t:wxCommandEventType/0`) to subscribe to events of this -type. +Use `wxEvtHandler:connect/3` with `wxCommandEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getClientData/1,getExtraLong/1,getInt/1,getSelection/1,getString/1, @@ -56,15 +51,13 @@ type. -include("wx.hrl"). -type wxCommandEventType() :: 'command_button_clicked' | 'command_checkbox_clicked' | 'command_choice_selected' | 'command_listbox_selected' | 'command_listbox_doubleclicked' | 'command_text_updated' | 'command_text_enter' | 'text_maxlen' | 'command_menu_selected' | 'command_slider_updated' | 'command_radiobox_selected' | 'command_radiobutton_selected' | 'command_scrollbar_updated' | 'command_vlbox_selected' | 'command_combobox_selected' | 'combobox_dropdown' | 'combobox_closeup' | 'command_tool_rclicked' | 'command_tool_enter' | 'tool_dropdown' | 'command_checklistbox_toggled' | 'command_togglebutton_clicked' | 'command_left_click' | 'command_left_dclick' | 'command_right_click' | 'command_set_focus' | 'command_kill_focus' | 'command_enter' | 'notification_message_click' | 'notification_message_dismissed' | 'notification_message_action'. -export_type([wxCommandEvent/0, wxCommand/0, wxCommandEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns client object pointer for a listbox or choice selection event (not valid -for a deselection). +Returns client object pointer for a listbox or choice selection event (not valid for a +deselection). """. -spec getClientData(This) -> term() when This::wxCommandEvent(). @@ -73,14 +66,13 @@ getClientData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_getClientData), wxe_util:rec(?wxCommandEvent_getClientData). -%% @doc See external documentation. -doc """ Returns extra information dependent on the event objects type. -If the event comes from a listbox selection, it is a boolean determining whether -the event was a selection (true) or a deselection (false). A listbox deselection -only occurs for multiple-selection boxes, and in this case the index and string -values are indeterminate and the listbox must be examined by the application. +If the event comes from a listbox selection, it is a boolean determining whether the +event was a selection (true) or a deselection (false). A listbox deselection only occurs +for multiple-selection boxes, and in this case the index and string values are +indeterminate and the listbox must be examined by the application. """. -spec getExtraLong(This) -> integer() when This::wxCommandEvent(). @@ -89,15 +81,13 @@ getExtraLong(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_GetExtraLong), wxe_util:rec(?wxCommandEvent_GetExtraLong). -%% @doc See external documentation. -doc """ -Returns the integer identifier corresponding to a listbox, choice or radiobox -selection (only if the event was a selection, not a deselection), or a boolean -value representing the value of a checkbox. +Returns the integer identifier corresponding to a listbox, choice or radiobox selection +(only if the event was a selection, not a deselection), or a boolean value representing +the value of a checkbox. -For a menu item, this method returns -1 if the item is not checkable or a -boolean value (true or false) for checkable items indicating the new state of -the item. +For a menu item, this method returns -1 if the item is not checkable or a boolean value +(true or false) for checkable items indicating the new state of the item. """. -spec getInt(This) -> integer() when This::wxCommandEvent(). @@ -106,11 +96,7 @@ getInt(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_GetInt), wxe_util:rec(?wxCommandEvent_GetInt). -%% @doc See external documentation. --doc """ -Returns item index for a listbox or choice selection event (not valid for a -deselection). -""". +-doc "Returns item index for a listbox or choice selection event (not valid for a deselection).". -spec getSelection(This) -> integer() when This::wxCommandEvent(). getSelection(#wx_ref{type=ThisT}=This) -> @@ -118,13 +104,12 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_GetSelection), wxe_util:rec(?wxCommandEvent_GetSelection). -%% @doc See external documentation. -doc """ Returns item string for a listbox or choice selection event. -If one or several items have been deselected, returns the index of the first -deselected item. If some items have been selected and others deselected at the -same time, it will return the index of the first selected item. +If one or several items have been deselected, returns the index of the first deselected +item. If some items have been selected and others deselected at the same time, it will +return the index of the first selected item. """. -spec getString(This) -> unicode:charlist() when This::wxCommandEvent(). @@ -133,13 +118,12 @@ getString(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_GetString), wxe_util:rec(?wxCommandEvent_GetString). -%% @doc See external documentation. -doc """ -This method can be used with checkbox and menu events: for the checkboxes, the -method returns true for a selection event and false for a deselection one. +This method can be used with checkbox and menu events: for the checkboxes, the method +returns true for a selection event and false for a deselection one. -For the menu events, this method indicates if the menu item just has become -checked or unchecked (and thus only makes sense for checkable menu items). +For the menu events, this method indicates if the menu item just has become checked or +unchecked (and thus only makes sense for checkable menu items). Notice that this method cannot be used with `m:wxCheckListBox` currently. """. @@ -150,13 +134,12 @@ isChecked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_IsChecked), wxe_util:rec(?wxCommandEvent_IsChecked). -%% @doc See external documentation. -doc """ -For a listbox or similar event, returns true if it is a selection, false if it -is a deselection. +For a listbox or similar event, returns true if it is a selection, false if it is a +deselection. -If some items have been selected and others deselected at the same time, it will -return true. +If some items have been selected and others deselected at the same time, it will return +true. """. -spec isSelection(This) -> boolean() when This::wxCommandEvent(). @@ -165,8 +148,7 @@ isSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCommandEvent_IsSelection), wxe_util:rec(?wxCommandEvent_IsSelection). -%% @doc See external documentation. --doc "Sets the `m_commandInt` member.". +-doc "Sets the `m\_commandInt` member.". -spec setInt(This, IntCommand) -> 'ok' when This::wxCommandEvent(), IntCommand::integer(). setInt(#wx_ref{type=ThisT}=This,IntCommand) @@ -174,8 +156,7 @@ setInt(#wx_ref{type=ThisT}=This,IntCommand) ?CLASS(ThisT,wxCommandEvent), wxe_util:queue_cmd(This,IntCommand,?get_env(),?wxCommandEvent_SetInt). -%% @doc See external documentation. --doc "Sets the `m_commandString` member.". +-doc "Sets the `m\_commandString` member.". -spec setString(This, String) -> 'ok' when This::wxCommandEvent(), String::unicode:chardata(). setString(#wx_ref{type=ThisT}=This,String) @@ -185,30 +166,21 @@ setString(#wx_ref{type=ThisT}=This,String) wxe_util:queue_cmd(This,String_UC,?get_env(),?wxCommandEvent_SetString). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxContextMenuEvent.erl b/lib/wx/src/gen/wxContextMenuEvent.erl index 4a2ab8a10430..bdba1293dbb5 100644 --- a/lib/wx/src/gen/wxContextMenuEvent.erl +++ b/lib/wx/src/gen/wxContextMenuEvent.erl @@ -20,38 +20,37 @@ -module(wxContextMenuEvent). -moduledoc """ -Functions for wxContextMenuEvent class +This class is used for context menu events, sent to give the application a chance to show +a context (popup) menu for a `m:wxWindow`. -This class is used for context menu events, sent to give the application a -chance to show a context (popup) menu for a `m:wxWindow`. +Note that if `getPosition/1` returns wxDefaultPosition, this means that the event originated from a +keyboard context button event, and you should compute a suitable position yourself, for +example by calling `wx_misc:getMousePosition/0`. -Note that if `getPosition/1` returns wxDefaultPosition, this means that the -event originated from a keyboard context button event, and you should compute a -suitable position yourself, for example by calling `wx_misc:getMousePosition/0`. +Notice that the exact sequence of mouse events is different across the platforms. For +example, under MSW the context menu event is generated after `EVT_RIGHT_UP` event and only +if it was not handled but under GTK the context menu event is generated after `EVT_RIGHT_DOWN` +event. This is correct in the sense that it ensures that the context menu is shown +according to the current platform UI conventions and also means that you must not handle +(or call `wxEvent:skip/2` in your handler if you do have one) neither right mouse down nor right mouse up +event if you plan on handling `EVT_CONTEXT_MENU` event. -Notice that the exact sequence of mouse events is different across the -platforms. For example, under MSW the context menu event is generated after -`EVT_RIGHT_UP` event and only if it was not handled but under GTK the context -menu event is generated after `EVT_RIGHT_DOWN` event. This is correct in the -sense that it ensures that the context menu is shown according to the current -platform UI conventions and also means that you must not handle (or call -`wxEvent:skip/2` in your handler if you do have one) neither right mouse down -nor right mouse up event if you plan on handling `EVT_CONTEXT_MENU` event. +See: +* `m:wxCommandEvent` -See: `m:wxCommandEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxContextMenuEvent](https://docs.wxwidgets.org/3.1/classwx_context_menu_event.html) +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxContextMenuEvent](https://docs.wxwidgets.org/3.2/classwx_context_menu_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxContextMenuEventType`](`t:wxContextMenuEventType/0`) to subscribe to events -of this type. +Use `wxEvtHandler:connect/3` with `wxContextMenuEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getPosition/1,setPosition/2]). @@ -66,23 +65,20 @@ of this type. -include("wx.hrl"). -type wxContextMenuEventType() :: 'context_menu'. -export_type([wxContextMenuEvent/0, wxContextMenu/0, wxContextMenuEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns the position in screen coordinates at which the menu should be shown. Use `wxWindow:screenToClient/2` to convert to client coordinates. -You can also omit a position from `wxWindow:popupMenu/4` in order to use the -current mouse pointer position. +You can also omit a position from `wxWindow:popupMenu/4` in order to use the current mouse pointer position. -If the event originated from a keyboard event, the value returned from this -function will be wxDefaultPosition. +If the event originated from a keyboard event, the value returned from this function will +be wxDefaultPosition. """. -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxContextMenuEvent(). @@ -91,7 +87,6 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxContextMenuEvent_GetPosition), wxe_util:rec(?wxContextMenuEvent_GetPosition). -%% @doc See external documentation. -doc "Sets the position at which the menu should be shown.". -spec setPosition(This, Point) -> 'ok' when This::wxContextMenuEvent(), Point::{X::integer(), Y::integer()}. @@ -101,58 +96,40 @@ setPosition(#wx_ref{type=ThisT}=This,{PointX,PointY} = Point) wxe_util:queue_cmd(This,Point,?get_env(),?wxContextMenuEvent_SetPosition). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxControl.erl b/lib/wx/src/gen/wxControl.erl index 97bc6d482362..a86e300412d7 100644 --- a/lib/wx/src/gen/wxControl.erl +++ b/lib/wx/src/gen/wxControl.erl @@ -20,26 +20,28 @@ -module(wxControl). -moduledoc """ -Functions for wxControl class - This is the base class for a control or "widget". -A control is generally a small window which processes user input and/or displays -one or more item of data. +A control is generally a small window which processes user input and/or displays one or +more item of data. + +This class is derived, and can use functions, from: -See: `wxValidator` (not implemented in wx) +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: [wxControl](https://docs.wxwidgets.org/3.1/classwx_control.html) +wxWidgets docs: [wxControl](https://docs.wxwidgets.org/3.2/classwx_control.html) ## Events Event types emitted from this class: -[`command_text_copy`](`m:wxClipboardTextEvent`), -[`command_text_cut`](`m:wxClipboardTextEvent`), -[`command_text_paste`](`m:wxClipboardTextEvent`) + +* [`command_text_copy`](`m:wxClipboardTextEvent`) + +* [`command_text_cut`](`m:wxClipboardTextEvent`) + +* [`command_text_paste`](`m:wxClipboardTextEvent`) """. -include("wxe.hrl"). -export([getLabel/1,setLabel/2]). @@ -85,23 +87,20 @@ Event types emitted from this class: -type wxControl() :: wx:wx_object(). -export_type([wxControl/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns the control's label, as it was passed to `setLabel/2`. -Note that the returned string may contains mnemonics ("&" characters) if they -were passed to the `setLabel/2` function; use `GetLabelText()` (not implemented -in wx) if they are undesired. +Note that the returned string may contains mnemonics ("&" characters) if they were passed +to the `setLabel/2` function; use `GetLabelText()` (not implemented in wx) if they are undesired. -Also note that the returned string is always the string which was passed to -`setLabel/2` but may be different from the string passed to `SetLabelText()` -(not implemented in wx) (since this last one escapes mnemonic characters). +Also note that the returned string is always the string which was passed to `setLabel/2` but may be +different from the string passed to `SetLabelText()` (not implemented in wx) (since this +last one escapes mnemonic characters). """. -spec getLabel(This) -> unicode:charlist() when This::wxControl(). @@ -110,15 +109,14 @@ getLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxControl_GetLabel), wxe_util:rec(?wxControl_GetLabel). -%% @doc See external documentation. -doc """ Sets the control's label. -All "&" characters in the `label` are special and indicate that the following -character is a `mnemonic` for this control and can be used to activate it from -the keyboard (typically by using `Alt` key in combination with it). To insert a -literal ampersand character, you need to double it, i.e. use "&&". If this -behaviour is undesirable, use `SetLabelText()` (not implemented in wx) instead. +All "&" characters in the `label` are special and indicate that the following character +is a `mnemonic` for this control and can be used to activate it from the keyboard +(typically by using `Alt` key in combination with it). To insert a literal ampersand +character, you need to double it, i.e. use "&&". If this behaviour is undesirable, use `SetLabelText()` +(not implemented in wx) instead. """. -spec setLabel(This, Label) -> 'ok' when This::wxControl(), Label::unicode:chardata(). @@ -129,547 +127,366 @@ setLabel(#wx_ref{type=ThisT}=This,Label) wxe_util:queue_cmd(This,Label_UC,?get_env(),?wxControl_SetLabel). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxControlWithItems.erl b/lib/wx/src/gen/wxControlWithItems.erl index 9f98bf85834e..3c9fb8233b97 100644 --- a/lib/wx/src/gen/wxControlWithItems.erl +++ b/lib/wx/src/gen/wxControlWithItems.erl @@ -20,20 +20,20 @@ -module(wxControlWithItems). -moduledoc """ -Functions for wxControlWithItems class +This is convenience class that derives from both `m:wxControl` and `wxItemContainer` (not +implemented in wx). -This is convenience class that derives from both `m:wxControl` and -`wxItemContainer` (not implemented in wx). It is used as basis for some -wxWidgets controls (`m:wxChoice` and `m:wxListBox`). +It is used as basis for some wxWidgets controls (`m:wxChoice` and `m:wxListBox`). -See: `wxItemContainer` (not implemented in wx), `wxItemContainerImmutable` (not -implemented in wx) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxControl` -wxWidgets docs: -[wxControlWithItems](https://docs.wxwidgets.org/3.1/classwx_control_with_items.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxControlWithItems](https://docs.wxwidgets.org/3.2/classwx_control_with_items.html) """. -include("wxe.hrl"). -export([append/2,append/3,appendStrings/2,appendStrings/3,clear/1,delete/2, @@ -84,20 +84,18 @@ wxWidgets docs: -type wxControlWithItems() :: wx:wx_object(). -export_type([wxControlWithItems/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Appends item into the control. -Return: The return value is the index of the newly inserted item. Note that this -may be different from the last one if the control is sorted (e.g. has -`wxLB_SORT` or `wxCB_SORT` style). +Return: The return value is the index of the newly inserted item. Note that this may be +different from the last one if the control is sorted (e.g. has `wxLB_SORT` or `wxCB_SORT` +style). """. -spec append(This, Item) -> integer() when This::wxControlWithItems(), Item::unicode:chardata(). @@ -108,13 +106,12 @@ append(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item_UC,?get_env(),?wxControlWithItems_Append_1), wxe_util:rec(?wxControlWithItems_Append_1). -%% @doc See external documentation. -doc """ Appends item into the control. -Return: The return value is the index of the newly inserted item. Note that this -may be different from the last one if the control is sorted (e.g. has -`wxLB_SORT` or `wxCB_SORT` style). +Return: The return value is the index of the newly inserted item. Note that this may be +different from the last one if the control is sorted (e.g. has `wxLB_SORT` or `wxCB_SORT` +style). """. -spec append(This, Item, ClientData) -> integer() when This::wxControlWithItems(), Item::unicode:chardata(), ClientData::term(). @@ -125,12 +122,11 @@ append(#wx_ref{type=ThisT}=This,Item,ClientData) wxe_util:queue_cmd(This,Item_UC,ClientData,?get_env(),?wxControlWithItems_Append_2), wxe_util:rec(?wxControlWithItems_Append_2). -%% @doc See external documentation. -doc """ Appends several items at once into the control. -Notice that calling this method is usually much faster than appending them one -by one if you need to add a lot of items. +Notice that calling this method is usually much faster than appending them one by one if +you need to add a lot of items. """. -spec appendStrings(This, Items) -> integer() when This::wxControlWithItems(), Items::[unicode:chardata()]. @@ -142,12 +138,11 @@ appendStrings(#wx_ref{type=ThisT}=This,Items) wxe_util:queue_cmd(This,Items_UCA,?get_env(),?wxControlWithItems_appendStrings_1), wxe_util:rec(?wxControlWithItems_appendStrings_1). -%% @doc See external documentation. -doc """ Appends several items at once into the control. -Notice that calling this method is usually much faster than appending them one -by one if you need to add a lot of items. +Notice that calling this method is usually much faster than appending them one by one if +you need to add a lot of items. """. -spec appendStrings(This, Items, ClientsData) -> integer() when This::wxControlWithItems(), Items::[unicode:chardata()], ClientsData::[term()]. @@ -159,12 +154,10 @@ appendStrings(#wx_ref{type=ThisT}=This,Items,ClientsData) wxe_util:queue_cmd(This,Items_UCA,ClientsData,?get_env(),?wxControlWithItems_appendStrings_2), wxe_util:rec(?wxControlWithItems_appendStrings_2). -%% @doc See external documentation. -doc """ Removes all items from the control. -`clear/1` also deletes the client data of the existing items if it is owned by -the control. +`clear/1` also deletes the client data of the existing items if it is owned by the control. """. -spec clear(This) -> 'ok' when This::wxControlWithItems(). @@ -172,20 +165,17 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxControlWithItems), wxe_util:queue_cmd(This,?get_env(),?wxControlWithItems_Clear). -%% @doc See external documentation. -doc """ Deletes an item from the control. -The client data associated with the item will be also deleted if it is owned by -the control. Note that it is an error (signalled by an assert failure in debug -builds) to remove an item with the index negative or greater or equal than the -number of items in the control. +The client data associated with the item will be also deleted if it is owned by the +control. Note that it is an error (signalled by an assert failure in debug builds) to +remove an item with the index negative or greater or equal than the number of items in the control. -If there is a currently selected item below the item being deleted, i.e. if -`getSelection/1` returns a valid index greater than or equal to `n`, the -selection is invalidated when this function is called. However if the selected -item appears before the item being deleted, the selection is preserved -unchanged. +If there is a currently selected item below the item being deleted, i.e. if `getSelection/1` returns a +valid index greater than or equal to `n`, the selection is invalidated when this function +is called. However if the selected item appears before the item being deleted, the +selection is preserved unchanged. See: `clear/1` """. @@ -196,7 +186,7 @@ delete(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxControlWithItems), wxe_util:queue_cmd(This,N,?get_env(),?wxControlWithItems_Delete). -%% @equiv findString(This,String, []) +-doc(#{equiv => findString(This,String, [])}). -spec findString(This, String) -> integer() when This::wxControlWithItems(), String::unicode:chardata(). @@ -204,12 +194,10 @@ findString(This,String) when is_record(This, wx_ref),?is_chardata(String) -> findString(This,String, []). -%% @doc See external documentation. -doc """ Finds an item whose label matches the given string. -Return: The zero-based position of the item, or wxNOT_FOUND if the string was -not found. +Return: The zero-based position of the item, or wxNOT_FOUND if the string was not found. """. -spec findString(This, String, [Option]) -> integer() when This::wxControlWithItems(), String::unicode:chardata(), @@ -224,17 +212,16 @@ findString(#wx_ref{type=ThisT}=This,String, Options) wxe_util:queue_cmd(This,String_UC, Opts,?get_env(),?wxControlWithItems_FindString), wxe_util:rec(?wxControlWithItems_FindString). -%% @doc See external documentation. -doc """ Returns a pointer to the client data associated with the given item (if any). -It is an error to call this function for a control which doesn't have typed -client data at all although it is OK to call it even if the given item doesn't -have any client data associated with it (but other items do). +It is an error to call this function for a control which doesn't have typed client data +at all although it is OK to call it even if the given item doesn't have any client data +associated with it (but other items do). -Notice that the returned pointer is still owned by the control and will be -deleted by it, use `DetachClientObject()` (not implemented in wx) if you want to -remove the pointer from the control. +Notice that the returned pointer is still owned by the control and will be deleted by it, +use `DetachClientObject()` (not implemented in wx) if you want to remove the pointer from +the control. Return: A pointer to the client data, or NULL if not present. """. @@ -246,14 +233,13 @@ getClientData(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxControlWithItems_getClientData), wxe_util:rec(?wxControlWithItems_getClientData). -%% @doc See external documentation. -doc """ -Associates the given typed client data pointer with the given item: the `data` -object will be deleted when the item is deleted (either explicitly by using -`delete/2` or implicitly when the control itself is destroyed). +Associates the given typed client data pointer with the given item: the `data` object +will be deleted when the item is deleted (either explicitly by using `delete/2` or +implicitly when the control itself is destroyed). -Note that it is an error to call this function if any untyped client data -pointers had been associated with the control items before. +Note that it is an error to call this function if any untyped client data pointers had +been associated with the control items before. """. -spec setClientData(This, N, Data) -> 'ok' when This::wxControlWithItems(), N::integer(), Data::term(). @@ -262,7 +248,6 @@ setClientData(#wx_ref{type=ThisT}=This,N,Data) ?CLASS(ThisT,wxControlWithItems), wxe_util:queue_cmd(This,N,Data,?get_env(),?wxControlWithItems_setClientData). -%% @doc See external documentation. -doc """ Returns the number of items in the control. @@ -275,17 +260,18 @@ getCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxControlWithItems_GetCount), wxe_util:rec(?wxControlWithItems_GetCount). -%% @doc See external documentation. -doc """ -Returns the index of the selected item or `wxNOT_FOUND` if no item is selected. +Returns the index of the selected item or `wxNOT\_FOUND` if no item is selected. Return: The position of the current selection. -Remark: This method can be used with single selection list boxes only, you -should use `wxListBox:getSelections/1` for the list boxes with wxLB_MULTIPLE -style. +Remark: This method can be used with single selection list boxes only, you should use `wxListBox:getSelections/1` +for the list boxes with wxLB_MULTIPLE style. + +See: +* `setSelection/2` -See: `setSelection/2`, `getStringSelection/1` +* `getStringSelection/1` """. -spec getSelection(This) -> integer() when This::wxControlWithItems(). @@ -294,7 +280,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxControlWithItems_GetSelection), wxe_util:rec(?wxControlWithItems_GetSelection). -%% @doc See external documentation. -doc """ Returns the label of the item with the given index. @@ -308,10 +293,8 @@ getString(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxControlWithItems_GetString), wxe_util:rec(?wxControlWithItems_GetString). -%% @doc See external documentation. -doc """ -Returns the label of the selected item or an empty string if no item is -selected. +Returns the label of the selected item or an empty string if no item is selected. See: `getSelection/1` """. @@ -322,12 +305,11 @@ getStringSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxControlWithItems_GetStringSelection), wxe_util:rec(?wxControlWithItems_GetStringSelection). -%% @doc See external documentation. -doc """ Inserts item into the control. -Return: The return value is the index of the newly inserted item. If the -insertion failed for some reason, -1 is returned. +Return: The return value is the index of the newly inserted item. If the insertion failed +for some reason, -1 is returned. """. -spec insert(This, Item, Pos) -> integer() when This::wxControlWithItems(), Item::unicode:chardata(), Pos::integer(). @@ -338,12 +320,11 @@ insert(#wx_ref{type=ThisT}=This,Item,Pos) wxe_util:queue_cmd(This,Item_UC,Pos,?get_env(),?wxControlWithItems_Insert_2), wxe_util:rec(?wxControlWithItems_Insert_2). -%% @doc See external documentation. -doc """ Inserts item into the control. -Return: The return value is the index of the newly inserted item. If the -insertion failed for some reason, -1 is returned. +Return: The return value is the index of the newly inserted item. If the insertion failed +for some reason, -1 is returned. """. -spec insert(This, Item, Pos, ClientData) -> integer() when This::wxControlWithItems(), Item::unicode:chardata(), Pos::integer(), ClientData::term(). @@ -354,15 +335,14 @@ insert(#wx_ref{type=ThisT}=This,Item,Pos,ClientData) wxe_util:queue_cmd(This,Item_UC,Pos,ClientData,?get_env(),?wxControlWithItems_Insert_3), wxe_util:rec(?wxControlWithItems_Insert_3). -%% @doc See external documentation. -doc """ Inserts several items at once into the control. -Notice that calling this method is usually much faster than inserting them one -by one if you need to insert a lot of items. +Notice that calling this method is usually much faster than inserting them one by one if +you need to insert a lot of items. -Return: The return value is the index of the last inserted item. If the -insertion failed for some reason, -1 is returned. +Return: The return value is the index of the last inserted item. If the insertion failed +for some reason, -1 is returned. """. -spec insertStrings(This, Items, Pos) -> integer() when This::wxControlWithItems(), Items::[unicode:chardata()], Pos::integer(). @@ -374,15 +354,14 @@ insertStrings(#wx_ref{type=ThisT}=This,Items,Pos) wxe_util:queue_cmd(This,Items_UCA,Pos,?get_env(),?wxControlWithItems_insertStrings_2), wxe_util:rec(?wxControlWithItems_insertStrings_2). -%% @doc See external documentation. -doc """ Inserts several items at once into the control. -Notice that calling this method is usually much faster than inserting them one -by one if you need to insert a lot of items. +Notice that calling this method is usually much faster than inserting them one by one if +you need to insert a lot of items. -Return: The return value is the index of the last inserted item. If the -insertion failed for some reason, -1 is returned. +Return: The return value is the index of the last inserted item. If the insertion failed +for some reason, -1 is returned. """. -spec insertStrings(This, Items, Pos, ClientsData) -> integer() when This::wxControlWithItems(), Items::[unicode:chardata()], Pos::integer(), ClientsData::[term()]. @@ -394,7 +373,6 @@ insertStrings(#wx_ref{type=ThisT}=This,Items,Pos,ClientsData) wxe_util:queue_cmd(This,Items_UCA,Pos,ClientsData,?get_env(),?wxControlWithItems_insertStrings_3), wxe_util:rec(?wxControlWithItems_insertStrings_3). -%% @doc See external documentation. -doc """ Returns true if the control is empty or false if it has some items. @@ -407,10 +385,9 @@ isEmpty(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxControlWithItems_IsEmpty), wxe_util:rec(?wxControlWithItems_IsEmpty). -%% @doc See external documentation. -doc """ -This is the same as `setSelection/2` and exists only because it is slightly more -natural for controls which support multiple selection. +This is the same as `setSelection/2` and exists only because it is slightly more natural +for controls which support multiple selection. """. -spec select(This, N) -> 'ok' when This::wxControlWithItems(), N::integer(). @@ -419,15 +396,16 @@ select(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxControlWithItems), wxe_util:queue_cmd(This,N,?get_env(),?wxControlWithItems_Select). -%% @doc See external documentation. -doc """ -Sets the selection to the given item `n` or removes the selection entirely if -`n` == `wxNOT_FOUND`. +Sets the selection to the given item `n` or removes the selection entirely if `n` == `wxNOT\_FOUND`. + +Note that this does not cause any command events to be emitted nor does it deselect any +other items in the controls which support multiple selections. -Note that this does not cause any command events to be emitted nor does it -deselect any other items in the controls which support multiple selections. +See: +* `setString/3` -See: `setString/3`, `setStringSelection/2` +* `setStringSelection/2` """. -spec setSelection(This, N) -> 'ok' when This::wxControlWithItems(), N::integer(). @@ -436,7 +414,6 @@ setSelection(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxControlWithItems), wxe_util:queue_cmd(This,N,?get_env(),?wxControlWithItems_SetSelection). -%% @doc See external documentation. -doc "Sets the label for the given item.". -spec setString(This, N, String) -> 'ok' when This::wxControlWithItems(), N::integer(), String::unicode:chardata(). @@ -446,19 +423,17 @@ setString(#wx_ref{type=ThisT}=This,N,String) String_UC = unicode:characters_to_binary(String), wxe_util:queue_cmd(This,N,String_UC,?get_env(),?wxControlWithItems_SetString). -%% @doc See external documentation. -doc """ Selects the item with the specified string in the control. This method doesn't cause any command events to be emitted. -Notice that this method is case-insensitive, i.e. the string is compared with -all the elements of the control case-insensitively and the first matching entry -is selected, even if it doesn't have exactly the same case as this string and -there is an exact match afterwards. +Notice that this method is case-insensitive, i.e. the string is compared with all the +elements of the control case-insensitively and the first matching entry is selected, even +if it doesn't have exactly the same case as this string and there is an exact match afterwards. -Return: true if the specified string has been selected, false if it wasn't found -in the control. +Return: true if the specified string has been selected, false if it wasn't found in the +control. """. -spec setStringSelection(This, String) -> boolean() when This::wxControlWithItems(), String::unicode:chardata(). @@ -470,554 +445,371 @@ setStringSelection(#wx_ref{type=ThisT}=This,String) wxe_util:rec(?wxControlWithItems_SetStringSelection). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxCursor.erl b/lib/wx/src/gen/wxCursor.erl index 56d5627f11f6..a44ca5f4d559 100644 --- a/lib/wx/src/gen/wxCursor.erl +++ b/lib/wx/src/gen/wxCursor.erl @@ -20,35 +20,50 @@ -module(wxCursor). -moduledoc """ -Functions for wxCursor class +A cursor is a small bitmap usually used for denoting where the mouse pointer is, with a +picture that might indicate the interpretation of a mouse click. -A cursor is a small bitmap usually used for denoting where the mouse pointer is, -with a picture that might indicate the interpretation of a mouse click. As with -icons, cursors in X and MS Windows are created in a different manner. Therefore, -separate cursors will be created for the different environments. -Platform-specific methods for creating a `m:wxCursor` object are catered for, -and this is an occasion where conditional compilation will probably be required -(see `m:wxIcon` for an example). +As with icons, cursors in X and MS Windows are created in a different manner. Therefore, +separate cursors will be created for the different environments. Platform-specific methods +for creating a `m:wxCursor` object are catered for, and this is an occasion where +conditional compilation will probably be required (see `m:wxIcon` for an example). -A single cursor object may be used in many windows (any subwindow type). The -wxWidgets convention is to set the cursor for a window, as in X, rather than to -set it globally as in MS Windows, although a global `wx_misc:setCursor/1` -function is also available for MS Windows use. +A single cursor object may be used in many windows (any subwindow type). The wxWidgets +convention is to set the cursor for a window, as in X, rather than to set it globally as +in MS Windows, although a global `wx_misc:setCursor/1` function is also available for MS Windows use. Creating a Custom Cursor -The following is an example of creating a cursor from 32x32 bitmap data -(down_bits) and a mask (down_mask) where 1 is black and 0 is white for the bits, -and 1 is opaque and 0 is transparent for the mask. It works on Windows and GTK+. +The following is an example of creating a cursor from 32x32 bitmap data (down_bits) and a +mask (down_mask) where 1 is black and 0 is white for the bits, and 1 is opaque and 0 is +transparent for the mask. It works on Windows and GTK+. Predefined objects (include wx.hrl): -See: `m:wxBitmap`, `m:wxIcon`, `wxWindow:setCursor/2`, `wx_misc:setCursor/1`, -?wxStockCursor +* ?wxNullCursor -This class is derived (and can use functions) from: `m:wxBitmap` +* ?wxSTANDARD\_CURSOR -wxWidgets docs: [wxCursor](https://docs.wxwidgets.org/3.1/classwx_cursor.html) +* ?wxHOURGLASS\_CURSOR + +* ?wxCROSS\_CURSOR + +See: +* `m:wxBitmap` + +* `m:wxIcon` + +* `wxWindow:setCursor/2` + +* `wx_misc:setCursor/1` + +* ?wxStockCursor + +This class is derived, and can use functions, from: + +* `m:wxBitmap` + +wxWidgets docs: [wxCursor](https://docs.wxwidgets.org/3.2/classwx_cursor.html) """. -include("wxe.hrl"). -export([destroy/1,isOk/1,new/0,new/1,new/2,ok/1]). @@ -60,28 +75,19 @@ wxWidgets docs: [wxCursor](https://docs.wxwidgets.org/3.1/classwx_cursor.html) -type wxCursor() :: wx:wx_object(). -export_type([wxCursor/0]). -%% @hidden -doc false. parent_class(wxBitmap) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxCursor(). new() -> wxe_util:queue_cmd(?get_env(), ?wxCursor_new_0), wxe_util:rec(?wxCursor_new_0). -%% @doc See external documentation. -%%
Also:
-%% new(Image) -> wxCursor() when
-%% Image::wxImage:wxImage() | wxCursor:wxCursor();
-%% (CursorId) -> wxCursor() when
-%% CursorId::wx:wx_enum().
-%% -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -%%
CursorId = ?wxCURSOR_NONE | ?wxCURSOR_ARROW | ?wxCURSOR_RIGHT_ARROW | ?wxCURSOR_BULLSEYE | ?wxCURSOR_CHAR | ?wxCURSOR_CROSS | ?wxCURSOR_HAND | ?wxCURSOR_IBEAM | ?wxCURSOR_LEFT_BUTTON | ?wxCURSOR_MAGNIFIER | ?wxCURSOR_MIDDLE_BUTTON | ?wxCURSOR_NO_ENTRY | ?wxCURSOR_PAINT_BRUSH | ?wxCURSOR_PENCIL | ?wxCURSOR_POINT_LEFT | ?wxCURSOR_POINT_RIGHT | ?wxCURSOR_QUESTION_ARROW | ?wxCURSOR_RIGHT_BUTTON | ?wxCURSOR_SIZENESW | ?wxCURSOR_SIZENS | ?wxCURSOR_SIZENWSE | ?wxCURSOR_SIZEWE | ?wxCURSOR_SIZING | ?wxCURSOR_SPRAYCAN | ?wxCURSOR_WAIT | ?wxCURSOR_WATCH | ?wxCURSOR_BLANK | ?wxCURSOR_DEFAULT | ?wxCURSOR_ARROWWAIT | ?wxCURSOR_MAX -doc "Constructs a cursor using a cursor identifier.". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY +%% CursorId = ?wxCURSOR_NONE | ?wxCURSOR_ARROW | ?wxCURSOR_RIGHT_ARROW | ?wxCURSOR_BULLSEYE | ?wxCURSOR_CHAR | ?wxCURSOR_CROSS | ?wxCURSOR_HAND | ?wxCURSOR_IBEAM | ?wxCURSOR_LEFT_BUTTON | ?wxCURSOR_MAGNIFIER | ?wxCURSOR_MIDDLE_BUTTON | ?wxCURSOR_NO_ENTRY | ?wxCURSOR_PAINT_BRUSH | ?wxCURSOR_PENCIL | ?wxCURSOR_POINT_LEFT | ?wxCURSOR_POINT_RIGHT | ?wxCURSOR_QUESTION_ARROW | ?wxCURSOR_RIGHT_BUTTON | ?wxCURSOR_SIZENESW | ?wxCURSOR_SIZENS | ?wxCURSOR_SIZENWSE | ?wxCURSOR_SIZEWE | ?wxCURSOR_SIZING | ?wxCURSOR_SPRAYCAN | ?wxCURSOR_WAIT | ?wxCURSOR_WATCH | ?wxCURSOR_BLANK | ?wxCURSOR_DEFAULT | ?wxCURSOR_ARROWWAIT | ?wxCURSOR_MAX -spec new(CursorName) -> wxCursor() when CursorName::unicode:chardata(); (Image) -> wxCursor() when @@ -107,15 +113,14 @@ new(CursorId) wxe_util:queue_cmd(CursorId,?get_env(),?wxCursor_new_1_1), wxe_util:rec(?wxCursor_new_1_1). -%% @doc See external documentation. -%%
Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Constructs a cursor by passing a string resource name or filename. -The arguments `hotSpotX` and `hotSpotY` are only used when there's no hotspot -info in the resource/image-file to load (e.g. when using `wxBITMAP_TYPE_ICO` -under wxMSW or `wxBITMAP_TYPE_XPM` under wxGTK). +The arguments `hotSpotX` and `hotSpotY` are only used when there's no hotspot info in the +resource/image-file to load (e.g. when using `wxBITMAP_TYPE_ICO` under wxMSW or `wxBITMAP_TYPE_XPM` +under wxGTK). """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(CursorName, [Option]) -> wxCursor() when CursorName::unicode:chardata(), Option :: {'type', wx:wx_enum()} @@ -132,8 +137,7 @@ new(CursorName, Options) wxe_util:queue_cmd(CursorName_UC, Opts,?get_env(),?wxCursor_new_2), wxe_util:rec(?wxCursor_new_2). -%% @doc See external documentation. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxCursor(). @@ -141,7 +145,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See external documentation. -doc "Returns true if cursor data is present.". -spec isOk(This) -> boolean() when This::wxCursor(). @@ -150,70 +153,44 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxCursor_IsOk), wxe_util:rec(?wxCursor_IsOk). -%% @doc Destroys this object, do not use object again --doc """ -Destroys the cursor. - -See reference-counted object destruction for more info. - -A cursor can be reused for more than one window, and does not get destroyed when -the window is destroyed. wxWidgets destroys all cursors on application exit, -although it is best to clean them up explicitly. -""". +-doc "Destroys the object". -spec destroy(This::wxCursor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxCursor), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBitmap -%% @hidden -doc false. setWidth(This,Width) -> wxBitmap:setWidth(This,Width). -%% @hidden -doc false. setPalette(This,Palette) -> wxBitmap:setPalette(This,Palette). -%% @hidden -doc false. setMask(This,Mask) -> wxBitmap:setMask(This,Mask). -%% @hidden -doc false. setHeight(This,Height) -> wxBitmap:setHeight(This,Height). -%% @hidden -doc false. setDepth(This,Depth) -> wxBitmap:setDepth(This,Depth). -%% @hidden -doc false. saveFile(This,Name,Type, Options) -> wxBitmap:saveFile(This,Name,Type, Options). -%% @hidden -doc false. saveFile(This,Name,Type) -> wxBitmap:saveFile(This,Name,Type). -%% @hidden -doc false. loadFile(This,Name, Options) -> wxBitmap:loadFile(This,Name, Options). -%% @hidden -doc false. loadFile(This,Name) -> wxBitmap:loadFile(This,Name). -%% @hidden -doc false. getSubBitmap(This,Rect) -> wxBitmap:getSubBitmap(This,Rect). -%% @hidden -doc false. getWidth(This) -> wxBitmap:getWidth(This). -%% @hidden -doc false. getMask(This) -> wxBitmap:getMask(This). -%% @hidden -doc false. getPalette(This) -> wxBitmap:getPalette(This). -%% @hidden -doc false. getHeight(This) -> wxBitmap:getHeight(This). -%% @hidden -doc false. getDepth(This) -> wxBitmap:getDepth(This). -%% @hidden -doc false. copyFromIcon(This,Icon) -> wxBitmap:copyFromIcon(This,Icon). -%% @hidden -doc false. convertToImage(This) -> wxBitmap:convertToImage(This). diff --git a/lib/wx/src/gen/wxDC.erl b/lib/wx/src/gen/wxDC.erl index 5bc279bc17eb..c90950cbd661 100644 --- a/lib/wx/src/gen/wxDC.erl +++ b/lib/wx/src/gen/wxDC.erl @@ -20,84 +20,74 @@ -module(wxDC). -moduledoc """ -Functions for wxDC class - -A `m:wxDC` is a `"device context"` onto which graphics and text can be drawn. It -is intended to represent different output devices and offers a common abstract -API for drawing on any of them. - -wxWidgets offers an alternative drawing API based on the modern drawing backends -GDI+, CoreGraphics, Cairo and Direct2D. See `m:wxGraphicsContext`, -`m:wxGraphicsRenderer` and related classes. There is also a `m:wxGCDC` linking -the APIs by offering the `m:wxDC` API on top of a `m:wxGraphicsContext`. - -`m:wxDC` is an abstract base class and cannot be created directly. Use -`m:wxPaintDC`, `m:wxClientDC`, `m:wxWindowDC`, `m:wxScreenDC`, `m:wxMemoryDC` or -`wxPrinterDC` (not implemented in wx). Notice that device contexts which are -associated with windows (i.e. `m:wxClientDC`, `m:wxWindowDC` and `m:wxPaintDC`) -use the window font and colours by default (starting with wxWidgets 2.9.0) but -the other device context classes use system-default values so you always must -set the appropriate fonts and colours before using them. - -In addition to the versions of the methods documented below, there are also -versions which accept single \{X,Y\} parameter instead of the two wxCoord ones -or \{X,Y\} and \{Width,Height\} instead of the four wxCoord parameters. - -Beginning with wxWidgets 2.9.0 the entire `m:wxDC` code has been reorganized. -All platform dependent code (actually all drawing code) has been moved into -backend classes which derive from a common wxDCImpl class. The user-visible -classes such as `m:wxClientDC` and `m:wxPaintDC` merely forward all calls to the -backend implementation. +A `m:wxDC` is a `"device context"` onto which graphics and text can be drawn. + +It is intended to represent different output devices and offers a common abstract API for +drawing on any of them. + +wxWidgets offers an alternative drawing API based on the modern drawing backends GDI+, +CoreGraphics, Cairo and Direct2D. See `m:wxGraphicsContext`, `m:wxGraphicsRenderer` and +related classes. There is also a `m:wxGCDC` linking the APIs by offering the `m:wxDC` API +on top of a `m:wxGraphicsContext`. + +`m:wxDC` is an abstract base class and cannot be created directly. Use `m:wxPaintDC`, `m:wxClientDC`, `m:wxWindowDC`, `m:wxScreenDC`, `m:wxMemoryDC` +or `wxPrinterDC` (not implemented in wx). Notice that device contexts which are +associated with windows (i.e. `m:wxClientDC`, `m:wxWindowDC` and `m:wxPaintDC`) use the +window font and colours by default (starting with wxWidgets 2.9.0) but the other device +context classes use system-default values so you always must set the appropriate fonts and +colours before using them. + +In addition to the versions of the methods documented below, there are also versions +which accept single {X,Y} parameter instead of the two wxCoord ones or {X,Y} and +{Width,Height} instead of the four wxCoord parameters. + +Beginning with wxWidgets 2.9.0 the entire `m:wxDC` code has been reorganized. All +platform dependent code (actually all drawing code) has been moved into backend classes +which derive from a common wxDCImpl class. The user-visible classes such as `m:wxClientDC` +and `m:wxPaintDC` merely forward all calls to the backend implementation. Device and logical units -In the `m:wxDC` context there is a distinction between `logical` units and -`device` units. +In the `m:wxDC` context there is a distinction between `logical` units and `device` units. -`Device` units are the units native to the particular device; e.g. for a screen, -a device unit is a `pixel`. For a printer, the device unit is defined by the -resolution of the printer (usually given in `DPI:` dot-per-inch). +`Device` units are the units native to the particular device; e.g. for a screen, a device +unit is a `pixel`. For a printer, the device unit is defined by the resolution of the +printer (usually given in `DPI:` dot-per-inch). -All `m:wxDC` functions use instead `logical` units, unless where explicitly -stated. Logical units are arbitrary units mapped to device units using the -current mapping mode (see `setMapMode/2`). +All `m:wxDC` functions use instead `logical` units, unless where explicitly stated. +Logical units are arbitrary units mapped to device units using the current mapping mode +(see `setMapMode/2`). -This mechanism allows reusing the same code which prints on e.g. a window on the -screen to print on e.g. a paper. +This mechanism allows reusing the same code which prints on e.g. a window on the screen +to print on e.g. a paper. Support for Transparency / Alpha Channel -In general `m:wxDC` methods don't support alpha transparency and the alpha -component of [`wx_color()`](`t:wx:wx_colour/0`) is simply ignored and you need -to use `m:wxGraphicsContext` for full transparency support. There are, however, -a few exceptions: first, under macOS and GTK+ 3 colours with alpha channel are -supported in all the normal wxDC-derived classes as they use -`m:wxGraphicsContext` internally. Second, under all platforms `wxSVGFileDC` (not -implemented in wx) also fully supports alpha channel. In both of these cases the -instances of `m:wxPen` or `m:wxBrush` that are built from -[`wx_color()`](`t:wx:wx_colour/0`) use the colour's alpha values when stroking -or filling. +In general `m:wxDC` methods don't support alpha transparency and the alpha component of `wx_color()` +is simply ignored and you need to use `m:wxGraphicsContext` for full transparency support. +There are, however, a few exceptions: first, under macOS and GTK+ 3 colours with alpha +channel are supported in all the normal wxDC-derived classes as they use `m:wxGraphicsContext` +internally. Second, under all platforms `wxSVGFileDC` (not implemented in wx) also fully +supports alpha channel. In both of these cases the instances of `m:wxPen` or `m:wxBrush` +that are built from `wx_color()` use the colour's alpha values when stroking or filling. Support for Transformation Matrix -On some platforms (currently under MSW, GTK+ 3, macOS) `m:wxDC` has support for -applying an arbitrary affine transformation matrix to its coordinate system -(since 3.1.1 this feature is also supported by `m:wxGCDC` in all ports). Call -`CanUseTransformMatrix()` (not implemented in wx) to check if this support is -available and then call `SetTransformMatrix()` (not implemented in wx) if it is. -If the transformation matrix is not supported, `SetTransformMatrix()` (not -implemented in wx) always simply returns `false` and doesn't do anything. +On some platforms (currently under MSW, GTK+ 3, macOS) `m:wxDC` has support for applying +an arbitrary affine transformation matrix to its coordinate system (since 3.1.1 this +feature is also supported by `m:wxGCDC` in all ports). Call `CanUseTransformMatrix()` (not +implemented in wx) to check if this support is available and then call `SetTransformMatrix()` +(not implemented in wx) if it is. If the transformation matrix is not supported, `SetTransformMatrix()` +(not implemented in wx) always simply returns `false` and doesn't do anything. + +This feature is only available when `wxUSE_DC_TRANSFORM_MATRIX` build option is enabled. -This feature is only available when `wxUSE_DC_TRANSFORM_MATRIX` build option is -enabled. +See: +* [Overview dc](https://docs.wxwidgets.org/3.2/overview_dc.html#overview_dc) -See: [Overview dc](https://docs.wxwidgets.org/3.1/overview_dc.html#overview_dc), -`m:wxGraphicsContext`, `wxDCFontChanger` (not implemented in wx), -`wxDCTextColourChanger` (not implemented in wx), `wxDCPenChanger` (not -implemented in wx), `wxDCBrushChanger` (not implemented in wx), `wxDCClipper` -(not implemented in wx) +* `m:wxGraphicsContext` -wxWidgets docs: [wxDC](https://docs.wxwidgets.org/3.1/classwx_d_c.html) +wxWidgets docs: [wxDC](https://docs.wxwidgets.org/3.2/classwx_d_c.html) """. -include("wxe.hrl"). -export([blit/5,blit/6,calcBoundingBox/3,clear/1,crossHair/2,destroyClippingRegion/1, @@ -126,11 +116,10 @@ wxWidgets docs: [wxDC](https://docs.wxwidgets.org/3.1/classwx_d_c.html) -type wxDC() :: wx:wx_object(). -export_type([wxDC/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv blit(This,Dest,Size,Source,Src, []) +-doc(#{equiv => blit(This,Dest,Size,Source,Src, [])}). -spec blit(This, Dest, Size, Source, Src) -> boolean() when This::wxDC(), Dest::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Source::wxDC(), Src::{X::integer(), Y::integer()}. @@ -138,26 +127,27 @@ blit(This,{DestX,DestY} = Dest,{SizeW,SizeH} = Size,Source,{SrcX,SrcY} = Src) when is_record(This, wx_ref),is_integer(DestX),is_integer(DestY),is_integer(SizeW),is_integer(SizeH),is_record(Source, wx_ref),is_integer(SrcX),is_integer(SrcY) -> blit(This,Dest,Size,Source,Src, []). -%% @doc See external documentation. -%%
Rop = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -doc """ Copy from a source DC to this DC. -With this method you can specify the destination coordinates and the size of -area to copy which will be the same for both the source and target DCs. If you -need to apply scaling while copying, use `StretchBlit()` (not implemented in -wx). +With this method you can specify the destination coordinates and the size of area to copy +which will be the same for both the source and target DCs. If you need to apply scaling +while copying, use `StretchBlit()` (not implemented in wx). -Notice that source DC coordinates `xsrc` and `ysrc` are interpreted using the -current source DC coordinate system, i.e. the scale, origin position and axis -directions are taken into account when transforming them to physical (pixel) -coordinates. +Notice that source DC coordinates `xsrc` and `ysrc` are interpreted using the current +source DC coordinate system, i.e. the scale, origin position and axis directions are taken +into account when transforming them to physical (pixel) coordinates. Remark: There is partial support for `blit/6` in `m:wxPostScriptDC`, under X. -See: `StretchBlit()` (not implemented in wx), `m:wxMemoryDC`, `m:wxBitmap`, -`m:wxMask` +See: +* `m:wxMemoryDC` + +* `m:wxBitmap` + +* `m:wxMask` """. +%% Rop = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -spec blit(This, Dest, Size, Source, Src, [Option]) -> boolean() when This::wxDC(), Dest::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Source::wxDC(), Src::{X::integer(), Y::integer()}, Option :: {'rop', wx:wx_enum()} @@ -175,10 +165,9 @@ blit(#wx_ref{type=ThisT}=This,{DestX,DestY} = Dest,{SizeW,SizeH} = Size,#wx_ref{ wxe_util:queue_cmd(This,Dest,Size,Source,Src, Opts,?get_env(),?wxDC_Blit), wxe_util:rec(?wxDC_Blit). -%% @doc See external documentation. -doc """ -Adds the specified point to the bounding box which can be retrieved with -`minX/1`, `maxX/1` and `minY/1`, `maxY/1` functions. +Adds the specified point to the bounding box which can be retrieved with `minX/1`, `maxX/1` +and `minY/1`, `maxY/1` functions. See: `resetBoundingBox/1` """. @@ -189,16 +178,13 @@ calcBoundingBox(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxDC_CalcBoundingBox). -%% @doc See external documentation. -doc """ Clears the device context using the current background brush. -Note that `setBackground/2` method must be used to set the brush used by -`clear/1`, the brush used for filling the shapes set by `setBrush/2` is ignored -by it. +Note that `setBackground/2` method must be used to set the brush used by `clear/1`, the brush used for filling the +shapes set by `setBrush/2` is ignored by it. -If no background brush was set, solid white brush is used to clear the device -context. +If no background brush was set, solid white brush is used to clear the device context. """. -spec clear(This) -> 'ok' when This::wxDC(). @@ -206,10 +192,9 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,?get_env(),?wxDC_Clear). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec crossHair(This, Pt) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}. @@ -218,7 +203,6 @@ crossHair(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,?get_env(),?wxDC_CrossHair). -%% @doc See external documentation. -doc """ Destroys the current clipping region so that none of the DC is clipped. @@ -230,10 +214,9 @@ destroyClippingRegion(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,?get_env(),?wxDC_DestroyClippingRegion). -%% @doc See external documentation. -doc """ -Convert `device` X coordinate to logical coordinate, using the current mapping -mode, user scale factor, device origin and axis orientation. +Convert `device` X coordinate to logical coordinate, using the current mapping mode, user +scale factor, device origin and axis orientation. """. -spec deviceToLogicalX(This, X) -> integer() when This::wxDC(), X::integer(). @@ -243,10 +226,9 @@ deviceToLogicalX(#wx_ref{type=ThisT}=This,X) wxe_util:queue_cmd(This,X,?get_env(),?wxDC_DeviceToLogicalX), wxe_util:rec(?wxDC_DeviceToLogicalX). -%% @doc See external documentation. -doc """ -Convert `device` X coordinate to relative logical coordinate, using the current -mapping mode and user scale factor but ignoring the axis orientation. +Convert `device` X coordinate to relative logical coordinate, using the current mapping +mode and user scale factor but ignoring the axis orientation. Use this for converting a width, for example. """. @@ -258,10 +240,9 @@ deviceToLogicalXRel(#wx_ref{type=ThisT}=This,X) wxe_util:queue_cmd(This,X,?get_env(),?wxDC_DeviceToLogicalXRel), wxe_util:rec(?wxDC_DeviceToLogicalXRel). -%% @doc See external documentation. -doc """ -Converts `device` Y coordinate to logical coordinate, using the current mapping -mode, user scale factor, device origin and axis orientation. +Converts `device` Y coordinate to logical coordinate, using the current mapping mode, +user scale factor, device origin and axis orientation. """. -spec deviceToLogicalY(This, Y) -> integer() when This::wxDC(), Y::integer(). @@ -271,10 +252,9 @@ deviceToLogicalY(#wx_ref{type=ThisT}=This,Y) wxe_util:queue_cmd(This,Y,?get_env(),?wxDC_DeviceToLogicalY), wxe_util:rec(?wxDC_DeviceToLogicalY). -%% @doc See external documentation. -doc """ -Convert `device` Y coordinate to relative logical coordinate, using the current -mapping mode and user scale factor but ignoring the axis orientation. +Convert `device` Y coordinate to relative logical coordinate, using the current mapping +mode and user scale factor but ignoring the axis orientation. Use this for converting a height, for example. """. @@ -286,10 +266,9 @@ deviceToLogicalYRel(#wx_ref{type=ThisT}=This,Y) wxe_util:queue_cmd(This,Y,?get_env(),?wxDC_DeviceToLogicalYRel), wxe_util:rec(?wxDC_DeviceToLogicalYRel). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawArc(This, PtStart, PtEnd, Centre) -> 'ok' when This::wxDC(), PtStart::{X::integer(), Y::integer()}, PtEnd::{X::integer(), Y::integer()}, Centre::{X::integer(), Y::integer()}. @@ -298,7 +277,7 @@ drawArc(#wx_ref{type=ThisT}=This,{PtStartX,PtStartY} = PtStart,{PtEndX,PtEndY} = ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,PtStart,PtEnd,Centre,?get_env(),?wxDC_DrawArc). -%% @equiv drawBitmap(This,Bmp,Pt, []) +-doc(#{equiv => drawBitmap(This,Bmp,Pt, [])}). -spec drawBitmap(This, Bmp, Pt) -> 'ok' when This::wxDC(), Bmp::wxBitmap:wxBitmap(), Pt::{X::integer(), Y::integer()}. @@ -306,10 +285,9 @@ drawBitmap(This,Bmp,{PtX,PtY} = Pt) when is_record(This, wx_ref),is_record(Bmp, wx_ref),is_integer(PtX),is_integer(PtY) -> drawBitmap(This,Bmp,Pt, []). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawBitmap(This, Bmp, Pt, [Option]) -> 'ok' when This::wxDC(), Bmp::wxBitmap:wxBitmap(), Pt::{X::integer(), Y::integer()}, @@ -323,10 +301,9 @@ drawBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=BmpT}=Bmp,{PtX,PtY} = Pt, Optio Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Bmp,Pt, Opts,?get_env(),?wxDC_DrawBitmap). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawCheckMark(This, Rect) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -335,10 +312,9 @@ drawCheckMark(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,?get_env(),?wxDC_DrawCheckMark). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawCircle(This, Pt, Radius) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Radius::integer(). @@ -347,10 +323,9 @@ drawCircle(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,Radius) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Radius,?get_env(),?wxDC_DrawCircle). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawEllipse(This, Rect) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -359,10 +334,9 @@ drawEllipse(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,?get_env(),?wxDC_DrawEllipse_1). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawEllipse(This, Pt, Size) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}. @@ -371,10 +345,9 @@ drawEllipse(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Size,?get_env(),?wxDC_DrawEllipse_2). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawEllipticArc(This, Pt, Sz, Sa, Ea) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Sz::{W::integer(), H::integer()}, Sa::number(), Ea::number(). @@ -383,10 +356,9 @@ drawEllipticArc(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,{SzW,SzH} = Sz,Sa,Ea) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Sz,Sa,Ea,?get_env(),?wxDC_DrawEllipticArc). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawIcon(This, Icon, Pt) -> 'ok' when This::wxDC(), Icon::wxIcon:wxIcon(), Pt::{X::integer(), Y::integer()}. @@ -396,7 +368,7 @@ drawIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon,{PtX,PtY} = Pt) ?CLASS(IconT,wxIcon), wxe_util:queue_cmd(This,Icon,Pt,?get_env(),?wxDC_DrawIcon). -%% @equiv drawLabel(This,Text,Rect, []) +-doc(#{equiv => drawLabel(This,Text,Rect, [])}). -spec drawLabel(This, Text, Rect) -> 'ok' when This::wxDC(), Text::unicode:chardata(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -404,10 +376,9 @@ drawLabel(This,Text,{RectX,RectY,RectW,RectH} = Rect) when is_record(This, wx_ref),?is_chardata(Text),is_integer(RectX),is_integer(RectY),is_integer(RectW),is_integer(RectH) -> drawLabel(This,Text,Rect, []). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawLabel(This, Text, Rect, [Option]) -> 'ok' when This::wxDC(), Text::unicode:chardata(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, @@ -423,10 +394,9 @@ drawLabel(#wx_ref{type=ThisT}=This,Text,{RectX,RectY,RectW,RectH} = Rect, Option Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Text_UC,Rect, Opts,?get_env(),?wxDC_DrawLabel). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawLine(This, Pt1, Pt2) -> 'ok' when This::wxDC(), Pt1::{X::integer(), Y::integer()}, Pt2::{X::integer(), Y::integer()}. @@ -435,7 +405,7 @@ drawLine(#wx_ref{type=ThisT}=This,{Pt1X,Pt1Y} = Pt1,{Pt2X,Pt2Y} = Pt2) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt1,Pt2,?get_env(),?wxDC_DrawLine). -%% @equiv drawLines(This,Points, []) +-doc(#{equiv => drawLines(This,Points, [])}). -spec drawLines(This, Points) -> 'ok' when This::wxDC(), Points::[{X::integer(), Y::integer()}]. @@ -443,10 +413,8 @@ drawLines(This,Points) when is_record(This, wx_ref),is_list(Points) -> drawLines(This,Points, []). -%% @doc See external documentation. -doc """ -Draws lines using an array of points of size `n` adding the optional offset -coordinate. +Draws lines using an array of points of size `n` adding the optional offset coordinate. The current pen is used for drawing the lines. """. @@ -463,7 +431,7 @@ drawLines(#wx_ref{type=ThisT}=This,Points, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Points, Opts,?get_env(),?wxDC_DrawLines). -%% @equiv drawPolygon(This,Points, []) +-doc(#{equiv => drawPolygon(This,Points, [])}). -spec drawPolygon(This, Points) -> 'ok' when This::wxDC(), Points::[{X::integer(), Y::integer()}]. @@ -471,20 +439,18 @@ drawPolygon(This,Points) when is_record(This, wx_ref),is_list(Points) -> drawPolygon(This,Points, []). -%% @doc See external documentation. -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc """ -Draws a filled polygon using an array of points of size `n`, adding the optional -offset coordinate. +Draws a filled polygon using an array of points of size `n`, adding the optional offset +coordinate. The first and last points are automatically closed. -The last argument specifies the fill rule: `wxODDEVEN_RULE` (the default) or -`wxWINDING_RULE`. +The last argument specifies the fill rule: `wxODDEVEN_RULE` (the default) or `wxWINDING_RULE`. -The current pen is used for drawing the outline, and the current brush for -filling the shape. Using a transparent brush suppresses filling. +The current pen is used for drawing the outline, and the current brush for filling the +shape. Using a transparent brush suppresses filling. """. +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec drawPolygon(This, Points, [Option]) -> 'ok' when This::wxDC(), Points::[{X::integer(), Y::integer()}], Option :: {'xoffset', integer()} @@ -500,10 +466,9 @@ drawPolygon(#wx_ref{type=ThisT}=This,Points, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Points, Opts,?get_env(),?wxDC_DrawPolygon). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawPoint(This, Pt) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}. @@ -512,10 +477,9 @@ drawPoint(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,?get_env(),?wxDC_DrawPoint). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawRectangle(This, Rect) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -524,10 +488,9 @@ drawRectangle(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,?get_env(),?wxDC_DrawRectangle_1). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawRectangle(This, Pt, Sz) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Sz::{W::integer(), H::integer()}. @@ -536,10 +499,9 @@ drawRectangle(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,{SzW,SzH} = Sz) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Sz,?get_env(),?wxDC_DrawRectangle_2). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawRotatedText(This, Text, Point, Angle) -> 'ok' when This::wxDC(), Text::unicode:chardata(), Point::{X::integer(), Y::integer()}, Angle::number(). @@ -549,10 +511,9 @@ drawRotatedText(#wx_ref{type=ThisT}=This,Text,{PointX,PointY} = Point,Angle) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,Point,Angle,?get_env(),?wxDC_DrawRotatedText). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawRoundedRectangle(This, Rect, Radius) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, Radius::number(). @@ -561,10 +522,9 @@ drawRoundedRectangle(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect,R ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,Radius,?get_env(),?wxDC_DrawRoundedRectangle_2). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawRoundedRectangle(This, Pt, Sz, Radius) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Sz::{W::integer(), H::integer()}, Radius::number(). @@ -573,10 +533,9 @@ drawRoundedRectangle(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,{SzW,SzH} = Sz,Radi ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Sz,Radius,?get_env(),?wxDC_DrawRoundedRectangle_3). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec drawText(This, Text, Pt) -> 'ok' when This::wxDC(), Text::unicode:chardata(), Pt::{X::integer(), Y::integer()}. @@ -586,7 +545,6 @@ drawText(#wx_ref{type=ThisT}=This,Text,{PtX,PtY} = Pt) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,Pt,?get_env(),?wxDC_DrawText). -%% @doc See external documentation. -doc "Ends a document (only relevant when outputting to a printer).". -spec endDoc(This) -> 'ok' when This::wxDC(). @@ -594,7 +552,6 @@ endDoc(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,?get_env(),?wxDC_EndDoc). -%% @doc See external documentation. -doc "Ends a document page (only relevant when outputting to a printer).". -spec endPage(This) -> 'ok' when This::wxDC(). @@ -602,7 +559,7 @@ endPage(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,?get_env(),?wxDC_EndPage). -%% @equiv floodFill(This,Pt,Col, []) +-doc(#{equiv => floodFill(This,Pt,Col, [])}). -spec floodFill(This, Pt, Col) -> boolean() when This::wxDC(), Pt::{X::integer(), Y::integer()}, Col::wx:wx_colour(). @@ -610,12 +567,11 @@ floodFill(This,{PtX,PtY} = Pt,Col) when is_record(This, wx_ref),is_integer(PtX),is_integer(PtY),?is_colordata(Col) -> floodFill(This,Pt,Col, []). -%% @doc See external documentation. -%%
Style = ?wxFLOOD_SURFACE | ?wxFLOOD_BORDER -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. +%% Style = ?wxFLOOD_SURFACE | ?wxFLOOD_BORDER -spec floodFill(This, Pt, Col, [Option]) -> boolean() when This::wxDC(), Pt::{X::integer(), Y::integer()}, Col::wx:wx_colour(), Option :: {'style', wx:wx_enum()}. @@ -628,7 +584,6 @@ floodFill(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,Col, Options) wxe_util:queue_cmd(This,Pt,wxe_util:color(Col), Opts,?get_env(),?wxDC_FloodFill), wxe_util:rec(?wxDC_FloodFill). -%% @doc See external documentation. -doc """ Gets the brush used for painting the background. @@ -641,10 +596,8 @@ getBackground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetBackground), wxe_util:rec(?wxDC_GetBackground). -%% @doc See external documentation. -doc """ -Returns the current background mode: `wxPENSTYLE_SOLID` or -`wxPENSTYLE_TRANSPARENT`. +Returns the current background mode: `wxPENSTYLE\_SOLID` or `wxPENSTYLE\_TRANSPARENT`. See: `setBackgroundMode/2` """. @@ -655,7 +608,6 @@ getBackgroundMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetBackgroundMode), wxe_util:rec(?wxDC_GetBackgroundMode). -%% @doc See external documentation. -doc """ Gets the current brush. @@ -668,7 +620,6 @@ getBrush(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetBrush), wxe_util:rec(?wxDC_GetBrush). -%% @doc See external documentation. -doc "Gets the character height of the currently set font.". -spec getCharHeight(This) -> integer() when This::wxDC(). @@ -677,7 +628,6 @@ getCharHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetCharHeight), wxe_util:rec(?wxDC_GetCharHeight). -%% @doc See external documentation. -doc "Gets the average character width of the currently set font.". -spec getCharWidth(This) -> integer() when This::wxDC(). @@ -686,13 +636,22 @@ getCharWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetCharWidth), wxe_util:rec(?wxDC_GetCharWidth). -%% @doc See external documentation. -doc """ -`Gets the rectangle surrounding the current clipping region. If no clipping region is set this function returns the extent of the device context. @remarks Clipping region is given in logical coordinates. @param x If non-NULL, filled in with the logical horizontal coordinate of the top left corner of the clipping region if the function returns true or 0 otherwise. @param y If non-NULL, filled in with the logical vertical coordinate of the top left corner of the clipping region if the function returns true or 0 otherwise. @param width If non-NULL, filled in with the width of the clipping region if the function returns true or the device context width otherwise. @param height If non-NULL, filled in with the height of the clipping region if the function returns true or the device context height otherwise.` +` Gets the rectangle surrounding the current clipping region. If no clipping region is set +this function returns the extent of the device context. @remarks Clipping region is given +in logical coordinates. @param x If non-NULL, filled in with +the logical horizontal coordinate of the top left corner of the clipping region if the +function returns true or 0 otherwise. @param y If non-NULL, +filled in with the logical vertical coordinate of the top left corner of the clipping +region if the function returns true or 0 otherwise. @param width If non-NULL, filled in with the width of the clipping region if the +function returns true or the device context width otherwise. @param height If non-NULL, filled in with the height of the clipping region if the +function returns true or the device context height otherwise. ` -Return: true if there is a clipping region or false if there is no active -clipping region (note that this return value is available only since wxWidgets -3.1.2, this function didn't return anything in the previous versions). +Return: true if there is a clipping region or false if there is no active clipping region +(note that this return value is available only since wxWidgets 3.1.2, this function didn't +return anything in the previous versions). """. -spec getClippingBox(This) -> Result when Result ::{X::integer(), Y::integer(), Width::integer(), Height::integer()}, @@ -702,13 +661,12 @@ getClippingBox(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetClippingBox), wxe_util:rec(?wxDC_GetClippingBox). -%% @doc See external documentation. -doc """ Gets the current font. Notice that even although each device context object has some default font after -creation, this method would return a ?wxNullFont initially and only after -calling `setFont/2` a valid font is returned. +creation, this method would return a ?wxNullFont initially and only after calling `setFont/2` a valid +font is returned. """. -spec getFont(This) -> wxFont:wxFont() when This::wxDC(). @@ -717,17 +675,15 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetFont), wxe_util:rec(?wxDC_GetFont). -%% @doc See external documentation. -%%
Res = ?wxLayout_Default | ?wxLayout_LeftToRight | ?wxLayout_RightToLeft -doc """ Gets the current layout direction of the device context. -On platforms where RTL layout is supported, the return value will either be -`wxLayout_LeftToRight` or `wxLayout_RightToLeft`. If RTL layout is not -supported, the return value will be `wxLayout_Default`. +On platforms where RTL layout is supported, the return value will either be `wxLayout_LeftToRight` +or `wxLayout_RightToLeft`. If RTL layout is not supported, the return value will be `wxLayout_Default`. See: `setLayoutDirection/2` """. +%% Res = ?wxLayout_Default | ?wxLayout_LeftToRight | ?wxLayout_RightToLeft -spec getLayoutDirection(This) -> wx:wx_enum() when This::wxDC(). getLayoutDirection(#wx_ref{type=ThisT}=This) -> @@ -735,13 +691,12 @@ getLayoutDirection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetLayoutDirection), wxe_util:rec(?wxDC_GetLayoutDirection). -%% @doc See external documentation. -%%
Res = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -doc """ Gets the current logical function. See: `setLogicalFunction/2` """. +%% Res = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -spec getLogicalFunction(This) -> wx:wx_enum() when This::wxDC(). getLogicalFunction(#wx_ref{type=ThisT}=This) -> @@ -749,13 +704,12 @@ getLogicalFunction(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetLogicalFunction), wxe_util:rec(?wxDC_GetLogicalFunction). -%% @doc See external documentation. -%%
Res = ?wxMM_TEXT | ?wxMM_METRIC | ?wxMM_LOMETRIC | ?wxMM_TWIPS | ?wxMM_POINTS -doc """ Gets the current mapping mode for the device context. See: `setMapMode/2` """. +%% Res = ?wxMM_TEXT | ?wxMM_METRIC | ?wxMM_LOMETRIC | ?wxMM_TWIPS | ?wxMM_POINTS -spec getMapMode(This) -> wx:wx_enum() when This::wxDC(). getMapMode(#wx_ref{type=ThisT}=This) -> @@ -763,17 +717,23 @@ getMapMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetMapMode), wxe_util:rec(?wxDC_GetMapMode). -%% @doc See external documentation. -doc """ Gets the dimensions of the string using the currently selected font. `string` is the text string to measure. -Return: The text extent as a \{Width,Height\} object. +Return: The text extent as a {Width,Height} object. Note: This function works with both single-line and multi-line strings. -See: `m:wxFont`, `setFont/2`, `getPartialTextExtents/2`, `getTextExtent/3` +See: +* `m:wxFont` + +* `setFont/2` + +* `getPartialTextExtents/2` + +* `getTextExtent/3` """. -spec getMultiLineTextExtent(This, String) -> {W::integer(), H::integer()} when This::wxDC(), String::unicode:chardata(). @@ -784,26 +744,32 @@ getMultiLineTextExtent(#wx_ref{type=ThisT}=This,String) wxe_util:queue_cmd(This,String_UC,?get_env(),?wxDC_GetMultiLineTextExtent_1), wxe_util:rec(?wxDC_GetMultiLineTextExtent_1). -%% @doc See external documentation. -doc """ Gets the dimensions of the string using the currently selected font. -`string` is the text string to measure, `heightLine`, if non NULL, is where to -store the height of a single line. +`string` is the text string to measure, `heightLine`, if non NULL, is where to store the +height of a single line. The text extent is set in the given `w` and `h` pointers. -If the optional parameter `font` is specified and valid, then it is used for the -text extent calculation, otherwise the currently selected font is used. +If the optional parameter `font` is specified and valid, then it is used for the text +extent calculation, otherwise the currently selected font is used. -If `string` is empty, its horizontal extent is 0 but, for convenience when using -this function for allocating enough space for a possibly multi-line string, its -vertical extent is the same as the height of an empty line of text. Please note -that this behaviour differs from that of `getTextExtent/3`. +If `string` is empty, its horizontal extent is 0 but, for convenience when using this +function for allocating enough space for a possibly multi-line string, its vertical extent +is the same as the height of an empty line of text. Please note that this behaviour +differs from that of `getTextExtent/3`. Note: This function works with both single-line and multi-line strings. -See: `m:wxFont`, `setFont/2`, `getPartialTextExtents/2`, `getTextExtent/3` +See: +* `m:wxFont` + +* `setFont/2` + +* `getPartialTextExtents/2` + +* `getTextExtent/3` """. -spec getMultiLineTextExtent(This, String, [Option]) -> {W::integer(), H::integer(), HeightLine::integer()} when This::wxDC(), String::unicode:chardata(), @@ -818,17 +784,18 @@ getMultiLineTextExtent(#wx_ref{type=ThisT}=This,String, Options) wxe_util:queue_cmd(This,String_UC, Opts,?get_env(),?wxDC_GetMultiLineTextExtent_4), wxe_util:rec(?wxDC_GetMultiLineTextExtent_4). -%% @doc See external documentation. -doc """ Fills the `widths` array with the widths from the beginning of `text` to the corresponding character of `text`. -The generic version simply builds a running total of the widths of each -character using `getTextExtent/3`, however if the various platforms have a -native API function that is faster or more accurate than the generic -implementation then it should be used instead. +The generic version simply builds a running total of the widths of each character using `getTextExtent/3`, +however if the various platforms have a native API function that is faster or more +accurate than the generic implementation then it should be used instead. -See: `getMultiLineTextExtent/3`, `getTextExtent/3` +See: +* `getMultiLineTextExtent/3` + +* `getTextExtent/3` """. -spec getPartialTextExtents(This, Text) -> Result when Result ::{Res ::boolean(), Widths::[integer()]}, @@ -840,7 +807,6 @@ getPartialTextExtents(#wx_ref{type=ThisT}=This,Text) wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxDC_GetPartialTextExtents), wxe_util:rec(?wxDC_GetPartialTextExtents). -%% @doc See external documentation. -doc """ Gets the current pen. @@ -853,17 +819,16 @@ getPen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetPen), wxe_util:rec(?wxDC_GetPen). -%% @doc See external documentation. -doc """ Gets in `colour` the colour at the specified location. -This method isn't available for `m:wxPostScriptDC` or `wxMetafileDC` (not -implemented in wx) nor for any DC in wxOSX port and simply returns false there. +This method isn't available for `m:wxPostScriptDC` or `wxMetafileDC` (not implemented in +wx) nor for any DC in wxOSX port and simply returns false there. Note: Setting a pixel can be done using `drawPoint/2`. -Note: This method shouldn't be used with `m:wxPaintDC` as accessing the DC while -drawing can result in unexpected results, notably in wxGTK. +Note: This method shouldn't be used with `m:wxPaintDC` as accessing the DC while drawing +can result in unexpected results, notably in wxGTK. """. -spec getPixel(This, Pos) -> Result when Result ::{Res ::boolean(), Colour::wx:wx_colour4()}, @@ -874,7 +839,6 @@ getPixel(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxDC_GetPixel), wxe_util:rec(?wxDC_GetPixel). -%% @doc See external documentation. -doc "Returns the resolution of the device in pixels per inch.". -spec getPPI(This) -> {W::integer(), H::integer()} when This::wxDC(). @@ -883,10 +847,9 @@ getPPI(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetPPI), wxe_util:rec(?wxDC_GetPPI). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec getSize(This) -> {W::integer(), H::integer()} when This::wxDC(). @@ -895,10 +858,9 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetSize), wxe_util:rec(?wxDC_GetSize). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec getSizeMM(This) -> {W::integer(), H::integer()} when This::wxDC(). @@ -907,7 +869,6 @@ getSizeMM(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetSizeMM), wxe_util:rec(?wxDC_GetSizeMM). -%% @doc See external documentation. -doc """ Gets the current text background colour. @@ -920,10 +881,9 @@ getTextBackground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetTextBackground), wxe_util:rec(?wxDC_GetTextBackground). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec getTextExtent(This, String) -> {W::integer(), H::integer()} when This::wxDC(), String::unicode:chardata(). @@ -934,27 +894,31 @@ getTextExtent(#wx_ref{type=ThisT}=This,String) wxe_util:queue_cmd(This,String_UC,?get_env(),?wxDC_GetTextExtent_1), wxe_util:rec(?wxDC_GetTextExtent_1). -%% @doc See external documentation. -doc """ Gets the dimensions of the string using the currently selected font. -`string` is the text string to measure, `descent` is the dimension from the -baseline of the font to the bottom of the descender, and `externalLeading` is -any extra vertical space added to the font by the font designer (usually is -zero). +`string` is the text string to measure, `descent` is the dimension from the baseline of +the font to the bottom of the descender, and `externalLeading` is any extra vertical space +added to the font by the font designer (usually is zero). -The text extent is returned in `w` and `h` pointers or as a \{Width,Height\} -object depending on which version of this function is used. +The text extent is returned in `w` and `h` pointers or as a {Width,Height} object +depending on which version of this function is used. -If the optional parameter `font` is specified and valid, then it is used for the -text extent calculation. Otherwise the currently selected font is. +If the optional parameter `font` is specified and valid, then it is used for the text +extent calculation. Otherwise the currently selected font is. If `string` is empty, its extent is 0 in both directions, as expected. Note: This function only works with single-line strings. -See: `m:wxFont`, `setFont/2`, `getPartialTextExtents/2`, -`getMultiLineTextExtent/3` +See: +* `m:wxFont` + +* `setFont/2` + +* `getPartialTextExtents/2` + +* `getMultiLineTextExtent/3` """. -spec getTextExtent(This, String, [Option]) -> Result when Result :: {W::integer(), H::integer(), Descent::integer(), ExternalLeading::integer()}, @@ -970,7 +934,6 @@ getTextExtent(#wx_ref{type=ThisT}=This,String, Options) wxe_util:queue_cmd(This,String_UC, Opts,?get_env(),?wxDC_GetTextExtent_4), wxe_util:rec(?wxDC_GetTextExtent_4). -%% @doc See external documentation. -doc """ Gets the current text foreground colour. @@ -983,7 +946,6 @@ getTextForeground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetTextForeground), wxe_util:rec(?wxDC_GetTextForeground). -%% @doc See external documentation. -doc """ Gets the current user scale factor. @@ -996,11 +958,9 @@ getUserScale(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_GetUserScale), wxe_util:rec(?wxDC_GetUserScale). -%% @doc See external documentation. -doc """ -Fill the area specified by rect with a radial gradient, starting from -`initialColour` at the centre of the circle and fading to `destColour` on the -circle outside. +Fill the area specified by rect with a radial gradient, starting from `initialColour` at +the centre of the circle and fading to `destColour` on the circle outside. The circle is placed at the centre of `rect`. @@ -1013,14 +973,11 @@ gradientFillConcentric(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,wxe_util:color(InitialColour),wxe_util:color(DestColour),?get_env(),?wxDC_GradientFillConcentric_3). -%% @doc See external documentation. -doc """ -Fill the area specified by rect with a radial gradient, starting from -`initialColour` at the centre of the circle and fading to `destColour` on the -circle outside. +Fill the area specified by rect with a radial gradient, starting from `initialColour` at +the centre of the circle and fading to `destColour` on the circle outside. -`circleCenter` are the relative coordinates of centre of the circle in the -specified `rect`. +`circleCenter` are the relative coordinates of centre of the circle in the specified `rect`. Note: Currently this function is very slow, don't use it for real-time drawing. """. @@ -1031,7 +988,7 @@ gradientFillConcentric(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,wxe_util:color(InitialColour),wxe_util:color(DestColour),CircleCenter,?get_env(),?wxDC_GradientFillConcentric_4). -%% @equiv gradientFillLinear(This,Rect,InitialColour,DestColour, []) +-doc(#{equiv => gradientFillLinear(This,Rect,InitialColour,DestColour, [])}). -spec gradientFillLinear(This, Rect, InitialColour, DestColour) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, InitialColour::wx:wx_colour(), DestColour::wx:wx_colour(). @@ -1039,16 +996,14 @@ gradientFillLinear(This,{RectX,RectY,RectW,RectH} = Rect,InitialColour,DestColou when is_record(This, wx_ref),is_integer(RectX),is_integer(RectY),is_integer(RectW),is_integer(RectH),?is_colordata(InitialColour),?is_colordata(DestColour) -> gradientFillLinear(This,Rect,InitialColour,DestColour, []). -%% @doc See external documentation. -%%
NDirection = ?wxLEFT | ?wxRIGHT | ?wxUP | ?wxDOWN | ?wxTOP | ?wxBOTTOM | ?wxNORTH | ?wxSOUTH | ?wxWEST | ?wxEAST | ?wxALL | ?wxDIRECTION_MASK -doc """ -Fill the area specified by `rect` with a linear gradient, starting from -`initialColour` and eventually fading to `destColour`. +Fill the area specified by `rect` with a linear gradient, starting from `initialColour` +and eventually fading to `destColour`. -The `nDirection` specifies the direction of the colour change, default is to use -`initialColour` on the left part of the rectangle and `destColour` on the right -one. +The `nDirection` specifies the direction of the colour change, default is to use `initialColour` +on the left part of the rectangle and `destColour` on the right one. """. +%% NDirection = ?wxLEFT | ?wxRIGHT | ?wxUP | ?wxDOWN | ?wxTOP | ?wxBOTTOM | ?wxNORTH | ?wxSOUTH | ?wxWEST | ?wxEAST | ?wxALL | ?wxDIRECTION_MASK -spec gradientFillLinear(This, Rect, InitialColour, DestColour, [Option]) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, InitialColour::wx:wx_colour(), DestColour::wx:wx_colour(), Option :: {'nDirection', wx:wx_enum()}. @@ -1060,10 +1015,9 @@ gradientFillLinear(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect,Ini Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Rect,wxe_util:color(InitialColour),wxe_util:color(DestColour), Opts,?get_env(),?wxDC_GradientFillLinear). -%% @doc See external documentation. -doc """ -Converts logical X coordinate to device coordinate, using the current mapping -mode, user scale factor, device origin and axis orientation. +Converts logical X coordinate to device coordinate, using the current mapping mode, user +scale factor, device origin and axis orientation. """. -spec logicalToDeviceX(This, X) -> integer() when This::wxDC(), X::integer(). @@ -1073,10 +1027,9 @@ logicalToDeviceX(#wx_ref{type=ThisT}=This,X) wxe_util:queue_cmd(This,X,?get_env(),?wxDC_LogicalToDeviceX), wxe_util:rec(?wxDC_LogicalToDeviceX). -%% @doc See external documentation. -doc """ -Converts logical X coordinate to relative device coordinate, using the current -mapping mode and user scale factor but ignoring the axis orientation. +Converts logical X coordinate to relative device coordinate, using the current mapping +mode and user scale factor but ignoring the axis orientation. Use this for converting a width, for example. """. @@ -1088,10 +1041,9 @@ logicalToDeviceXRel(#wx_ref{type=ThisT}=This,X) wxe_util:queue_cmd(This,X,?get_env(),?wxDC_LogicalToDeviceXRel), wxe_util:rec(?wxDC_LogicalToDeviceXRel). -%% @doc See external documentation. -doc """ -Converts logical Y coordinate to device coordinate, using the current mapping -mode, user scale factor, device origin and axis orientation. +Converts logical Y coordinate to device coordinate, using the current mapping mode, user +scale factor, device origin and axis orientation. """. -spec logicalToDeviceY(This, Y) -> integer() when This::wxDC(), Y::integer(). @@ -1101,10 +1053,9 @@ logicalToDeviceY(#wx_ref{type=ThisT}=This,Y) wxe_util:queue_cmd(This,Y,?get_env(),?wxDC_LogicalToDeviceY), wxe_util:rec(?wxDC_LogicalToDeviceY). -%% @doc See external documentation. -doc """ -Converts logical Y coordinate to relative device coordinate, using the current -mapping mode and user scale factor but ignoring the axis orientation. +Converts logical Y coordinate to relative device coordinate, using the current mapping +mode and user scale factor but ignoring the axis orientation. Use this for converting a height, for example. """. @@ -1116,7 +1067,6 @@ logicalToDeviceYRel(#wx_ref{type=ThisT}=This,Y) wxe_util:queue_cmd(This,Y,?get_env(),?wxDC_LogicalToDeviceYRel), wxe_util:rec(?wxDC_LogicalToDeviceYRel). -%% @doc See external documentation. -doc "Gets the maximum horizontal extent used in drawing commands so far.". -spec maxX(This) -> integer() when This::wxDC(). @@ -1125,7 +1075,6 @@ maxX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_MaxX), wxe_util:rec(?wxDC_MaxX). -%% @doc See external documentation. -doc "Gets the maximum vertical extent used in drawing commands so far.". -spec maxY(This) -> integer() when This::wxDC(). @@ -1134,7 +1083,6 @@ maxY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_MaxY), wxe_util:rec(?wxDC_MaxY). -%% @doc See external documentation. -doc "Gets the minimum horizontal extent used in drawing commands so far.". -spec minX(This) -> integer() when This::wxDC(). @@ -1143,7 +1091,6 @@ minX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_MinX), wxe_util:rec(?wxDC_MinX). -%% @doc See external documentation. -doc "Gets the minimum vertical extent used in drawing commands so far.". -spec minY(This) -> integer() when This::wxDC(). @@ -1152,7 +1099,6 @@ minY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_MinY), wxe_util:rec(?wxDC_MinY). -%% @doc See external documentation. -doc "Returns true if the DC is ok to use.". -spec isOk(This) -> boolean() when This::wxDC(). @@ -1161,10 +1107,9 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDC_IsOk), wxe_util:rec(?wxDC_IsOk). -%% @doc See external documentation. -doc """ -Resets the bounding box: after a call to this function, the bounding box doesn't -contain anything. +Resets the bounding box: after a call to this function, the bounding box doesn't contain +anything. See: `calcBoundingBox/3` """. @@ -1174,10 +1119,9 @@ resetBoundingBox(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,?get_env(),?wxDC_ResetBoundingBox). -%% @doc See external documentation. -doc """ -Sets the x and y axis orientation (i.e. the direction from lowest to highest -values on the axis). +Sets the x and y axis orientation (i.e. the direction from lowest to highest values on +the axis). The default orientation is x axis from left to right and y axis from top down. """. @@ -1188,7 +1132,6 @@ setAxisOrientation(#wx_ref{type=ThisT}=This,XLeftRight,YBottomUp) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,XLeftRight,YBottomUp,?get_env(),?wxDC_SetAxisOrientation). -%% @doc See external documentation. -doc "Sets the current background brush for the DC.". -spec setBackground(This, Brush) -> 'ok' when This::wxDC(), Brush::wxBrush:wxBrush(). @@ -1197,12 +1140,10 @@ setBackground(#wx_ref{type=ThisT}=This,#wx_ref{type=BrushT}=Brush) -> ?CLASS(BrushT,wxBrush), wxe_util:queue_cmd(This,Brush,?get_env(),?wxDC_SetBackground). -%% @doc See external documentation. -doc """ -`mode` may be one of `wxPENSTYLE_SOLID` and `wxPENSTYLE_TRANSPARENT`. +`mode` may be one of `wxPENSTYLE\_SOLID` and `wxPENSTYLE\_TRANSPARENT`. -This setting determines whether text will be drawn with a background colour or -not. +This setting determines whether text will be drawn with a background colour or not. """. -spec setBackgroundMode(This, Mode) -> 'ok' when This::wxDC(), Mode::integer(). @@ -1211,17 +1152,17 @@ setBackgroundMode(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Mode,?get_env(),?wxDC_SetBackgroundMode). -%% @doc See external documentation. -doc """ Sets the current brush for the DC. -If the argument is ?wxNullBrush (or another invalid brush; see -`wxBrush:isOk/1`), the current brush is selected out of the device context -(leaving `m:wxDC` without any valid brush), allowing the current brush to be -destroyed safely. +If the argument is ?wxNullBrush (or another invalid brush; see `wxBrush:isOk/1`), the current brush is +selected out of the device context (leaving `m:wxDC` without any valid brush), allowing +the current brush to be destroyed safely. + +See: +* `m:wxBrush` -See: `m:wxBrush`, `m:wxMemoryDC`, (for the interpretation of colours when -drawing into a monochrome bitmap) +* `m:wxMemoryDC` """. -spec setBrush(This, Brush) -> 'ok' when This::wxDC(), Brush::wxBrush:wxBrush(). @@ -1230,10 +1171,9 @@ setBrush(#wx_ref{type=ThisT}=This,#wx_ref{type=BrushT}=Brush) -> ?CLASS(BrushT,wxBrush), wxe_util:queue_cmd(This,Brush,?get_env(),?wxDC_SetBrush). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setClippingRegion(This, Rect) -> 'ok' when This::wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -1242,10 +1182,9 @@ setClippingRegion(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Rect,?get_env(),?wxDC_SetClippingRegion_1). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setClippingRegion(This, Pt, Sz) -> 'ok' when This::wxDC(), Pt::{X::integer(), Y::integer()}, Sz::{W::integer(), H::integer()}. @@ -1254,13 +1193,11 @@ setClippingRegion(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt,{SzW,SzH} = Sz) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Pt,Sz,?get_env(),?wxDC_SetClippingRegion_2). -%% @doc See external documentation. -doc """ -Sets the device origin (i.e. the origin in pixels after scaling has been -applied). +Sets the device origin (i.e. the origin in pixels after scaling has been applied). -This function may be useful in Windows printing operations for placing a graphic -on a page. +This function may be useful in Windows printing operations for placing a graphic on a +page. """. -spec setDeviceOrigin(This, X, Y) -> 'ok' when This::wxDC(), X::integer(), Y::integer(). @@ -1269,13 +1206,12 @@ setDeviceOrigin(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxDC_SetDeviceOrigin). -%% @doc See external documentation. -doc """ Sets the current font for the DC. -If the argument is ?wxNullFont (or another invalid font; see `wxFont:isOk/1`), -the current font is selected out of the device context (leaving `m:wxDC` without -any valid font), allowing the current font to be destroyed safely. +If the argument is ?wxNullFont (or another invalid font; see `wxFont:isOk/1`), the current font is +selected out of the device context (leaving `m:wxDC` without any valid font), allowing the +current font to be destroyed safely. See: `m:wxFont` """. @@ -1286,13 +1222,12 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxDC_SetFont). -%% @doc See external documentation. -%%
Dir = ?wxLayout_Default | ?wxLayout_LeftToRight | ?wxLayout_RightToLeft -doc """ Sets the current layout direction for the device context. See: `getLayoutDirection/1` """. +%% Dir = ?wxLayout_Default | ?wxLayout_LeftToRight | ?wxLayout_RightToLeft -spec setLayoutDirection(This, Dir) -> 'ok' when This::wxDC(), Dir::wx:wx_enum(). setLayoutDirection(#wx_ref{type=ThisT}=This,Dir) @@ -1300,27 +1235,25 @@ setLayoutDirection(#wx_ref{type=ThisT}=This,Dir) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Dir,?get_env(),?wxDC_SetLayoutDirection). -%% @doc See external documentation. -%%
Function = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -doc """ Sets the current logical function for the device context. -Note: This function is not fully supported in all ports, due to the limitations -of the underlying drawing model. Notably, `wxINVERT` which was commonly used for -drawing rubber bands or other moving outlines in the past, is not, and will not, -be supported by wxGTK3 and wxMac. The suggested alternative is to draw -temporarily objects normally and refresh the (affected part of the) window to -remove them later. +Note: This function is not fully supported in all ports, due to the limitations of the +underlying drawing model. Notably, `wxINVERT` which was commonly used for drawing rubber +bands or other moving outlines in the past, is not, and will not, be supported by wxGTK3 +and wxMac. The suggested alternative is to draw temporarily objects normally and refresh +the (affected part of the) window to remove them later. -It determines how a `source` pixel (from a pen or brush colour, or source device -context if using `blit/6`) combines with a `destination` pixel in the current -device context. Text drawing is not affected by this function. +It determines how a `source` pixel (from a pen or brush colour, or source device context +if using `blit/6`) combines with a `destination` pixel in the current device context. Text drawing +is not affected by this function. See ?wxRasterOperationMode enumeration values for more info. -The default is `wxCOPY`, which simply draws with the current colour. The others -combine the current colour and the background using a logical operation. +The default is `wxCOPY`, which simply draws with the current colour. The others combine +the current colour and the background using a logical operation. """. +%% Function = ?wxCLEAR | ?wxXOR | ?wxINVERT | ?wxOR_REVERSE | ?wxAND_REVERSE | ?wxCOPY | ?wxAND | ?wxAND_INVERT | ?wxNO_OP | ?wxNOR | ?wxEQUIV | ?wxSRC_INVERT | ?wxOR_INVERT | ?wxNAND | ?wxOR | ?wxSET -spec setLogicalFunction(This, Function) -> 'ok' when This::wxDC(), Function::wx:wx_enum(). setLogicalFunction(#wx_ref{type=ThisT}=This,Function) @@ -1328,23 +1261,21 @@ setLogicalFunction(#wx_ref{type=ThisT}=This,Function) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Function,?get_env(),?wxDC_SetLogicalFunction). -%% @doc See external documentation. -%%
Mode = ?wxMM_TEXT | ?wxMM_METRIC | ?wxMM_LOMETRIC | ?wxMM_TWIPS | ?wxMM_POINTS -doc """ -The mapping mode of the device context defines the unit of measurement used to -convert `logical` units to `device` units. +The mapping mode of the device context defines the unit of measurement used to convert `logical` +units to `device` units. -Note that in X, text drawing isn't handled consistently with the mapping mode; a -font is always specified in point size. However, setting the user scale (see -`setUserScale/3`) scales the text appropriately. In Windows, scalable TrueType -fonts are always used; in X, results depend on availability of fonts, but -usually a reasonable match is found. +Note that in X, text drawing isn't handled consistently with the mapping mode; a font is +always specified in point size. However, setting the user scale (see `setUserScale/3`) scales the text +appropriately. In Windows, scalable TrueType fonts are always used; in X, results depend +on availability of fonts, but usually a reasonable match is found. The coordinate origin is always at the top left of the screen/printer. -Drawing to a Windows printer device context uses the current mapping mode, but -mapping mode is currently ignored for PostScript output. +Drawing to a Windows printer device context uses the current mapping mode, but mapping +mode is currently ignored for PostScript output. """. +%% Mode = ?wxMM_TEXT | ?wxMM_METRIC | ?wxMM_LOMETRIC | ?wxMM_TWIPS | ?wxMM_POINTS -spec setMapMode(This, Mode) -> 'ok' when This::wxDC(), Mode::wx:wx_enum(). setMapMode(#wx_ref{type=ThisT}=This,Mode) @@ -1352,13 +1283,12 @@ setMapMode(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,Mode,?get_env(),?wxDC_SetMapMode). -%% @doc See external documentation. -doc """ -If this is a window DC or memory DC, assigns the given palette to the window or -bitmap associated with the DC. +If this is a window DC or memory DC, assigns the given palette to the window or bitmap +associated with the DC. -If the argument is ?wxNullPalette, the current palette is selected out of the -device context, and the original palette restored. +If the argument is ?wxNullPalette, the current palette is selected out of the device +context, and the original palette restored. See: `m:wxPalette` """. @@ -1369,16 +1299,14 @@ setPalette(#wx_ref{type=ThisT}=This,#wx_ref{type=PaletteT}=Palette) -> ?CLASS(PaletteT,wxPalette), wxe_util:queue_cmd(This,Palette,?get_env(),?wxDC_SetPalette). -%% @doc See external documentation. -doc """ Sets the current pen for the DC. -If the argument is ?wxNullPen (or another invalid pen; see `wxPen:isOk/1`), the -current pen is selected out of the device context (leaving `m:wxDC` without any -valid pen), allowing the current pen to be destroyed safely. +If the argument is ?wxNullPen (or another invalid pen; see `wxPen:isOk/1`), the current pen is selected +out of the device context (leaving `m:wxDC` without any valid pen), allowing the current +pen to be destroyed safely. -See: `m:wxMemoryDC`, for the interpretation of colours when drawing into a -monochrome bitmap +See: `m:wxMemoryDC` """. -spec setPen(This, Pen) -> 'ok' when This::wxDC(), Pen::wxPen:wxPen(). @@ -1387,7 +1315,6 @@ setPen(#wx_ref{type=ThisT}=This,#wx_ref{type=PenT}=Pen) -> ?CLASS(PenT,wxPen), wxe_util:queue_cmd(This,Pen,?get_env(),?wxDC_SetPen). -%% @doc See external documentation. -doc "Sets the current text background colour for the DC.". -spec setTextBackground(This, Colour) -> 'ok' when This::wxDC(), Colour::wx:wx_colour(). @@ -1396,12 +1323,10 @@ setTextBackground(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxDC_SetTextBackground). -%% @doc See external documentation. -doc """ Sets the current text foreground colour for the DC. -See: `m:wxMemoryDC`, for the interpretation of colours when drawing into a -monochrome bitmap +See: `m:wxMemoryDC` """. -spec setTextForeground(This, Colour) -> 'ok' when This::wxDC(), Colour::wx:wx_colour(). @@ -1410,7 +1335,6 @@ setTextForeground(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxDC_SetTextForeground). -%% @doc See external documentation. -doc "Sets the user scaling factor, useful for applications which require 'zooming'.". -spec setUserScale(This, XScale, YScale) -> 'ok' when This::wxDC(), XScale::number(), YScale::number(). @@ -1419,7 +1343,6 @@ setUserScale(#wx_ref{type=ThisT}=This,XScale,YScale) ?CLASS(ThisT,wxDC), wxe_util:queue_cmd(This,XScale,YScale,?get_env(),?wxDC_SetUserScale). -%% @doc See external documentation. -doc """ Starts a document (only relevant when outputting to a printer). @@ -1434,7 +1357,6 @@ startDoc(#wx_ref{type=ThisT}=This,Message) wxe_util:queue_cmd(This,Message_UC,?get_env(),?wxDC_StartDoc), wxe_util:rec(?wxDC_StartDoc). -%% @doc See external documentation. -doc "Starts a document page (only relevant when outputting to a printer).". -spec startPage(This) -> 'ok' when This::wxDC(). diff --git a/lib/wx/src/gen/wxDCOverlay.erl b/lib/wx/src/gen/wxDCOverlay.erl index 060c06836cd1..6a6468cf85de 100644 --- a/lib/wx/src/gen/wxDCOverlay.erl +++ b/lib/wx/src/gen/wxDCOverlay.erl @@ -20,14 +20,14 @@ -module(wxDCOverlay). -moduledoc """ -Functions for wxDCOverlay class - Connects an overlay with a drawing DC. -See: `m:wxOverlay`, `m:wxDC` +See: +* `m:wxOverlay` + +* `m:wxDC` -wxWidgets docs: -[wxDCOverlay](https://docs.wxwidgets.org/3.1/classwx_d_c_overlay.html) +wxWidgets docs: [wxDCOverlay](https://docs.wxwidgets.org/3.2/classwx_d_c_overlay.html) """. -include("wxe.hrl"). -export([clear/1,destroy/1,new/2,new/6]). @@ -37,11 +37,9 @@ wxWidgets docs: -type wxDCOverlay() :: wx:wx_object(). -export_type([wxDCOverlay/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Convenience wrapper that behaves the same using the entire area of the dc.". -spec new(Overlay, Dc) -> wxDCOverlay() when Overlay::wxOverlay:wxOverlay(), Dc::wxDC:wxDC(). @@ -51,10 +49,9 @@ new(#wx_ref{type=OverlayT}=Overlay,#wx_ref{type=DcT}=Dc) -> wxe_util:queue_cmd(Overlay,Dc,?get_env(),?wxDCOverlay_new_2), wxe_util:rec(?wxDCOverlay_new_2). -%% @doc See external documentation. -doc """ -Connects this overlay to the corresponding drawing dc, if the overlay is not -initialized yet this call will do so. +Connects this overlay to the corresponding drawing dc, if the overlay is not initialized +yet this call will do so. """. -spec new(Overlay, Dc, X, Y, Width, Height) -> wxDCOverlay() when Overlay::wxOverlay:wxOverlay(), Dc::wxDC:wxDC(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -65,7 +62,6 @@ new(#wx_ref{type=OverlayT}=Overlay,#wx_ref{type=DcT}=Dc,X,Y,Width,Height) wxe_util:queue_cmd(Overlay,Dc,X,Y,Width,Height,?get_env(),?wxDCOverlay_new_6), wxe_util:rec(?wxDCOverlay_new_6). -%% @doc See external documentation. -doc "Clears the layer, restoring the state at the last init.". -spec clear(This) -> 'ok' when This::wxDCOverlay(). @@ -73,8 +69,7 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxDCOverlay), wxe_util:queue_cmd(This,?get_env(),?wxDCOverlay_Clear). -%% @doc Destroys this object, do not use object again --doc "Removes the connection between the overlay and the dc.". +-doc "Destroys the object". -spec destroy(This::wxDCOverlay()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDCOverlay), diff --git a/lib/wx/src/gen/wxDataObject.erl b/lib/wx/src/gen/wxDataObject.erl index 8cec28569a72..16f5bd919d85 100644 --- a/lib/wx/src/gen/wxDataObject.erl +++ b/lib/wx/src/gen/wxDataObject.erl @@ -20,84 +20,78 @@ -module(wxDataObject). -moduledoc """ -Functions for wxDataObject class +A `m:wxDataObject` represents data that can be copied to or from the clipboard, or +dragged and dropped. -A `m:wxDataObject` represents data that can be copied to or from the clipboard, -or dragged and dropped. The important thing about `m:wxDataObject` is that this -is a 'smart' piece of data unlike 'dumb' data containers such as memory buffers -or files. Being 'smart' here means that the data object itself should know what -data formats it supports and how to render itself in each of its supported -formats. +The important thing about `m:wxDataObject` is that this is a 'smart' piece of data unlike +'dumb' data containers such as memory buffers or files. Being 'smart' here means that the +data object itself should know what data formats it supports and how to render itself in +each of its supported formats. A supported format, incidentally, is exactly the format in which the data can be -requested from a data object or from which the data object may be set. In the -general case, an object may support different formats on 'input' and 'output', -i.e. it may be able to render itself in a given format but not be created from -data on this format or vice versa. `m:wxDataObject` defines the -`wxDataObject::Direction` (not implemented in wx) enumeration type which -distinguishes between them. +requested from a data object or from which the data object may be set. In the general +case, an object may support different formats on 'input' and 'output', i.e. it may be able +to render itself in a given format but not be created from data on this format or vice +versa. `m:wxDataObject` defines the `wxDataObject::Direction` (not implemented in wx) +enumeration type which distinguishes between them. See `wxDataFormat` (not implemented in wx) documentation for more about formats. -Not surprisingly, being 'smart' comes at a price of added complexity. This is -reasonable for the situations when you really need to support multiple formats, -but may be annoying if you only want to do something simple like cut and paste -text. - -To provide a solution for both cases, wxWidgets has two predefined classes which -derive from `m:wxDataObject`: `wxDataObjectSimple` (not implemented in wx) and -`wxDataObjectComposite` (not implemented in wx). `wxDataObjectSimple` (not -implemented in wx) is the simplest `m:wxDataObject` possible and only holds data -in a single format (such as HTML or text) and `wxDataObjectComposite` (not -implemented in wx) is the simplest way to implement a `m:wxDataObject` that does -support multiple formats because it achieves this by simply holding several -`wxDataObjectSimple` (not implemented in wx) objects. - -So, you have several solutions when you need a `m:wxDataObject` class (and you -need one as soon as you want to transfer data via the clipboard or drag and -drop): - -Please note that the easiest way to use drag and drop and the clipboard with -multiple formats is by using `wxDataObjectComposite` (not implemented in wx), -but it is not the most efficient one as each `wxDataObjectSimple` (not -implemented in wx) would contain the whole data in its respective formats. Now -imagine that you want to paste 200 pages of text in your proprietary format, as -well as Word, RTF, HTML, Unicode and plain text to the clipboard and even -today's computers are in trouble. For this case, you will have to derive from -`m:wxDataObject` directly and make it enumerate its formats and provide the data -in the requested format on demand. - -Note that neither the GTK+ data transfer mechanisms for clipboard and drag and -drop, nor OLE data transfer, `copies` any data until another application -actually requests the data. This is in contrast to the 'feel' offered to the -user of a program who would normally think that the data resides in the -clipboard after having pressed 'Copy' - in reality it is only declared to be -`available`. +Not surprisingly, being 'smart' comes at a price of added complexity. This is reasonable +for the situations when you really need to support multiple formats, but may be annoying +if you only want to do something simple like cut and paste text. + +To provide a solution for both cases, wxWidgets has two predefined classes which derive +from `m:wxDataObject`: `wxDataObjectSimple` (not implemented in wx) and `wxDataObjectComposite` +(not implemented in wx). `wxDataObjectSimple` (not implemented in wx) is the simplest `m:wxDataObject` +possible and only holds data in a single format (such as HTML or text) and `wxDataObjectComposite` +(not implemented in wx) is the simplest way to implement a `m:wxDataObject` that does +support multiple formats because it achieves this by simply holding several `wxDataObjectSimple` +(not implemented in wx) objects. + +So, you have several solutions when you need a `m:wxDataObject` class (and you need one +as soon as you want to transfer data via the clipboard or drag and drop): + +Please note that the easiest way to use drag and drop and the clipboard with multiple +formats is by using `wxDataObjectComposite` (not implemented in wx), but it is not the +most efficient one as each `wxDataObjectSimple` (not implemented in wx) would contain the +whole data in its respective formats. Now imagine that you want to paste 200 pages of text +in your proprietary format, as well as Word, RTF, HTML, Unicode and plain text to the +clipboard and even today's computers are in trouble. For this case, you will have to +derive from `m:wxDataObject` directly and make it enumerate its formats and provide the +data in the requested format on demand. + +Note that neither the GTK+ data transfer mechanisms for clipboard and drag and drop, nor +OLE data transfer, `copies` any data until another application actually requests the data. +This is in contrast to the 'feel' offered to the user of a program who would normally +think that the data resides in the clipboard after having pressed 'Copy' - in reality it +is only declared to be `available`. You may also derive your own data object classes from `wxCustomDataObject` (not -implemented in wx) for user-defined types. The format of user-defined data is -given as a mime-type string literal, such as "application/word" or "image/png". -These strings are used as they are under Unix (so far only GTK+) to identify a -format and are translated into their Windows equivalent under Win32 (using the -OLE IDataObject for data exchange to and from the clipboard and for drag and -drop). Note that the format string translation under Windows is not yet -finished. - -Each class derived directly from `m:wxDataObject` must override and implement -all of its functions which are pure virtual in the base class. The data objects -which only render their data or only set it (i.e. work in only one direction), -should return 0 from `GetFormatCount()` (not implemented in wx). +implemented in wx) for user-defined types. The format of user-defined data is given as a +mime-type string literal, such as "application/word" or "image/png". These strings are +used as they are under Unix (so far only GTK+) to identify a format and are translated +into their Windows equivalent under Win32 (using the OLE IDataObject for data exchange to +and from the clipboard and for drag and drop). Note that the format string translation +under Windows is not yet finished. + +Each class derived directly from `m:wxDataObject` must override and implement all of its +functions which are pure virtual in the base class. The data objects which only render +their data or only set it (i.e. work in only one direction), should return 0 from `GetFormatCount()` +(not implemented in wx). See: -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd), -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_dnd), -`m:wxFileDataObject`, `m:wxTextDataObject`, `m:wxBitmapDataObject`, -`wxCustomDataObject` (not implemented in wx), `wxDropTarget` (not implemented in -wx), `wxDropSource` (not implemented in wx), `wxTextDropTarget` (not implemented -in wx), `wxFileDropTarget` (not implemented in wx) - -wxWidgets docs: -[wxDataObject](https://docs.wxwidgets.org/3.1/classwx_data_object.html) +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_dnd) + +* `m:wxFileDataObject` + +* `m:wxTextDataObject` + +* `m:wxBitmapDataObject` + +wxWidgets docs: [wxDataObject](https://docs.wxwidgets.org/3.2/classwx_data_object.html) """. -include("wxe.hrl"). -export([]). @@ -107,7 +101,6 @@ wxWidgets docs: -type wxDataObject() :: wx:wx_object(). -export_type([wxDataObject/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). diff --git a/lib/wx/src/gen/wxDateEvent.erl b/lib/wx/src/gen/wxDateEvent.erl index c5ab99f55540..638a5f6bfaa0 100644 --- a/lib/wx/src/gen/wxDateEvent.erl +++ b/lib/wx/src/gen/wxDateEvent.erl @@ -20,16 +20,17 @@ -module(wxDateEvent). -moduledoc """ -Functions for wxDateEvent class +This event class holds information about a date change and is used together with `m:wxDatePickerCtrl`. -This event class holds information about a date change and is used together with -`m:wxDatePickerCtrl`. It also serves as a base class for `m:wxCalendarEvent`. +It also serves as a base class for `m:wxCalendarEvent`. -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxDateEvent](https://docs.wxwidgets.org/3.1/classwx_date_event.html) +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxDateEvent](https://docs.wxwidgets.org/3.2/classwx_date_event.html) """. -include("wxe.hrl"). -export([getDate/1]). @@ -44,13 +45,11 @@ wxWidgets docs: -include("wx.hrl"). -type wxDateEventType() :: 'date_changed'. -export_type([wxDateEvent/0, wxDate/0, wxDateEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Returns the date.". -spec getDate(This) -> wx:wx_datetime() when This::wxDateEvent(). @@ -60,58 +59,40 @@ getDate(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxDateEvent_GetDate). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxDatePickerCtrl.erl b/lib/wx/src/gen/wxDatePickerCtrl.erl index ae2bffc42fd7..46ba30873689 100644 --- a/lib/wx/src/gen/wxDatePickerCtrl.erl +++ b/lib/wx/src/gen/wxDatePickerCtrl.erl @@ -20,32 +20,63 @@ -module(wxDatePickerCtrl). -moduledoc """ -Functions for wxDatePickerCtrl class +This control allows the user to select a date. -This control allows the user to select a date. Unlike `m:wxCalendarCtrl`, which -is a relatively big control, `m:wxDatePickerCtrl` is implemented as a small -window showing the currently selected date. The control can be edited using the -keyboard, and can also display a popup window for more user-friendly date +Unlike `m:wxCalendarCtrl`, which is a relatively big control, `m:wxDatePickerCtrl` is +implemented as a small window showing the currently selected date. The control can be +edited using the keyboard, and can also display a popup window for more user-friendly date selection, depending on the styles used and the platform. It is only available if `wxUSE_DATEPICKCTRL` is set to 1. -Styles +## Styles This class supports the following styles: -See: `wxTimePickerCtrl` (not implemented in wx), `m:wxCalendarCtrl`, -`m:wxDateEvent` +* wxDP_SPIN: Creates a control without a month calendar drop down but with +spin-control-like arrows to change individual date components. This style is not supported +by the generic version. -This class is derived (and can use functions) from: `m:wxPickerBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* wxDP_DROPDOWN: Creates a control with a month calendar drop-down part from which the user +can select a date. This style is not supported in OSX/Cocoa native version. -wxWidgets docs: -[wxDatePickerCtrl](https://docs.wxwidgets.org/3.1/classwx_date_picker_ctrl.html) +* wxDP_DEFAULT: Creates a control with the style that is best supported for the current +platform (currently wxDP_SPIN under Windows and OSX/Cocoa and wxDP_DROPDOWN elsewhere). + +* wxDP_ALLOWNONE: With this style, the control allows the user to not enter any valid date +at all. Without it - the default - the control always has some valid date. This style is +not supported in OSX/Cocoa native version. + +* wxDP_SHOWCENTURY: Forces display of the century in the default date format. Without this +style the century could be displayed, or not, depending on the default date representation +in the system. This style is not supported in OSX/Cocoa native version currently. As can +be seen from the remarks above, most of the control style are only supported in the native +MSW implementation. In portable code it's recommended to use `wxDP_DEFAULT` style only, +possibly combined with `wxDP_SHOWCENTURY` (this is also the style used by default if none +is specified). + +See: +* `m:wxCalendarCtrl` + +* `m:wxDateEvent` + +This class is derived, and can use functions, from: + +* `m:wxPickerBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxDatePickerCtrl](https://docs.wxwidgets.org/3.2/classwx_date_picker_ctrl.html) ## Events -Event types emitted from this class: [`date_changed`](`m:wxDateEvent`) +Event types emitted from this class: + +* [`date_changed`](`m:wxDateEvent`) """. -include("wxe.hrl"). -export([destroy/1,getRange/3,getValue/1,new/0,new/2,new/3,setRange/3,setValue/2]). @@ -95,7 +126,6 @@ Event types emitted from this class: [`date_changed`](`m:wxDateEvent`) -type wxDatePickerCtrl() :: wx:wx_object(). -export_type([wxDatePickerCtrl/0]). -%% @hidden -doc false. parent_class(wxPickerBase) -> true; parent_class(wxControl) -> true; @@ -103,14 +133,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxDatePickerCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxDatePickerCtrl_new_0), wxe_util:rec(?wxDatePickerCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxDatePickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -118,7 +147,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc """ Initializes the object and calls `Create()` (not implemented in wx) with all the parameters. @@ -143,20 +171,17 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxDatePickerCtrl_new_3), wxe_util:rec(?wxDatePickerCtrl_new_3). -%% @doc See external documentation. -doc """ -If the control had been previously limited to a range of dates using -`setRange/3`, returns the lower and upper bounds of this range. +If the control had been previously limited to a range of dates using `setRange/3`, +returns the lower and upper bounds of this range. -If no range is set (or only one of the bounds is set), `dt1` and/or `dt2` are -set to be invalid. +If no range is set (or only one of the bounds is set), `dt1` and/or `dt2` are set to be invalid. -Notice that when using a native MSW implementation of this control the lower -range is always set, even if `setRange/3` hadn't been called explicitly, as the -native control only supports dates later than year 1601. +Notice that when using a native MSW implementation of this control the lower range is +always set, even if `setRange/3` hadn't been called explicitly, as the native control only supports +dates later than year 1601. -Return: false if no range limits are currently set, true if at least one bound -is set. +Return: false if no range limits are currently set, true if at least one bound is set. """. -spec getRange(This, Dt1, Dt2) -> boolean() when This::wxDatePickerCtrl(), Dt1::wx:wx_datetime(), Dt2::wx:wx_datetime(). @@ -166,12 +191,11 @@ getRange(#wx_ref{type=ThisT}=This,{{Dt1Y,Dt1Mo,Dt1D},{Dt1H,Dt1Mi,Dt1S}},{{Dt2Y,D wxe_util:queue_cmd(This,{Dt1D,Dt1Mo,Dt1Y,Dt1H,Dt1Mi,Dt1S},{Dt2D,Dt2Mo,Dt2Y,Dt2H,Dt2Mi,Dt2S},?get_env(),?wxDatePickerCtrl_GetRange), wxe_util:rec(?wxDatePickerCtrl_GetRange). -%% @doc See external documentation. -doc """ Returns the currently entered date. -For a control with `wxDP_ALLOWNONE` style the returned value may be invalid if -no date is entered, otherwise it is always valid. +For a control with `wxDP_ALLOWNONE` style the returned value may be invalid if no date is +entered, otherwise it is always valid. """. -spec getValue(This) -> wx:wx_datetime() when This::wxDatePickerCtrl(). @@ -180,19 +204,18 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDatePickerCtrl_GetValue), wxe_util:rec(?wxDatePickerCtrl_GetValue). -%% @doc See external documentation. -doc """ Sets the valid range for the date selection. -If `dt1` is valid, it becomes the earliest date (inclusive) accepted by the -control. If `dt2` is valid, it becomes the latest possible date. +If `dt1` is valid, it becomes the earliest date (inclusive) accepted by the control. If `dt2` +is valid, it becomes the latest possible date. -Notice that if the current value is not inside the new range, it will be -adjusted to lie inside it, i.e. calling this method can change the control -value, however no events are generated by it. +Notice that if the current value is not inside the new range, it will be adjusted to lie +inside it, i.e. calling this method can change the control value, however no events are +generated by it. -Remark: If the current value of the control is outside of the newly set range -bounds, the behaviour is undefined. +Remark: If the current value of the control is outside of the newly set range bounds, the +behaviour is undefined. """. -spec setRange(This, Dt1, Dt2) -> 'ok' when This::wxDatePickerCtrl(), Dt1::wx:wx_datetime(), Dt2::wx:wx_datetime(). @@ -201,12 +224,11 @@ setRange(#wx_ref{type=ThisT}=This,{{Dt1Y,Dt1Mo,Dt1D},{Dt1H,Dt1Mi,Dt1S}},{{Dt2Y,D ?CLASS(ThisT,wxDatePickerCtrl), wxe_util:queue_cmd(This,{Dt1D,Dt1Mo,Dt1Y,Dt1H,Dt1Mi,Dt1S},{Dt2D,Dt2Mo,Dt2Y,Dt2H,Dt2Mi,Dt2S},?get_env(),?wxDatePickerCtrl_SetRange). -%% @doc See external documentation. -doc """ Changes the current value of the control. -The date should be valid unless the control was created with `wxDP_ALLOWNONE` -style and included in the currently selected range, if any. +The date should be valid unless the control was created with `wxDP_ALLOWNONE` style and +included in the currently selected range, if any. Calling this method does not result in a date change event. """. @@ -217,605 +239,407 @@ setValue(#wx_ref{type=ThisT}=This,{{DtY,DtMo,DtD},{DtH,DtMi,DtS}}) ?CLASS(ThisT,wxDatePickerCtrl), wxe_util:queue_cmd(This,{DtD,DtMo,DtY,DtH,DtMi,DtS},?get_env(),?wxDatePickerCtrl_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxDatePickerCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDatePickerCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPickerBase -%% @hidden -doc false. isPickerCtrlGrowable(This) -> wxPickerBase:isPickerCtrlGrowable(This). -%% @hidden -doc false. setTextCtrlGrowable(This, Options) -> wxPickerBase:setTextCtrlGrowable(This, Options). -%% @hidden -doc false. setTextCtrlGrowable(This) -> wxPickerBase:setTextCtrlGrowable(This). -%% @hidden -doc false. setPickerCtrlGrowable(This, Options) -> wxPickerBase:setPickerCtrlGrowable(This, Options). -%% @hidden -doc false. setPickerCtrlGrowable(This) -> wxPickerBase:setPickerCtrlGrowable(This). -%% @hidden -doc false. isTextCtrlGrowable(This) -> wxPickerBase:isTextCtrlGrowable(This). -%% @hidden -doc false. getTextCtrl(This) -> wxPickerBase:getTextCtrl(This). -%% @hidden -doc false. hasTextCtrl(This) -> wxPickerBase:hasTextCtrl(This). -%% @hidden -doc false. getPickerCtrlProportion(This) -> wxPickerBase:getPickerCtrlProportion(This). -%% @hidden -doc false. getTextCtrlProportion(This) -> wxPickerBase:getTextCtrlProportion(This). -%% @hidden -doc false. setPickerCtrlProportion(This,Prop) -> wxPickerBase:setPickerCtrlProportion(This,Prop). -%% @hidden -doc false. setTextCtrlProportion(This,Prop) -> wxPickerBase:setTextCtrlProportion(This,Prop). -%% @hidden -doc false. getInternalMargin(This) -> wxPickerBase:getInternalMargin(This). -%% @hidden -doc false. setInternalMargin(This,Margin) -> wxPickerBase:setInternalMargin(This,Margin). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxDialog.erl b/lib/wx/src/gen/wxDialog.erl index 20b8a4c850a6..02c667e0fd53 100644 --- a/lib/wx/src/gen/wxDialog.erl +++ b/lib/wx/src/gen/wxDialog.erl @@ -20,63 +20,107 @@ -module(wxDialog). -moduledoc """ -Functions for wxDialog class +A dialog box is a window with a title bar and sometimes a system menu, which can be moved +around the screen. -A dialog box is a window with a title bar and sometimes a system menu, which can -be moved around the screen. It can contain controls and other windows and is -often used to allow the user to make some choice or to answer a question. +It can contain controls and other windows and is often used to allow the user to make +some choice or to answer a question. -Dialogs can be made scrollable, automatically, for computers with low resolution -screens: please see overview_dialog_autoscrolling for further details. +Dialogs can be made scrollable, automatically, for computers with low resolution screens: +please see overview_dialog_autoscrolling for further details. -Dialogs usually contain either a single button allowing to close the dialog or -two buttons, one accepting the changes and the other one discarding them (such -button, if present, is automatically activated if the user presses the "Esc" -key). By default, buttons with the standard wxID_OK and wxID_CANCEL identifiers -behave as expected. Starting with wxWidgets 2.7 it is also possible to use a -button with a different identifier instead, see `setAffirmativeId/2` and -`SetEscapeId()` (not implemented in wx). +Dialogs usually contain either a single button allowing to close the dialog or two +buttons, one accepting the changes and the other one discarding them (such button, if +present, is automatically activated if the user presses the "Esc" key). By default, +buttons with the standard wxID_OK and wxID_CANCEL identifiers behave as expected. Starting +with wxWidgets 2.7 it is also possible to use a button with a different identifier +instead, see `setAffirmativeId/2` and `SetEscapeId()` (not implemented in wx). -Also notice that the `createButtonSizer/2` should be used to create the buttons -appropriate for the current platform and positioned correctly (including their -order which is platform-dependent). +Also notice that the `createButtonSizer/2` should be used to create the buttons appropriate for the current +platform and positioned correctly (including their order which is platform-dependent). Modal and Modeless -There are two kinds of dialog, modal and modeless. A modal dialog blocks program -flow and user input on other windows until it is dismissed, whereas a modeless -dialog behaves more like a frame in that program flow continues, and input in -other windows is still possible. To show a modal dialog you should use the -`showModal/1` method while to show a dialog modelessly you simply use `show/2`, -just as with frames. +There are two kinds of dialog, modal and modeless. A modal dialog blocks program flow and +user input on other windows until it is dismissed, whereas a modeless dialog behaves more +like a frame in that program flow continues, and input in other windows is still possible. +To show a modal dialog you should use the `showModal/1` method while to show a dialog modelessly you +simply use `show/2`, just as with frames. -Note that the modal dialog is one of the very few examples of wxWindow-derived -objects which may be created on the stack and not on the heap. In other words, -while most windows would be created like this: +Note that the modal dialog is one of the very few examples of wxWindow-derived objects +which may be created on the stack and not on the heap. In other words, while most windows +would be created like this: You can achieve the same result with dialogs by using simpler code: -An application can define a `m:wxCloseEvent` handler for the dialog to respond -to system close events. +An application can define a `m:wxCloseEvent` handler for the dialog to respond to system +close events. -Styles +## Styles This class supports the following styles: +* wxCAPTION: Puts a caption on the dialog box. + +* wxDEFAULT_DIALOG_STYLE: Equivalent to a combination of wxCAPTION, wxCLOSE_BOX and +wxSYSTEM_MENU (the last one is not used under Unix). + +* wxRESIZE_BORDER: Display a resizable frame around the window. + +* wxSYSTEM_MENU: Display a system menu. + +* wxCLOSE_BOX: Displays a close box on the frame. + +* wxMAXIMIZE_BOX: Displays a maximize box on the dialog. + +* wxMINIMIZE_BOX: Displays a minimize box on the dialog. + +* wxTHICK_FRAME: Display a thick frame around the window. + +* wxSTAY_ON_TOP: The dialog stays on top of all other windows. + +* wxNO_3D: This style is obsolete and doesn't do anything any more, don't use it in any new +code. + +* wxDIALOG_NO_PARENT: By default, a dialog created with a NULL parent window will be given +the `application's top level window` (not implemented in wx) as parent. Use this style to +prevent this from happening and create an orphan dialog. This is not recommended for modal +dialogs. + +* wxDIALOG_EX_CONTEXTHELP: Under Windows, puts a query button on the caption. When pressed, +Windows will go into a context-sensitive help mode and wxWidgets will send a `wxEVT_HELP` +event if the user clicked on an application window. Note that this is an extended style +and must be set by calling `wxWindow:setExtraStyle/2` before Create is called (two-step construction). + +* wxDIALOG_EX_METAL: On macOS, frames with this style will be shown with a metallic look. +This is an extra style. Under Unix or Linux, MWM (the Motif Window Manager) or other +window managers recognizing the MHM hints should be running for any of these styles to +have an effect. + See: -[Overview dialog](https://docs.wxwidgets.org/3.1/overview_dialog.html#overview_dialog), -`m:wxFrame`, -[Overview validator](https://docs.wxwidgets.org/3.1/overview_validator.html#overview_validator) +* [Overview dialog](https://docs.wxwidgets.org/3.2/overview_dialog.html#overview_dialog) + +* `m:wxFrame` + +* [Overview validator](https://docs.wxwidgets.org/3.2/overview_validator.html#overview_validator) + +This class is derived, and can use functions, from: + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxTopLevelWindow` -`m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: [wxDialog](https://docs.wxwidgets.org/3.1/classwx_dialog.html) +wxWidgets docs: [wxDialog](https://docs.wxwidgets.org/3.2/classwx_dialog.html) ## Events -Event types emitted from this class: [`close_window`](`m:wxCloseEvent`), -[`init_dialog`](`m:wxInitDialogEvent`) +Event types emitted from this class: + +* [`close_window`](`m:wxCloseEvent`) + +* [`init_dialog`](`m:wxInitDialogEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,createButtonSizer/2,createStdDialogButtonSizer/2, @@ -129,21 +173,19 @@ Event types emitted from this class: [`close_window`](`m:wxCloseEvent`), -type wxDialog() :: wx:wx_object(). -export_type([wxDialog/0]). -%% @hidden -doc false. parent_class(wxTopLevelWindow) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxDialog(). new() -> wxe_util:queue_cmd(?get_env(), ?wxDialog_new_0), wxe_util:rec(?wxDialog_new_0). -%% @equiv new(Parent,Id,Title, []) +-doc(#{equiv => new(Parent,Id,Title, [])}). -spec new(Parent, Id, Title) -> wxDialog() when Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -151,7 +193,6 @@ new(Parent,Id,Title) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> new(Parent,Id,Title, []). -%% @doc See external documentation. -doc """ Constructor. @@ -174,7 +215,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(Parent,Id,Title_UC, Opts,?get_env(),?wxDialog_new_4), wxe_util:rec(?wxDialog_new_4). -%% @equiv create(This,Parent,Id,Title, []) +-doc(#{equiv => create(This,Parent,Id,Title, [])}). -spec create(This, Parent, Id, Title) -> boolean() when This::wxDialog(), Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -182,7 +223,6 @@ create(This,Parent,Id,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> create(This,Parent,Id,Title, []). -%% @doc See external documentation. -doc """ Used for two-step dialog box construction. @@ -206,20 +246,18 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(This,Parent,Id,Title_UC, Opts,?get_env(),?wxDialog_Create), wxe_util:rec(?wxDialog_Create). -%% @doc See external documentation. -doc """ Creates a sizer with standard buttons. -`flags` is a bit list of the following flags: wxOK, wxCANCEL, wxYES, wxNO, -wxAPPLY, wxCLOSE, wxHELP, wxNO_DEFAULT. +`flags` is a bit list of the following flags: wxOK, wxCANCEL, wxYES, wxNO, wxAPPLY, +wxCLOSE, wxHELP, wxNO_DEFAULT. The sizer lays out the buttons in a manner appropriate to the platform. -This function uses `createStdDialogButtonSizer/2` internally for most platforms -but doesn't create the sizer at all for the platforms with hardware buttons -(such as smartphones) for which it sets up the hardware buttons appropriately -and returns NULL, so don't forget to test that the return value is valid before -using it. +This function uses `createStdDialogButtonSizer/2` internally for most platforms but doesn't create the sizer at all for +the platforms with hardware buttons (such as smartphones) for which it sets up the +hardware buttons appropriately and returns NULL, so don't forget to test that the return +value is valid before using it. """. -spec createButtonSizer(This, Flags) -> wxSizer:wxSizer() when This::wxDialog(), Flags::integer(). @@ -229,12 +267,11 @@ createButtonSizer(#wx_ref{type=ThisT}=This,Flags) wxe_util:queue_cmd(This,Flags,?get_env(),?wxDialog_CreateButtonSizer), wxe_util:rec(?wxDialog_CreateButtonSizer). -%% @doc See external documentation. -doc """ Creates a `m:wxStdDialogButtonSizer` with standard buttons. -`flags` is a bit list of the following flags: wxOK, wxCANCEL, wxYES, wxNO, -wxAPPLY, wxCLOSE, wxHELP, wxNO_DEFAULT. +`flags` is a bit list of the following flags: wxOK, wxCANCEL, wxYES, wxNO, wxAPPLY, +wxCLOSE, wxHELP, wxNO_DEFAULT. The sizer lays out the buttons in a manner appropriate to the platform. """. @@ -246,12 +283,15 @@ createStdDialogButtonSizer(#wx_ref{type=ThisT}=This,Flags) wxe_util:queue_cmd(This,Flags,?get_env(),?wxDialog_CreateStdDialogButtonSizer), wxe_util:rec(?wxDialog_CreateStdDialogButtonSizer). -%% @doc See external documentation. -doc """ -Ends a modal dialog, passing a value to be returned from the `showModal/1` -invocation. +Ends a modal dialog, passing a value to be returned from the `showModal/1` invocation. + +See: +* `showModal/1` + +* `getReturnCode/1` -See: `showModal/1`, `getReturnCode/1`, `setReturnCode/2` +* `setReturnCode/2` """. -spec endModal(This, RetCode) -> 'ok' when This::wxDialog(), RetCode::integer(). @@ -260,10 +300,8 @@ endModal(#wx_ref{type=ThisT}=This,RetCode) ?CLASS(ThisT,wxDialog), wxe_util:queue_cmd(This,RetCode,?get_env(),?wxDialog_EndModal). -%% @doc See external documentation. -doc """ -Gets the identifier of the button which works like standard OK button in this -dialog. +Gets the identifier of the button which works like standard OK button in this dialog. See: `setAffirmativeId/2` """. @@ -274,14 +312,18 @@ getAffirmativeId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDialog_GetAffirmativeId), wxe_util:rec(?wxDialog_GetAffirmativeId). -%% @doc See external documentation. -doc """ Gets the return code for this window. -Remark: A return code is normally associated with a modal dialog, where -`showModal/1` returns a code to the application. +Remark: A return code is normally associated with a modal dialog, where `showModal/1` returns a code +to the application. -See: `setReturnCode/2`, `showModal/1`, `endModal/2` +See: +* `setReturnCode/2` + +* `showModal/1` + +* `endModal/2` """. -spec getReturnCode(This) -> integer() when This::wxDialog(). @@ -290,7 +332,6 @@ getReturnCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDialog_GetReturnCode), wxe_util:rec(?wxDialog_GetReturnCode). -%% @doc See external documentation. -doc "Returns true if the dialog box is modal, false otherwise.". -spec isModal(This) -> boolean() when This::wxDialog(). @@ -299,21 +340,18 @@ isModal(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDialog_IsModal), wxe_util:rec(?wxDialog_IsModal). -%% @doc See external documentation. -doc """ Sets the identifier to be used as OK button. -When the button with this identifier is pressed, the dialog calls -`wxWindow:validate/1` and `wxWindow:transferDataFromWindow/1` and, if they both +When the button with this identifier is pressed, the dialog calls `wxWindow:validate/1` and `wxWindow:transferDataFromWindow/1` and, if they both return true, closes the dialog with the affirmative id return code. -Also, when the user presses a hardware OK button on the devices having one or -the special OK button in the PocketPC title bar, an event with this id is -generated. +Also, when the user presses a hardware OK button on the devices having one or the special +OK button in the PocketPC title bar, an event with this id is generated. By default, the affirmative id is wxID_OK. -See: `getAffirmativeId/1`, `SetEscapeId()` (not implemented in wx) +See: `getAffirmativeId/1` """. -spec setAffirmativeId(This, Id) -> 'ok' when This::wxDialog(), Id::integer(). @@ -322,15 +360,18 @@ setAffirmativeId(#wx_ref{type=ThisT}=This,Id) ?CLASS(ThisT,wxDialog), wxe_util:queue_cmd(This,Id,?get_env(),?wxDialog_SetAffirmativeId). -%% @doc See external documentation. -doc """ Sets the return code for this window. -A return code is normally associated with a modal dialog, where `showModal/1` -returns a code to the application. The function `endModal/2` calls -`setReturnCode/2`. +A return code is normally associated with a modal dialog, where `showModal/1` returns a code to the +application. The function `endModal/2` calls `setReturnCode/2`. + +See: +* `getReturnCode/1` + +* `showModal/1` -See: `getReturnCode/1`, `showModal/1`, `endModal/2` +* `endModal/2` """. -spec setReturnCode(This, RetCode) -> 'ok' when This::wxDialog(), RetCode::integer(). @@ -339,7 +380,7 @@ setReturnCode(#wx_ref{type=ThisT}=This,RetCode) ?CLASS(ThisT,wxDialog), wxe_util:queue_cmd(This,RetCode,?get_env(),?wxDialog_SetReturnCode). -%% @equiv show(This, []) +-doc(#{equiv => show(This, [])}). -spec show(This) -> boolean() when This::wxDialog(). @@ -347,7 +388,6 @@ show(This) when is_record(This, wx_ref) -> show(This, []). -%% @doc See external documentation. -doc """ Hides or shows the dialog. @@ -365,27 +405,28 @@ show(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxDialog_Show), wxe_util:rec(?wxDialog_Show). -%% @doc See external documentation. -doc """ Shows an application-modal dialog. -Program flow does not return until the dialog has been dismissed with -`endModal/2`. +Program flow does not return until the dialog has been dismissed with `endModal/2`. -Notice that it is possible to call `showModal/1` for a dialog which had been -previously shown with `show/2`, this allows making an existing modeless dialog -modal. However `showModal/1` can't be called twice without intervening -`endModal/2` calls. +Notice that it is possible to call `showModal/1` for a dialog which had been previously shown with `show/2`, +this allows making an existing modeless dialog modal. However `showModal/1` can't be called twice +without intervening `endModal/2` calls. -Note that this function creates a temporary event loop which takes precedence -over the application's main event loop (see `wxEventLoopBase` (not implemented -in wx)) and which is destroyed when the dialog is dismissed. This also results -in a call to `wxApp::ProcessPendingEvents()` (not implemented in wx). +Note that this function creates a temporary event loop which takes precedence over the +application's main event loop (see `wxEventLoopBase` (not implemented in wx)) and which is +destroyed when the dialog is dismissed. This also results in a call to `wxApp::ProcessPendingEvents()` +(not implemented in wx). Return: The value set with `setReturnCode/2`. -See: `ShowWindowModal()` (not implemented in wx), `ShowWindowModalThenDo()` (not -implemented in wx), `endModal/2`, `getReturnCode/1`, `setReturnCode/2` +See: +* `endModal/2` + +* `getReturnCode/1` + +* `setReturnCode/2` """. -spec showModal(This) -> integer() when This::wxDialog(). @@ -394,631 +435,420 @@ showModal(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDialog_ShowModal), wxe_util:rec(?wxDialog_ShowModal). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Deletes any child windows before deleting the physical window. - -See overview_windowdeletion for more info. -""". +-doc "Destroys the object". -spec destroy(This::wxDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxDirDialog.erl b/lib/wx/src/gen/wxDirDialog.erl index 4d16a17105a8..af2984251102 100644 --- a/lib/wx/src/gen/wxDirDialog.erl +++ b/lib/wx/src/gen/wxDirDialog.erl @@ -20,31 +20,58 @@ -module(wxDirDialog). -moduledoc """ -Functions for wxDirDialog class - This class represents the directory chooser dialog. -Styles +## Styles This class supports the following styles: +* wxDD_DEFAULT_STYLE: Equivalent to a combination of wxDEFAULT_DIALOG_STYLE and +wxRESIZE_BORDER. + +* wxDD_DIR_MUST_EXIST: The dialog will allow the user to choose only an existing folder. +When this style is not given, a "Create new directory" button is added to the dialog (on +Windows) or some other way is provided to the user to type the name of a new folder. + +* wxDD_CHANGE_DIR: Change the current working directory to the directory chosen by the +user. + Note: This flag cannot be used with the `wxDD_MULTIPLE` style. -Remark: MacOS 10.11+ does not display a title bar on the dialog. Use -`setMessage/2` to change the string displayed to the user at the top of the -dialog after creation. The `wxTopLevelWindow:setTitle/2` method is provided for -compatibility with pre-10.11 MacOS versions that do still support displaying the -title bar. +* wxDD_MULTIPLE: Allow the user to select multiple directories. This flag is only +available since wxWidgets 3.1.4 + +* wxDD_SHOW_HIDDEN: Show hidden and system folders. This flag is only available since +wxWidgets 3.1.4 Notice that `wxRESIZE_BORDER` has special side effect under Windows where +two different directory selection dialogs are available and this style also implicitly +selects the new version as the old one always has fixed size. As the new version is almost +always preferable, it is recommended that `wxRESIZE_BORDER` style be always used. This is +the case if the dialog is created with the default style value but if you need to use any +additional styles you should still specify `wxDD_DEFAULT_STYLE` unless you explicitly need +to use the old dialog version under Windows. E.g. do instead of just using `wxDD_DIR_MUST_EXIST` +style alone. + +Remark: MacOS 10.11+ does not display a title bar on the dialog. Use `setMessage/2` to change the +string displayed to the user at the top of the dialog after creation. The `wxTopLevelWindow:setTitle/2` method is +provided for compatibility with pre-10.11 MacOS versions that do still support displaying +the title bar. See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_dir), -`m:wxFileDialog` +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_dir) + +* `m:wxFileDialog` + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxDirDialog](https://docs.wxwidgets.org/3.1/classwx_dir_dialog.html) +wxWidgets docs: [wxDirDialog](https://docs.wxwidgets.org/3.2/classwx_dir_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getMessage/1,getPath/1,new/1,new/2,setMessage/2,setPath/2]). @@ -96,7 +123,6 @@ wxWidgets docs: -type wxDirDialog() :: wx:wx_object(). -export_type([wxDirDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -104,7 +130,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxDirDialog() when Parent::wxWindow:wxWindow(). @@ -112,7 +138,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ Constructor. @@ -138,12 +163,11 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxDirDialog_new), wxe_util:rec(?wxDirDialog_new). -%% @doc See external documentation. -doc """ Returns the default or user-selected path. -Note: This function can't be used with dialogs which have the `wxDD_MULTIPLE` -style, use `GetPaths()` (not implemented in wx) instead. +Note: This function can't be used with dialogs which have the `wxDD_MULTIPLE` style, use `GetPaths()` +(not implemented in wx) instead. """. -spec getPath(This) -> unicode:charlist() when This::wxDirDialog(). @@ -152,7 +176,6 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDirDialog_GetPath), wxe_util:rec(?wxDirDialog_GetPath). -%% @doc See external documentation. -doc "Returns the message that will be displayed on the dialog.". -spec getMessage(This) -> unicode:charlist() when This::wxDirDialog(). @@ -161,7 +184,6 @@ getMessage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDirDialog_GetMessage), wxe_util:rec(?wxDirDialog_GetMessage). -%% @doc See external documentation. -doc "Sets the message that will be displayed on the dialog.". -spec setMessage(This, Message) -> 'ok' when This::wxDirDialog(), Message::unicode:chardata(). @@ -171,7 +193,6 @@ setMessage(#wx_ref{type=ThisT}=This,Message) Message_UC = unicode:characters_to_binary(Message), wxe_util:queue_cmd(This,Message_UC,?get_env(),?wxDirDialog_SetMessage). -%% @doc See external documentation. -doc "Sets the default path.". -spec setPath(This, Path) -> 'ok' when This::wxDirDialog(), Path::unicode:chardata(). @@ -181,659 +202,443 @@ setPath(#wx_ref{type=ThisT}=This,Path) Path_UC = unicode:characters_to_binary(Path), wxe_util:queue_cmd(This,Path_UC,?get_env(),?wxDirDialog_SetPath). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxDirDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDirDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxDirPickerCtrl.erl b/lib/wx/src/gen/wxDirPickerCtrl.erl index 50c908229553..ab880f9238b0 100644 --- a/lib/wx/src/gen/wxDirPickerCtrl.erl +++ b/lib/wx/src/gen/wxDirPickerCtrl.erl @@ -20,30 +20,59 @@ -module(wxDirPickerCtrl). -moduledoc """ -Functions for wxDirPickerCtrl class +This control allows the user to select a directory. -This control allows the user to select a directory. The generic implementation -is a button which brings up a `m:wxDirDialog` when clicked. Native -implementation may differ but this is usually a (small) widget which give access -to the dir-chooser dialog. It is only available if `wxUSE_DIRPICKERCTRL` is set -to 1 (the default). +The generic implementation is a button which brings up a `m:wxDirDialog` when clicked. +Native implementation may differ but this is usually a (small) widget which give access to +the dir-chooser dialog. It is only available if `wxUSE_DIRPICKERCTRL` is set to 1 (the default). -Styles +## Styles This class supports the following styles: -See: `m:wxDirDialog`, `m:wxFileDirPickerEvent` +* wxDIRP_DEFAULT_STYLE: The default style: includes wxDIRP_DIR_MUST_EXIST and, under wxMSW +only, wxDIRP_USE_TEXTCTRL. -This class is derived (and can use functions) from: `m:wxPickerBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* wxDIRP_USE_TEXTCTRL: Creates a text control to the left of the picker button which is +completely managed by the `m:wxDirPickerCtrl` and which can be used by the user to specify +a path (see SetPath). The text control is automatically synchronized with button's value. +Use functions defined in `m:wxPickerBase` to modify the text control. -wxWidgets docs: -[wxDirPickerCtrl](https://docs.wxwidgets.org/3.1/classwx_dir_picker_ctrl.html) +* wxDIRP_DIR_MUST_EXIST: Creates a picker which allows selecting only existing directories +in the popup `m:wxDirDialog`. Notice that, as with `wxFLP_FILE_MUST_EXIST`, it is still +possible to enter a non-existent directory even when this file is specified if `wxDIRP_USE_TEXTCTRL` +style is also used. Also note that if `wxDIRP_USE_TEXTCTRL` is not used, the native wxGTK +implementation always uses this style as it doesn't support selecting non-existent +directories. + +* wxDIRP_CHANGE_DIR: Change current working directory on each user directory selection +change. + +* wxDIRP_SMALL: Use smaller version of the control with a small "..." button instead of the +normal "Browse" one. This flag is new since wxWidgets 2.9.3. + +See: +* `m:wxDirDialog` + +* `m:wxFileDirPickerEvent` + +This class is derived, and can use functions, from: + +* `m:wxPickerBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxDirPickerCtrl](https://docs.wxwidgets.org/3.2/classwx_dir_picker_ctrl.html) ## Events Event types emitted from this class: -[`command_dirpicker_changed`](`m:wxFileDirPickerEvent`) + +* [`command_dirpicker_changed`](`m:wxFileDirPickerEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getPath/1,new/0,new/2,new/3,setPath/2]). @@ -93,7 +122,6 @@ Event types emitted from this class: -type wxDirPickerCtrl() :: wx:wx_object(). -export_type([wxDirPickerCtrl/0]). -%% @hidden -doc false. parent_class(wxPickerBase) -> true; parent_class(wxControl) -> true; @@ -101,13 +129,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxDirPickerCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxDirPickerCtrl_new_0), wxe_util:rec(?wxDirPickerCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxDirPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -115,7 +143,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Initializes the object and calls `create/4` with all the parameters.". -spec new(Parent, Id, [Option]) -> wxDirPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -139,7 +166,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxDirPickerCtrl_new_3), wxe_util:rec(?wxDirPickerCtrl_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxDirPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -147,12 +174,10 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Creates the widgets with the given parameters. -Return: true if the control was successfully created or false if creation -failed. +Return: true if the control was successfully created or false if creation failed. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxDirPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -177,7 +202,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxDirPickerCtrl_Create), wxe_util:rec(?wxDirPickerCtrl_Create). -%% @doc See external documentation. -doc "Returns the absolute path of the currently selected directory.". -spec getPath(This) -> unicode:charlist() when This::wxDirPickerCtrl(). @@ -186,14 +210,12 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDirPickerCtrl_GetPath), wxe_util:rec(?wxDirPickerCtrl_GetPath). -%% @doc See external documentation. -doc """ Sets the absolute path of the currently selected directory. -If the control uses `wxDIRP_DIR_MUST_EXIST` and does not use -`wxDIRP_USE_TEXTCTRL` style, the `dirname` must be a name of an existing -directory and will be simply ignored by the native wxGTK implementation if this -is not the case. +If the control uses `wxDIRP_DIR_MUST_EXIST` and does not use `wxDIRP_USE_TEXTCTRL` style, +the `dirname` must be a name of an existing directory and will be simply ignored by the +native wxGTK implementation if this is not the case. """. -spec setPath(This, Dirname) -> 'ok' when This::wxDirPickerCtrl(), Dirname::unicode:chardata(). @@ -203,605 +225,407 @@ setPath(#wx_ref{type=ThisT}=This,Dirname) Dirname_UC = unicode:characters_to_binary(Dirname), wxe_util:queue_cmd(This,Dirname_UC,?get_env(),?wxDirPickerCtrl_SetPath). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxDirPickerCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDirPickerCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPickerBase -%% @hidden -doc false. isPickerCtrlGrowable(This) -> wxPickerBase:isPickerCtrlGrowable(This). -%% @hidden -doc false. setTextCtrlGrowable(This, Options) -> wxPickerBase:setTextCtrlGrowable(This, Options). -%% @hidden -doc false. setTextCtrlGrowable(This) -> wxPickerBase:setTextCtrlGrowable(This). -%% @hidden -doc false. setPickerCtrlGrowable(This, Options) -> wxPickerBase:setPickerCtrlGrowable(This, Options). -%% @hidden -doc false. setPickerCtrlGrowable(This) -> wxPickerBase:setPickerCtrlGrowable(This). -%% @hidden -doc false. isTextCtrlGrowable(This) -> wxPickerBase:isTextCtrlGrowable(This). -%% @hidden -doc false. getTextCtrl(This) -> wxPickerBase:getTextCtrl(This). -%% @hidden -doc false. hasTextCtrl(This) -> wxPickerBase:hasTextCtrl(This). -%% @hidden -doc false. getPickerCtrlProportion(This) -> wxPickerBase:getPickerCtrlProportion(This). -%% @hidden -doc false. getTextCtrlProportion(This) -> wxPickerBase:getTextCtrlProportion(This). -%% @hidden -doc false. setPickerCtrlProportion(This,Prop) -> wxPickerBase:setPickerCtrlProportion(This,Prop). -%% @hidden -doc false. setTextCtrlProportion(This,Prop) -> wxPickerBase:setTextCtrlProportion(This,Prop). -%% @hidden -doc false. getInternalMargin(This) -> wxPickerBase:getInternalMargin(This). -%% @hidden -doc false. setInternalMargin(This,Margin) -> wxPickerBase:setInternalMargin(This,Margin). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxDisplay.erl b/lib/wx/src/gen/wxDisplay.erl index c921939e4c3c..6d78cca8cfd2 100644 --- a/lib/wx/src/gen/wxDisplay.erl +++ b/lib/wx/src/gen/wxDisplay.erl @@ -20,11 +20,9 @@ -module(wxDisplay). -moduledoc """ -Functions for wxDisplay class - Determines the sizes and locations of displays connected to the system. -wxWidgets docs: [wxDisplay](https://docs.wxwidgets.org/3.1/classwx_display.html) +wxWidgets docs: [wxDisplay](https://docs.wxwidgets.org/3.2/classwx_display.html) """. -include("wxe.hrl"). -export([destroy/1,getClientArea/1,getCount/0,getFromPoint/1,getFromWindow/1, @@ -35,31 +33,21 @@ wxWidgets docs: [wxDisplay](https://docs.wxwidgets.org/3.1/classwx_display.html) -type wxDisplay() :: wx:wx_object(). -export_type([wxDisplay/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. --doc """ -Default constructor creating `m:wxDisplay` object representing the primary -display. -""". +-doc "Default constructor creating `m:wxDisplay` object representing the primary display.". -spec new() -> wxDisplay(). new() -> wxe_util:queue_cmd(?get_env(), ?wxDisplay_new_0), wxe_util:rec(?wxDisplay_new_0). -%% @doc See external documentation. -%%
Also:
-%% new(Window) -> wxDisplay() when
-%% Window::wxWindow:wxWindow().
-%% -doc """ Constructor creating the display object associated with the given window. -This is the most convenient way of finding the display on which the given window -is shown while falling back to the default display if it is not shown at all or -positioned outside of any display. +This is the most convenient way of finding the display on which the given window is shown +while falling back to the default display if it is not shown at all or positioned outside +of any display. See: `getFromWindow/1` @@ -78,7 +66,6 @@ new(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxDisplay_new_1_1), wxe_util:rec(?wxDisplay_new_1_1). -%% @doc See external documentation. -doc "Returns true if the object was initialized successfully.". -spec isOk(This) -> boolean() when This::wxDisplay(). @@ -87,13 +74,12 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_IsOk), wxe_util:rec(?wxDisplay_IsOk). -%% @doc See external documentation. -doc """ Returns the client area of the display. -The client area is the part of the display available for the normal (non full -screen) windows, usually it is the same as `getGeometry/1` but it could be less -if there is a taskbar (or equivalent) on this display. +The client area is the part of the display available for the normal (non full screen) +windows, usually it is the same as `getGeometry/1` but it could be less if there is a taskbar (or +equivalent) on this display. """. -spec getClientArea(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxDisplay(). @@ -102,12 +88,13 @@ getClientArea(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_GetClientArea), wxe_util:rec(?wxDisplay_GetClientArea). -%% @doc See external documentation. -doc """ -Returns the bounding rectangle of the display whose index was passed to the -constructor. +Returns the bounding rectangle of the display whose index was passed to the constructor. + +See: +* `getClientArea/1` -See: `getClientArea/1`, `wx_misc:displaySize/0` +* `wx_misc:displaySize/0` """. -spec getGeometry(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxDisplay(). @@ -116,7 +103,6 @@ getGeometry(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_GetGeometry), wxe_util:rec(?wxDisplay_GetGeometry). -%% @doc See external documentation. -doc """ Returns the display's name. @@ -129,7 +115,6 @@ getName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_GetName), wxe_util:rec(?wxDisplay_GetName). -%% @doc See external documentation. -doc """ Returns true if the display is the primary display. @@ -142,17 +127,15 @@ isPrimary(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_IsPrimary), wxe_util:rec(?wxDisplay_IsPrimary). -%% @doc See external documentation. -doc "Returns the number of connected displays.". -spec getCount() -> integer(). getCount() -> wxe_util:queue_cmd(?get_env(), ?wxDisplay_GetCount), wxe_util:rec(?wxDisplay_GetCount). -%% @doc See external documentation. -doc """ -Returns the index of the display on which the given point lies, or `wxNOT_FOUND` -if the point is not on any connected display. +Returns the index of the display on which the given point lies, or `wxNOT\_FOUND` if the +point is not on any connected display. """. -spec getFromPoint(Pt) -> integer() when Pt::{X::integer(), Y::integer()}. @@ -161,12 +144,11 @@ getFromPoint({PtX,PtY} = Pt) wxe_util:queue_cmd(Pt,?get_env(),?wxDisplay_GetFromPoint), wxe_util:rec(?wxDisplay_GetFromPoint). -%% @doc See external documentation. -doc """ Returns the index of the display on which the given window lies. -If the window is on more than one display it gets the display that overlaps the -window the most. +If the window is on more than one display it gets the display that overlaps the window +the most. Returns `wxNOT_FOUND` if the window is not on any connected display. """. @@ -177,12 +159,11 @@ getFromWindow(#wx_ref{type=WinT}=Win) -> wxe_util:queue_cmd(Win,?get_env(),?wxDisplay_GetFromWindow), wxe_util:rec(?wxDisplay_GetFromWindow). -%% @doc See external documentation. -doc """ Returns display resolution in pixels per inch. Horizontal and vertical resolution are returned in `x` and `y` components of the -\{Width,Height\} object respectively. +{Width,Height} object respectively. If the resolution information is not available, returns. @@ -195,8 +176,7 @@ getPPI(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDisplay_GetPPI), wxe_util:rec(?wxDisplay_GetPPI). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxDisplay()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxDisplay), diff --git a/lib/wx/src/gen/wxDisplayChangedEvent.erl b/lib/wx/src/gen/wxDisplayChangedEvent.erl index 44459ccc5940..7b317664340f 100644 --- a/lib/wx/src/gen/wxDisplayChangedEvent.erl +++ b/lib/wx/src/gen/wxDisplayChangedEvent.erl @@ -20,27 +20,22 @@ -module(wxDisplayChangedEvent). -moduledoc """ -Functions for wxDisplayChangedEvent class - -A display changed event is sent to top-level windows when the display resolution -has changed. +A display changed event is sent to top-level windows when the display resolution has +changed. This event is currently emitted under Windows only. -Only for:wxmsw - See: `m:wxDisplay` -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxEvent` -wxWidgets docs: -[wxDisplayChangedEvent](https://docs.wxwidgets.org/3.1/classwx_display_changed_event.html) +wxWidgets docs: [wxDisplayChangedEvent](https://docs.wxwidgets.org/3.2/classwx_display_changed_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxDisplayChangedEventType`](`t:wxDisplayChangedEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxDisplayChangedEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -53,36 +48,26 @@ events of this type. -include("wx.hrl"). -type wxDisplayChangedEventType() :: 'display_changed'. -export_type([wxDisplayChangedEvent/0, wxDisplayChanged/0, wxDisplayChangedEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxDropFilesEvent.erl b/lib/wx/src/gen/wxDropFilesEvent.erl index 7c22a903c61c..999fb2372ba7 100644 --- a/lib/wx/src/gen/wxDropFilesEvent.erl +++ b/lib/wx/src/gen/wxDropFilesEvent.erl @@ -20,35 +20,29 @@ -module(wxDropFilesEvent). -moduledoc """ -Functions for wxDropFilesEvent class +This class is used for drop files events, that is, when files have been dropped onto the +window. -This class is used for drop files events, that is, when files have been dropped -onto the window. +The window must have previously been enabled for dropping by calling `wxWindow:dragAcceptFiles/2`. -The window must have previously been enabled for dropping by calling -`wxWindow:dragAcceptFiles/2`. +Important note: this is a separate implementation to the more general drag and drop +implementation documented in the overview_dnd. It uses the older, Windows message-based +approach of dropping files. -Important note: this is a separate implementation to the more general drag and -drop implementation documented in the overview_dnd. It uses the older, Windows -message-based approach of dropping files. +See: +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -Remark: Windows only until version 2.8.9, available on all platforms since -2.8.10. +* `wxWindow:dragAcceptFiles/2` -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxWindow:dragAcceptFiles/2` +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxDropFilesEvent](https://docs.wxwidgets.org/3.1/classwx_drop_files_event.html) +wxWidgets docs: [wxDropFilesEvent](https://docs.wxwidgets.org/3.2/classwx_drop_files_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxDropFilesEventType`](`t:wxDropFilesEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxDropFilesEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getFiles/1,getNumberOfFiles/1,getPosition/1]). @@ -61,12 +55,10 @@ this type. -include("wx.hrl"). -type wxDropFilesEventType() :: 'drop_files'. -export_type([wxDropFilesEvent/0, wxDropFiles/0, wxDropFilesEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns the position at which the files were dropped. @@ -79,7 +71,6 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDropFilesEvent_GetPosition), wxe_util:rec(?wxDropFilesEvent_GetPosition). -%% @doc See external documentation. -doc "Returns the number of files dropped.". -spec getNumberOfFiles(This) -> integer() when This::wxDropFilesEvent(). @@ -88,7 +79,6 @@ getNumberOfFiles(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxDropFilesEvent_GetNumberOfFiles), wxe_util:rec(?wxDropFilesEvent_GetNumberOfFiles). -%% @doc See external documentation. -doc "Returns an array of filenames.". -spec getFiles(This) -> [unicode:charlist()] when This::wxDropFilesEvent(). @@ -98,30 +88,21 @@ getFiles(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxDropFilesEvent_GetFiles). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxEraseEvent.erl b/lib/wx/src/gen/wxEraseEvent.erl index fcea908fb7dc..d06938a75d55 100644 --- a/lib/wx/src/gen/wxEraseEvent.erl +++ b/lib/wx/src/gen/wxEraseEvent.erl @@ -20,33 +20,29 @@ -module(wxEraseEvent). -moduledoc """ -Functions for wxEraseEvent class - An erase event is sent when a window's background needs to be repainted. -On some platforms, such as GTK+, this event is simulated (simply generated just -before the paint event) and may cause flicker. It is therefore recommended that -you set the text background colour explicitly in order to prevent flicker. The -default background colour under GTK+ is grey. +On some platforms, such as GTK+, this event is simulated (simply generated just before +the paint event) and may cause flicker. It is therefore recommended that you set the text +background colour explicitly in order to prevent flicker. The default background colour +under GTK+ is grey. + +To intercept this event, use the EVT_ERASE_BACKGROUND macro in an event table definition. -To intercept this event, use the EVT_ERASE_BACKGROUND macro in an event table -definition. +You must use the device context returned by `getDC/1` to draw on, don't create a `m:wxPaintDC` in +the event handler. -You must use the device context returned by `getDC/1` to draw on, don't create a -`m:wxPaintDC` in the event handler. +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxEraseEvent](https://docs.wxwidgets.org/3.1/classwx_erase_event.html) +wxWidgets docs: [wxEraseEvent](https://docs.wxwidgets.org/3.2/classwx_erase_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxEraseEventType`](`t:wxEraseEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxEraseEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getDC/1]). @@ -59,12 +55,10 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxEraseEventType() :: 'erase_background'. -export_type([wxEraseEvent/0, wxErase/0, wxEraseEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns the device context associated with the erase event to draw on. @@ -78,30 +72,21 @@ getDC(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxEraseEvent_GetDC). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxEvent.erl b/lib/wx/src/gen/wxEvent.erl index 4515d885240f..1daf26ca84c0 100644 --- a/lib/wx/src/gen/wxEvent.erl +++ b/lib/wx/src/gen/wxEvent.erl @@ -20,19 +20,20 @@ -module(wxEvent). -moduledoc """ -Functions for wxEvent class +An event is a structure holding information about an event passed to a callback or member +function. -An event is a structure holding information about an event passed to a callback -or member function. - -`m:wxEvent` used to be a multipurpose event object, and is an abstract base -class for other event classes (see below). +`m:wxEvent` used to be a multipurpose event object, and is an abstract base class for +other event classes (see below). For more information about events, see the overview_events overview. -See: `m:wxCommandEvent`, `m:wxMouseEvent` +See: +* `m:wxCommandEvent` + +* `m:wxMouseEvent` -wxWidgets docs: [wxEvent](https://docs.wxwidgets.org/3.1/classwx_event.html) +wxWidgets docs: [wxEvent](https://docs.wxwidgets.org/3.2/classwx_event.html) """. -include("wxe.hrl"). -export([getId/1,getSkipped/1,getTimestamp/1,isCommandEvent/1,resumePropagation/2, @@ -43,11 +44,9 @@ wxWidgets docs: [wxEvent](https://docs.wxwidgets.org/3.1/classwx_event.html) -type wxEvent() :: wx:wx_object(). -export_type([wxEvent/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Returns the identifier associated with this event, such as a button command id.". -spec getId(This) -> integer() when This::wxEvent(). @@ -56,7 +55,6 @@ getId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxEvent_GetId), wxe_util:rec(?wxEvent_GetId). -%% @doc See external documentation. -doc "Returns true if the event handler should be skipped, false otherwise.". -spec getSkipped(This) -> boolean() when This::wxEvent(). @@ -65,16 +63,17 @@ getSkipped(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxEvent_GetSkipped), wxe_util:rec(?wxEvent_GetSkipped). -%% @doc See external documentation. -doc """ Gets the timestamp for the event. -The timestamp is the time in milliseconds since some fixed moment (not -necessarily the standard Unix Epoch, so only differences between the timestamps -and not their absolute values usually make sense). +The timestamp is the time in milliseconds since some fixed moment (not necessarily the +standard Unix Epoch, so only differences between the timestamps and not their absolute +values usually make sense). + +Warning: -Warning: wxWidgets returns a non-NULL timestamp only for mouse and key events -(see `m:wxMouseEvent` and `m:wxKeyEvent`). +wxWidgets returns a non-NULL timestamp only for mouse and key events (see `m:wxMouseEvent` +and `m:wxKeyEvent`). """. -spec getTimestamp(This) -> integer() when This::wxEvent(). @@ -83,10 +82,8 @@ getTimestamp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxEvent_GetTimestamp), wxe_util:rec(?wxEvent_GetTimestamp). -%% @doc See external documentation. -doc """ -Returns true if the event is or is derived from `m:wxCommandEvent` else it -returns false. +Returns true if the event is or is derived from `m:wxCommandEvent` else it returns false. Note: exists only for optimization purposes. """. @@ -97,10 +94,9 @@ isCommandEvent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxEvent_IsCommandEvent), wxe_util:rec(?wxEvent_IsCommandEvent). -%% @doc See external documentation. -doc """ -Sets the propagation level to the given value (for example returned from an -earlier call to `stopPropagation/1`). +Sets the propagation level to the given value (for example returned from an earlier call +to `stopPropagation/1`). """. -spec resumePropagation(This, PropagationLevel) -> 'ok' when This::wxEvent(), PropagationLevel::integer(). @@ -109,7 +105,6 @@ resumePropagation(#wx_ref{type=ThisT}=This,PropagationLevel) ?CLASS(ThisT,wxEvent), wxe_util:queue_cmd(This,PropagationLevel,?get_env(),?wxEvent_ResumePropagation). -%% @doc See external documentation. -doc """ Test if this event should be propagated or not, i.e. if the propagation level is currently greater than 0. @@ -121,7 +116,7 @@ shouldPropagate(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxEvent_ShouldPropagate), wxe_util:rec(?wxEvent_ShouldPropagate). -%% @equiv skip(This, []) +-doc(#{equiv => skip(This, [])}). -spec skip(This) -> 'ok' when This::wxEvent(). @@ -129,20 +124,19 @@ skip(This) when is_record(This, wx_ref) -> skip(This, []). -%% @doc See external documentation. -doc """ -This method can be used inside an event handler to control whether further event -handlers bound to this event will be called after the current one returns. - -Without `skip/2` (or equivalently if Skip(false) is used), the event will not be -processed any more. If Skip(true) is called, the event processing system -continues searching for a further handler function for this event, even though -it has been processed already in the current handler. - -In general, it is recommended to skip all non-command events to allow the -default handling to take place. The command events are, however, normally not -skipped as usually a single command such as a button click or menu item -selection must only be processed by one handler. +This method can be used inside an event handler to control whether further event handlers +bound to this event will be called after the current one returns. + +Without `skip/2` (or equivalently if Skip(false) is used), the event will not be processed any +more. If Skip(true) is called, the event processing system continues searching for a +further handler function for this event, even though it has been processed already in the +current handler. + +In general, it is recommended to skip all non-command events to allow the default +handling to take place. The command events are, however, normally not skipped as usually a +single command such as a button click or menu item selection must only be processed by one +handler. """. -spec skip(This, [Option]) -> 'ok' when This::wxEvent(), @@ -155,12 +149,11 @@ skip(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxEvent_Skip). -%% @doc See external documentation. -doc """ Stop the event from propagating to its parent window. -Returns the old propagation level value which may be later passed to -`resumePropagation/2` to allow propagating the event again. +Returns the old propagation level value which may be later passed to `resumePropagation/2` to allow +propagating the event again. """. -spec stopPropagation(This) -> integer() when This::wxEvent(). diff --git a/lib/wx/src/gen/wxEvtHandler.erl b/lib/wx/src/gen/wxEvtHandler.erl index 9f239b2795a5..97208b8e1a28 100644 --- a/lib/wx/src/gen/wxEvtHandler.erl +++ b/lib/wx/src/gen/wxEvtHandler.erl @@ -20,34 +20,14 @@ %% 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. -%% -%% -%% The original documentation. -%% -%% -module(wxEvtHandler). -moduledoc """ -Functions for wxEvtHandler class +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`. +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. @@ -62,10 +42,10 @@ process) to handle the event. The callback should be of arity 2. Note: The callback will be in executed in new process each time. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events_processing) +[Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events_processing) wxWidgets docs: -[wxEvtHandler](https://docs.wxwidgets.org/3.1/classwx_evt_handler.html) +[wxEvtHandler](https://docs.wxwidgets.org/3.2/classwx_evt_handler.html) """. -include("wxe.hrl"). -include("../include/wx.hrl"). @@ -79,30 +59,11 @@ wxWidgets docs: -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. @@ -170,24 +131,18 @@ 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 external documentation -%% 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. @@ -206,8 +161,6 @@ 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, @@ -217,7 +170,6 @@ 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, diff --git a/lib/wx/src/gen/wxFileDataObject.erl b/lib/wx/src/gen/wxFileDataObject.erl index eca46c9ae3e9..c5227caaa529 100644 --- a/lib/wx/src/gen/wxFileDataObject.erl +++ b/lib/wx/src/gen/wxFileDataObject.erl @@ -20,21 +20,27 @@ -module(wxFileDataObject). -moduledoc """ -Functions for wxFileDataObject class +`m:wxFileDataObject` is a specialization of `m:wxDataObject` for file names. -`m:wxFileDataObject` is a specialization of `m:wxDataObject` for file names. The -program works with it just as if it were a list of absolute file names, but -internally it uses the same format as Explorer and other compatible programs -under Windows or GNOME/KDE file manager under Unix which makes it possible to -receive files from them using this class. +The program works with it just as if it were a list of absolute file names, but +internally it uses the same format as Explorer and other compatible programs under Windows +or GNOME/KDE file manager under Unix which makes it possible to receive files from them +using this class. -See: `m:wxDataObject`, `wxDataObjectSimple` (not implemented in wx), -`m:wxTextDataObject`, `m:wxBitmapDataObject`, `m:wxDataObject` +See: +* `m:wxDataObject` -This class is derived (and can use functions) from: `m:wxDataObject` +* `m:wxTextDataObject` -wxWidgets docs: -[wxFileDataObject](https://docs.wxwidgets.org/3.1/classwx_file_data_object.html) +* `m:wxBitmapDataObject` + +* `m:wxDataObject` + +This class is derived, and can use functions, from: + +* `m:wxDataObject` + +wxWidgets docs: [wxFileDataObject](https://docs.wxwidgets.org/3.2/classwx_file_data_object.html) """. -include("wxe.hrl"). -export([addFile/2,destroy/1,getFilenames/1,new/0]). @@ -44,19 +50,16 @@ wxWidgets docs: -type wxFileDataObject() :: wx:wx_object(). -export_type([wxFileDataObject/0]). -%% @hidden -doc false. parent_class(wxDataObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Constructor.". -spec new() -> wxFileDataObject(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFileDataObject_new), wxe_util:rec(?wxFileDataObject_new). -%% @doc See external documentation. -doc "Adds a file to the file list represented by this data object (Windows only).". -spec addFile(This, File) -> 'ok' when This::wxFileDataObject(), File::unicode:chardata(). @@ -66,7 +69,6 @@ addFile(#wx_ref{type=ThisT}=This,File) File_UC = unicode:characters_to_binary(File), wxe_util:queue_cmd(This,File_UC,?get_env(),?wxFileDataObject_AddFile). -%% @doc See external documentation. -doc "Returns the array of file names.". -spec getFilenames(This) -> [unicode:charlist()] when This::wxFileDataObject(). @@ -75,8 +77,7 @@ getFilenames(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDataObject_GetFilenames), wxe_util:rec(?wxFileDataObject_GetFilenames). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFileDataObject()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFileDataObject), diff --git a/lib/wx/src/gen/wxFileDialog.erl b/lib/wx/src/gen/wxFileDialog.erl index e6f8d5c0184a..2a324fdef3dc 100644 --- a/lib/wx/src/gen/wxFileDialog.erl +++ b/lib/wx/src/gen/wxFileDialog.erl @@ -20,51 +20,84 @@ -module(wxFileDialog). -moduledoc """ -Functions for wxFileDialog class - This class represents the file chooser dialog. The path and filename are distinct elements of a full file pathname. If path is -?wxEmptyString, the current directory will be used. If filename is -?wxEmptyString, no default filename will be supplied. The wildcard determines -what files are displayed in the file selector, and file extension supplies a -type extension for the required filename. +?wxEmptyString, the current directory will be used. If filename is ?wxEmptyString, no +default filename will be supplied. The wildcard determines what files are displayed in the +file selector, and file extension supplies a type extension for the required filename. The typical usage for the open file dialog is: The typical usage for the save file dialog is instead somewhat simpler: -Remark: All implementations of the `m:wxFileDialog` provide a wildcard filter. -Typing a filename containing wildcards (_, ?) in the filename text item, and -clicking on Ok, will result in only those files matching the pattern being -displayed. The wildcard may be a specification for multiple types of file with a -description for each, such as: It must be noted that wildcard support in the -native Motif file dialog is quite limited: only one file type is supported, and -it is displayed without the descriptive test; "BMP files (_.bmp)|_.bmp" is -displayed as "_.bmp", and both "BMP files (_.bmp)|_.bmp|GIF files (_.gif)|_.gif" -and "Image files|_.bmp;_.gif" are errors. On Mac macOS in the open file dialog -the filter choice box is not shown by default. Instead all given wildcards are -appplied at the same time: So in the above example all bmp, gif and png files -are displayed. To enforce the display of the filter choice set the corresponding -`m:wxSystemOptions` before calling the file open dialog: But in contrast to -Windows and Unix, where the file type choice filters only the selected files, on -Mac macOS even in this case the dialog shows all files matching all file types. -The files which does not match the currently selected file type are greyed out -and are not selectable. - -Styles +Remark: All implementations of the `m:wxFileDialog` provide a wildcard filter. Typing a +filename containing wildcards (*, ?) in the filename text item, and clicking on Ok, will +result in only those files matching the pattern being displayed. The wildcard may be a +specification for multiple types of file with a description for each, such as: It must be +noted that wildcard support in the native Motif file dialog is quite limited: only one +file type is supported, and it is displayed without the descriptive test; "BMP files +(*.bmp)|*.bmp" is displayed as "*.bmp", and both "BMP files (*.bmp)|*.bmp|GIF files +(*.gif)|*.gif" and "Image files|*.bmp;*.gif" are errors. On Mac macOS in the open file +dialog the filter choice box is not shown by default. Instead all given wildcards are +appplied at the same time: So in the above example all bmp, gif and png files are +displayed. To enforce the display of the filter choice set the corresponding `m:wxSystemOptions` +before calling the file open dialog: But in contrast to Windows and Unix, where the file +type choice filters only the selected files, on Mac macOS even in this case the dialog +shows all files matching all file types. The files which does not match the currently +selected file type are greyed out and are not selectable. + +## Styles This class supports the following styles: +* wxFD_DEFAULT_STYLE: Equivalent to `wxFD_OPEN`. + +* wxFD_OPEN: This is an open dialog; usually this means that the default button's label of +the dialog is "Open". Cannot be combined with `wxFD_SAVE`. + +* wxFD_SAVE: This is a save dialog; usually this means that the default button's label of +the dialog is "Save". Cannot be combined with `wxFD_OPEN`. + +* wxFD_OVERWRITE_PROMPT: For save dialog only: prompt for a confirmation if a file will be +overwritten. + +* wxFD_NO_FOLLOW: Directs the dialog to return the path and file name of the selected +shortcut file, not its target as it does by default. Currently this flag is only +implemented in wxMSW and wxOSX (where it prevents aliases from being resolved). The +non-dereferenced link path is always returned, even without this flag, under Unix and so +using it there doesn't do anything. This flag was added in wxWidgets 3.1.0. + +* wxFD_FILE_MUST_EXIST: For open dialog only: the user may only select files that actually +exist. Notice that under macOS the file dialog with `wxFD_OPEN` style always behaves as if +this style was specified, because it is impossible to choose a file that doesn't exist +from a standard macOS file dialog. + +* wxFD_MULTIPLE: For open dialog only: allows selecting multiple files. + +* wxFD_CHANGE_DIR: Change the current working directory (when the dialog is dismissed) to +the directory where the file(s) chosen by the user are. + +* wxFD_PREVIEW: Show the preview of the selected files (currently only supported by wxGTK). + +* wxFD_SHOW_HIDDEN: Show hidden files. This flag was added in wxWidgets 3.1.3 + See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_file), -?wxFileSelector() +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_file) + +* ?wxFileSelector() + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxFileDialog](https://docs.wxwidgets.org/3.1/classwx_file_dialog.html) +wxWidgets docs: [wxFileDialog](https://docs.wxwidgets.org/3.2/classwx_file_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getDirectory/1,getFilename/1,getFilenames/1,getFilterIndex/1, @@ -118,7 +151,6 @@ wxWidgets docs: -type wxFileDialog() :: wx:wx_object(). -export_type([wxFileDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -126,7 +158,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxFileDialog() when Parent::wxWindow:wxWindow(). @@ -134,7 +166,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ Constructor. @@ -164,7 +195,6 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxFileDialog_new), wxe_util:rec(?wxFileDialog_new). -%% @doc See external documentation. -doc "Returns the default directory.". -spec getDirectory(This) -> unicode:charlist() when This::wxFileDialog(). @@ -173,12 +203,11 @@ getDirectory(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetDirectory), wxe_util:rec(?wxFileDialog_GetDirectory). -%% @doc See external documentation. -doc """ Returns the default filename. -Note: This function can't be used with dialogs which have the `wxFD_MULTIPLE` -style, use `getFilenames/1` instead. +Note: This function can't be used with dialogs which have the `wxFD_MULTIPLE` style, use `getFilenames/1` +instead. """. -spec getFilename(This) -> unicode:charlist() when This::wxFileDialog(). @@ -187,16 +216,15 @@ getFilename(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetFilename), wxe_util:rec(?wxFileDialog_GetFilename). -%% @doc See external documentation. -doc """ Fills the array `filenames` with the names of the files chosen. -This function should only be used with the dialogs which have `wxFD_MULTIPLE` -style, use `getFilename/1` for the others. +This function should only be used with the dialogs which have `wxFD_MULTIPLE` style, use `getFilename/1` +for the others. -Note that under Windows, if the user selects shortcuts, the filenames include -paths, since the application cannot determine the full path of each referenced -file by appending the directory containing the shortcuts to the filename. +Note that under Windows, if the user selects shortcuts, the filenames include paths, +since the application cannot determine the full path of each referenced file by appending +the directory containing the shortcuts to the filename. """. -spec getFilenames(This) -> [unicode:charlist()] when This::wxFileDialog(). @@ -205,13 +233,11 @@ getFilenames(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetFilenames), wxe_util:rec(?wxFileDialog_GetFilenames). -%% @doc See external documentation. -doc """ Returns the index into the list of filters supplied, optionally, in the wildcard parameter. -Before the dialog is shown, this is the index which will be used when the dialog -is first displayed. +Before the dialog is shown, this is the index which will be used when the dialog is first displayed. After the dialog is shown, this is the index selected by the user. """. @@ -222,7 +248,6 @@ getFilterIndex(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetFilterIndex), wxe_util:rec(?wxFileDialog_GetFilterIndex). -%% @doc See external documentation. -doc "Returns the message that will be displayed on the dialog.". -spec getMessage(This) -> unicode:charlist() when This::wxFileDialog(). @@ -231,12 +256,11 @@ getMessage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetMessage), wxe_util:rec(?wxFileDialog_GetMessage). -%% @doc See external documentation. -doc """ Returns the full path (directory and filename) of the selected file. -Note: This function can't be used with dialogs which have the `wxFD_MULTIPLE` -style, use `getPaths/1` instead. +Note: This function can't be used with dialogs which have the `wxFD_MULTIPLE` style, use `getPaths/1` +instead. """. -spec getPath(This) -> unicode:charlist() when This::wxFileDialog(). @@ -245,12 +269,11 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetPath), wxe_util:rec(?wxFileDialog_GetPath). -%% @doc See external documentation. -doc """ Fills the array `paths` with the full paths of the files chosen. -This function should only be used with the dialogs which have `wxFD_MULTIPLE` -style, use `getPath/1` for the others. +This function should only be used with the dialogs which have `wxFD_MULTIPLE` style, use `getPath/1` +for the others. """. -spec getPaths(This) -> [unicode:charlist()] when This::wxFileDialog(). @@ -259,7 +282,6 @@ getPaths(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetPaths), wxe_util:rec(?wxFileDialog_GetPaths). -%% @doc See external documentation. -doc "Returns the file dialog wildcard.". -spec getWildcard(This) -> unicode:charlist() when This::wxFileDialog(). @@ -268,7 +290,6 @@ getWildcard(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFileDialog_GetWildcard), wxe_util:rec(?wxFileDialog_GetWildcard). -%% @doc See external documentation. -doc "Sets the default directory.". -spec setDirectory(This, Directory) -> 'ok' when This::wxFileDialog(), Directory::unicode:chardata(). @@ -278,12 +299,10 @@ setDirectory(#wx_ref{type=ThisT}=This,Directory) Directory_UC = unicode:characters_to_binary(Directory), wxe_util:queue_cmd(This,Directory_UC,?get_env(),?wxFileDialog_SetDirectory). -%% @doc See external documentation. -doc """ Sets the default filename. -In wxGTK this will have little effect unless a default directory has previously -been set. +In wxGTK this will have little effect unless a default directory has previously been set. """. -spec setFilename(This, Setfilename) -> 'ok' when This::wxFileDialog(), Setfilename::unicode:chardata(). @@ -293,7 +312,6 @@ setFilename(#wx_ref{type=ThisT}=This,Setfilename) Setfilename_UC = unicode:characters_to_binary(Setfilename), wxe_util:queue_cmd(This,Setfilename_UC,?get_env(),?wxFileDialog_SetFilename). -%% @doc See external documentation. -doc "Sets the default filter index, starting from zero.". -spec setFilterIndex(This, FilterIndex) -> 'ok' when This::wxFileDialog(), FilterIndex::integer(). @@ -302,7 +320,6 @@ setFilterIndex(#wx_ref{type=ThisT}=This,FilterIndex) ?CLASS(ThisT,wxFileDialog), wxe_util:queue_cmd(This,FilterIndex,?get_env(),?wxFileDialog_SetFilterIndex). -%% @doc See external documentation. -doc "Sets the message that will be displayed on the dialog.". -spec setMessage(This, Message) -> 'ok' when This::wxFileDialog(), Message::unicode:chardata(). @@ -312,10 +329,9 @@ setMessage(#wx_ref{type=ThisT}=This,Message) Message_UC = unicode:characters_to_binary(Message), wxe_util:queue_cmd(This,Message_UC,?get_env(),?wxFileDialog_SetMessage). -%% @doc See external documentation. -doc """ -Sets the path (the combined directory and filename that will be returned when -the dialog is dismissed). +Sets the path (the combined directory and filename that will be returned when the dialog +is dismissed). """. -spec setPath(This, Path) -> 'ok' when This::wxFileDialog(), Path::unicode:chardata(). @@ -325,13 +341,12 @@ setPath(#wx_ref{type=ThisT}=This,Path) Path_UC = unicode:characters_to_binary(Path), wxe_util:queue_cmd(This,Path_UC,?get_env(),?wxFileDialog_SetPath). -%% @doc See external documentation. -doc """ -Sets the wildcard, which can contain multiple file types, for example: "BMP -files (_.bmp)|_.bmp|GIF files (_.gif)|_.gif". +Sets the wildcard, which can contain multiple file types, for example: "BMP files +(\*.bmp)|\*.bmp|GIF files (\*.gif)|\*.gif". -Note that the native Motif dialog has some limitations with respect to -wildcards; see the Remarks section above. +Note that the native Motif dialog has some limitations with respect to wildcards; see the +Remarks section above. """. -spec setWildcard(This, WildCard) -> 'ok' when This::wxFileDialog(), WildCard::unicode:chardata(). @@ -341,659 +356,443 @@ setWildcard(#wx_ref{type=ThisT}=This,WildCard) WildCard_UC = unicode:characters_to_binary(WildCard), wxe_util:queue_cmd(This,WildCard_UC,?get_env(),?wxFileDialog_SetWildcard). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxFileDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFileDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxFileDirPickerEvent.erl b/lib/wx/src/gen/wxFileDirPickerEvent.erl index 1adba2d2b516..364e9331b652 100644 --- a/lib/wx/src/gen/wxFileDirPickerEvent.erl +++ b/lib/wx/src/gen/wxFileDirPickerEvent.erl @@ -20,24 +20,24 @@ -module(wxFileDirPickerEvent). -moduledoc """ -Functions for wxFileDirPickerEvent class +This event class is used for the events generated by `m:wxFilePickerCtrl` and by `m:wxDirPickerCtrl`. -This event class is used for the events generated by `m:wxFilePickerCtrl` and by -`m:wxDirPickerCtrl`. +See: +* `m:wxFilePickerCtrl` -See: `m:wxFilePickerCtrl`, `m:wxDirPickerCtrl` +* `m:wxDirPickerCtrl` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxFileDirPickerEvent](https://docs.wxwidgets.org/3.1/classwx_file_dir_picker_event.html) +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxFileDirPickerEvent](https://docs.wxwidgets.org/3.2/classwx_file_dir_picker_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxFileDirPickerEventType`](`t:wxFileDirPickerEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxFileDirPickerEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getPath/1]). @@ -52,13 +52,11 @@ events of this type. -include("wx.hrl"). -type wxFileDirPickerEventType() :: 'command_filepicker_changed' | 'command_dirpicker_changed'. -export_type([wxFileDirPickerEvent/0, wxFileDirPicker/0, wxFileDirPickerEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Retrieve the absolute path of the file/directory the user has just selected.". -spec getPath(This) -> unicode:charlist() when This::wxFileDirPickerEvent(). @@ -68,58 +66,40 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxFileDirPickerEvent_GetPath). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxFilePickerCtrl.erl b/lib/wx/src/gen/wxFilePickerCtrl.erl index ca9f357ac765..c644260f0766 100644 --- a/lib/wx/src/gen/wxFilePickerCtrl.erl +++ b/lib/wx/src/gen/wxFilePickerCtrl.erl @@ -20,30 +20,64 @@ -module(wxFilePickerCtrl). -moduledoc """ -Functions for wxFilePickerCtrl class +This control allows the user to select a file. -This control allows the user to select a file. The generic implementation is a -button which brings up a `m:wxFileDialog` when clicked. Native implementation -may differ but this is usually a (small) widget which give access to the -file-chooser dialog. It is only available if `wxUSE_FILEPICKERCTRL` is set to 1 -(the default). +The generic implementation is a button which brings up a `m:wxFileDialog` when clicked. +Native implementation may differ but this is usually a (small) widget which give access to +the file-chooser dialog. It is only available if `wxUSE_FILEPICKERCTRL` is set to 1 (the default). -Styles +## Styles This class supports the following styles: -See: `m:wxFileDialog`, `m:wxFileDirPickerEvent` +* wxFLP_DEFAULT_STYLE: The default style: includes wxFLP_OPEN | wxFLP_FILE_MUST_EXIST and, +under wxMSW and wxOSX, wxFLP_USE_TEXTCTRL. -This class is derived (and can use functions) from: `m:wxPickerBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* wxFLP_USE_TEXTCTRL: Creates a text control to the left of the picker button which is +completely managed by the `m:wxFilePickerCtrl` and which can be used by the user to +specify a path (see SetPath). The text control is automatically synchronized with button's +value. Use functions defined in `m:wxPickerBase` to modify the text control. -wxWidgets docs: -[wxFilePickerCtrl](https://docs.wxwidgets.org/3.1/classwx_file_picker_ctrl.html) +* wxFLP_OPEN: Creates a picker which allows the user to select a file to open. + +* wxFLP_SAVE: Creates a picker which allows the user to select a file to save. + +* wxFLP_OVERWRITE_PROMPT: Can be combined with wxFLP_SAVE only: ask confirmation to the +user before selecting a file. + +* wxFLP_FILE_MUST_EXIST: Can be combined with wxFLP_OPEN only: the file selected in the +popup `m:wxFileDialog` must be an existing file. Notice that it still remains possible for +the user to enter a non-existent file name in the text control if `wxFLP_USE_TEXTCTRL` is +also used, this flag is a hint for the user rather than a guarantee that the selected file +does exist for the program. + +* wxFLP_CHANGE_DIR: Change current working directory on each user file selection change. + +* wxFLP_SMALL: Use smaller version of the control with a small "..." button instead of the +normal "Browse" one. This flag is new since wxWidgets 2.9.3. + +See: +* `m:wxFileDialog` + +* `m:wxFileDirPickerEvent` + +This class is derived, and can use functions, from: + +* `m:wxPickerBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxFilePickerCtrl](https://docs.wxwidgets.org/3.2/classwx_file_picker_ctrl.html) ## Events Event types emitted from this class: -[`command_filepicker_changed`](`m:wxFileDirPickerEvent`) + +* [`command_filepicker_changed`](`m:wxFileDirPickerEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getPath/1,new/0,new/2,new/3,setPath/2]). @@ -93,7 +127,6 @@ Event types emitted from this class: -type wxFilePickerCtrl() :: wx:wx_object(). -export_type([wxFilePickerCtrl/0]). -%% @hidden -doc false. parent_class(wxPickerBase) -> true; parent_class(wxControl) -> true; @@ -101,13 +134,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxFilePickerCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFilePickerCtrl_new_0), wxe_util:rec(?wxFilePickerCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxFilePickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -115,7 +148,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Initializes the object and calls `create/4` with all the parameters.". -spec new(Parent, Id, [Option]) -> wxFilePickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -141,7 +173,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxFilePickerCtrl_new_3), wxe_util:rec(?wxFilePickerCtrl_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxFilePickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -149,12 +181,10 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Creates this widget with the given parameters. -Return: true if the control was successfully created or false if creation -failed. +Return: true if the control was successfully created or false if creation failed. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxFilePickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -181,7 +211,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxFilePickerCtrl_Create), wxe_util:rec(?wxFilePickerCtrl_Create). -%% @doc See external documentation. -doc "Returns the absolute path of the currently selected file.". -spec getPath(This) -> unicode:charlist() when This::wxFilePickerCtrl(). @@ -190,16 +219,14 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFilePickerCtrl_GetPath), wxe_util:rec(?wxFilePickerCtrl_GetPath). -%% @doc See external documentation. -doc """ Sets the absolute path of the currently selected file. -If the control uses `wxFLP_FILE_MUST_EXIST` and does not use -`wxFLP_USE_TEXTCTRL` style, the `filename` must be a name of an existing file -and will be simply ignored by the native wxGTK implementation if this is not the -case (the generic implementation used under the other platforms accepts even -invalid file names currently, but this is subject to change in the future, don't -rely on being able to use non-existent paths with it). +If the control uses `wxFLP_FILE_MUST_EXIST` and does not use `wxFLP_USE_TEXTCTRL` style, +the `filename` must be a name of an existing file and will be simply ignored by the native +wxGTK implementation if this is not the case (the generic implementation used under the +other platforms accepts even invalid file names currently, but this is subject to change +in the future, don't rely on being able to use non-existent paths with it). """. -spec setPath(This, Filename) -> 'ok' when This::wxFilePickerCtrl(), Filename::unicode:chardata(). @@ -209,605 +236,407 @@ setPath(#wx_ref{type=ThisT}=This,Filename) Filename_UC = unicode:characters_to_binary(Filename), wxe_util:queue_cmd(This,Filename_UC,?get_env(),?wxFilePickerCtrl_SetPath). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFilePickerCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFilePickerCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPickerBase -%% @hidden -doc false. isPickerCtrlGrowable(This) -> wxPickerBase:isPickerCtrlGrowable(This). -%% @hidden -doc false. setTextCtrlGrowable(This, Options) -> wxPickerBase:setTextCtrlGrowable(This, Options). -%% @hidden -doc false. setTextCtrlGrowable(This) -> wxPickerBase:setTextCtrlGrowable(This). -%% @hidden -doc false. setPickerCtrlGrowable(This, Options) -> wxPickerBase:setPickerCtrlGrowable(This, Options). -%% @hidden -doc false. setPickerCtrlGrowable(This) -> wxPickerBase:setPickerCtrlGrowable(This). -%% @hidden -doc false. isTextCtrlGrowable(This) -> wxPickerBase:isTextCtrlGrowable(This). -%% @hidden -doc false. getTextCtrl(This) -> wxPickerBase:getTextCtrl(This). -%% @hidden -doc false. hasTextCtrl(This) -> wxPickerBase:hasTextCtrl(This). -%% @hidden -doc false. getPickerCtrlProportion(This) -> wxPickerBase:getPickerCtrlProportion(This). -%% @hidden -doc false. getTextCtrlProportion(This) -> wxPickerBase:getTextCtrlProportion(This). -%% @hidden -doc false. setPickerCtrlProportion(This,Prop) -> wxPickerBase:setPickerCtrlProportion(This,Prop). -%% @hidden -doc false. setTextCtrlProportion(This,Prop) -> wxPickerBase:setTextCtrlProportion(This,Prop). -%% @hidden -doc false. getInternalMargin(This) -> wxPickerBase:getInternalMargin(This). -%% @hidden -doc false. setInternalMargin(This,Margin) -> wxPickerBase:setInternalMargin(This,Margin). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxFindReplaceData.erl b/lib/wx/src/gen/wxFindReplaceData.erl index d6ba97e4de73..13b7a390ea42 100644 --- a/lib/wx/src/gen/wxFindReplaceData.erl +++ b/lib/wx/src/gen/wxFindReplaceData.erl @@ -20,21 +20,17 @@ -module(wxFindReplaceData). -moduledoc """ -Functions for wxFindReplaceData class - `m:wxFindReplaceData` holds the data for `m:wxFindReplaceDialog`. -It is used to initialize the dialog with the default values and will keep the -last values from the dialog when it is closed. It is also updated each time a -`wxFindDialogEvent` (not implemented in wx) is generated so instead of using the -`wxFindDialogEvent` (not implemented in wx) methods you can also directly query -this object. +It is used to initialize the dialog with the default values and will keep the last values +from the dialog when it is closed. It is also updated each time a `wxFindDialogEvent` (not +implemented in wx) is generated so instead of using the `wxFindDialogEvent` (not +implemented in wx) methods you can also directly query this object. -Note that all `SetXXX()` methods may only be called before showing the dialog -and calling them has no effect later. +Note that all `SetXXX()` methods may only be called before showing the dialog and calling +them has no effect later. -wxWidgets docs: -[wxFindReplaceData](https://docs.wxwidgets.org/3.1/classwx_find_replace_data.html) +wxWidgets docs: [wxFindReplaceData](https://docs.wxwidgets.org/3.2/classwx_find_replace_data.html) """. -include("wxe.hrl"). -export([destroy/1,getFindString/1,getFlags/1,getReplaceString/1,new/0,new/1, @@ -45,17 +41,15 @@ wxWidgets docs: -type wxFindReplaceData() :: wx:wx_object(). -export_type([wxFindReplaceData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxFindReplaceData(). new() -> new([]). -%% @doc See external documentation. -doc "Constructor initializes the flags to default value (0).". -spec new([Option]) -> wxFindReplaceData() when Option :: {'flags', integer()}. @@ -67,7 +61,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxFindReplaceData_new), wxe_util:rec(?wxFindReplaceData_new). -%% @doc See external documentation. -doc "Get the string to find.". -spec getFindString(This) -> unicode:charlist() when This::wxFindReplaceData(). @@ -76,7 +69,6 @@ getFindString(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFindReplaceData_GetFindString), wxe_util:rec(?wxFindReplaceData_GetFindString). -%% @doc See external documentation. -doc "Get the replacement string.". -spec getReplaceString(This) -> unicode:charlist() when This::wxFindReplaceData(). @@ -85,7 +77,6 @@ getReplaceString(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFindReplaceData_GetReplaceString), wxe_util:rec(?wxFindReplaceData_GetReplaceString). -%% @doc See external documentation. -doc "Get the combination of `wxFindReplaceFlags` values.". -spec getFlags(This) -> integer() when This::wxFindReplaceData(). @@ -94,7 +85,6 @@ getFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFindReplaceData_GetFlags), wxe_util:rec(?wxFindReplaceData_GetFlags). -%% @doc See external documentation. -doc "Set the flags to use to initialize the controls of the dialog.". -spec setFlags(This, Flags) -> 'ok' when This::wxFindReplaceData(), Flags::integer(). @@ -103,7 +93,6 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxFindReplaceData), wxe_util:queue_cmd(This,Flags,?get_env(),?wxFindReplaceData_SetFlags). -%% @doc See external documentation. -doc "Set the string to find (used as initial value by the dialog).". -spec setFindString(This, Str) -> 'ok' when This::wxFindReplaceData(), Str::unicode:chardata(). @@ -113,7 +102,6 @@ setFindString(#wx_ref{type=ThisT}=This,Str) Str_UC = unicode:characters_to_binary(Str), wxe_util:queue_cmd(This,Str_UC,?get_env(),?wxFindReplaceData_SetFindString). -%% @doc See external documentation. -doc "Set the replacement string (used as initial value by the dialog).". -spec setReplaceString(This, Str) -> 'ok' when This::wxFindReplaceData(), Str::unicode:chardata(). @@ -123,8 +111,7 @@ setReplaceString(#wx_ref{type=ThisT}=This,Str) Str_UC = unicode:characters_to_binary(Str), wxe_util:queue_cmd(This,Str_UC,?get_env(),?wxFindReplaceData_SetReplaceString). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFindReplaceData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFindReplaceData), diff --git a/lib/wx/src/gen/wxFindReplaceDialog.erl b/lib/wx/src/gen/wxFindReplaceDialog.erl index 14a04877bed8..f849a948bd28 100644 --- a/lib/wx/src/gen/wxFindReplaceDialog.erl +++ b/lib/wx/src/gen/wxFindReplaceDialog.erl @@ -20,24 +20,27 @@ -module(wxFindReplaceDialog). -moduledoc """ -Functions for wxFindReplaceDialog class +`m:wxFindReplaceDialog` is a standard modeless dialog which is used to allow the user to +search for some text (and possibly replace it with something else). -`m:wxFindReplaceDialog` is a standard modeless dialog which is used to allow the -user to search for some text (and possibly replace it with something else). - -The actual searching is supposed to be done in the owner window which is the -parent of this dialog. Note that it means that unlike for the other standard -dialogs this one `must` have a parent window. Also note that there is no way to -use this dialog in a modal way; it is always, by design and implementation, -modeless. +The actual searching is supposed to be done in the owner window which is the parent of +this dialog. Note that it means that unlike for the other standard dialogs this one `must` +have a parent window. Also note that there is no way to use this dialog in a modal way; it +is always, by design and implementation, modeless. Please see the page_samples_dialogs sample for an example of using it. -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` -wxWidgets docs: -[wxFindReplaceDialog](https://docs.wxwidgets.org/3.1/classwx_find_replace_dialog.html) +wxWidgets docs: [wxFindReplaceDialog](https://docs.wxwidgets.org/3.2/classwx_find_replace_dialog.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getData/1,new/0,new/3,new/4]). @@ -89,7 +92,6 @@ wxWidgets docs: -type wxFindReplaceDialog() :: wx:wx_object(). -export_type([wxFindReplaceDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -97,13 +99,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxFindReplaceDialog(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFindReplaceDialog_new_0), wxe_util:rec(?wxFindReplaceDialog_new_0). -%% @equiv new(Parent,Data,Title, []) +-doc(#{equiv => new(Parent,Data,Title, [])}). -spec new(Parent, Data, Title) -> wxFindReplaceDialog() when Parent::wxWindow:wxWindow(), Data::wxFindReplaceData:wxFindReplaceData(), Title::unicode:chardata(). @@ -111,7 +113,6 @@ new(Parent,Data,Title) when is_record(Parent, wx_ref),is_record(Data, wx_ref),?is_chardata(Title) -> new(Parent,Data,Title, []). -%% @doc See external documentation. -doc """ After using default constructor `create/5` must be called. @@ -131,7 +132,7 @@ new(#wx_ref{type=ParentT}=Parent,#wx_ref{type=DataT}=Data,Title, Options) wxe_util:queue_cmd(Parent,Data,Title_UC, Opts,?get_env(),?wxFindReplaceDialog_new_4), wxe_util:rec(?wxFindReplaceDialog_new_4). -%% @equiv create(This,Parent,Data,Title, []) +-doc(#{equiv => create(This,Parent,Data,Title, [])}). -spec create(This, Parent, Data, Title) -> boolean() when This::wxFindReplaceDialog(), Parent::wxWindow:wxWindow(), Data::wxFindReplaceData:wxFindReplaceData(), Title::unicode:chardata(). @@ -139,7 +140,6 @@ create(This,Parent,Data,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_record(Data, wx_ref),?is_chardata(Title) -> create(This,Parent,Data,Title, []). -%% @doc See external documentation. -doc """ Creates the dialog; use `wxWindow:show/2` to show it on screen. @@ -160,7 +160,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,#wx_ref{type=DataT} wxe_util:queue_cmd(This,Parent,Data,Title_UC, Opts,?get_env(),?wxFindReplaceDialog_Create), wxe_util:rec(?wxFindReplaceDialog_Create). -%% @doc See external documentation. -doc "Get the `m:wxFindReplaceData` object used by this dialog.". -spec getData(This) -> wxFindReplaceData:wxFindReplaceData() when This::wxFindReplaceDialog(). @@ -169,659 +168,443 @@ getData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFindReplaceDialog_GetData), wxe_util:rec(?wxFindReplaceDialog_GetData). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxFindReplaceDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFindReplaceDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxFlexGridSizer.erl b/lib/wx/src/gen/wxFlexGridSizer.erl index bd9ad1ff8b93..7eac36ecc058 100644 --- a/lib/wx/src/gen/wxFlexGridSizer.erl +++ b/lib/wx/src/gen/wxFlexGridSizer.erl @@ -20,27 +20,28 @@ -module(wxFlexGridSizer). -moduledoc """ -Functions for wxFlexGridSizer class +A flex grid sizer is a sizer which lays out its children in a two-dimensional table with +all table fields in one row having the same height and all fields in one column having the +same width, but all rows or all columns are not necessarily the same height or width as in +the `m:wxGridSizer`. -A flex grid sizer is a sizer which lays out its children in a two-dimensional -table with all table fields in one row having the same height and all fields in -one column having the same width, but all rows or all columns are not -necessarily the same height or width as in the `m:wxGridSizer`. +Since wxWidgets 2.5.0, `m:wxFlexGridSizer` can also size items equally in one direction +but unequally ("flexibly") in the other. If the sizer is only flexible in one direction +(this can be changed using `setFlexibleDirection/2`), it needs to be decided how the sizer should grow in the other +("non-flexible") direction in order to fill the available space. The `setNonFlexibleGrowMode/2` method serves this purpose. -Since wxWidgets 2.5.0, `m:wxFlexGridSizer` can also size items equally in one -direction but unequally ("flexibly") in the other. If the sizer is only flexible -in one direction (this can be changed using `setFlexibleDirection/2`), it needs -to be decided how the sizer should grow in the other ("non-flexible") direction -in order to fill the available space. The `setNonFlexibleGrowMode/2` method -serves this purpose. +See: +* `m:wxSizer` -See: `m:wxSizer`, -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer) +* [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) -This class is derived (and can use functions) from: `m:wxGridSizer` `m:wxSizer` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxFlexGridSizer](https://docs.wxwidgets.org/3.1/classwx_flex_grid_sizer.html) +* `m:wxGridSizer` + +* `m:wxSizer` + +wxWidgets docs: [wxFlexGridSizer](https://docs.wxwidgets.org/3.2/classwx_flex_grid_sizer.html) """. -include("wxe.hrl"). -export([addGrowableCol/2,addGrowableCol/3,addGrowableRow/2,addGrowableRow/3, @@ -62,13 +63,12 @@ wxWidgets docs: -type wxFlexGridSizer() :: wx:wx_object(). -export_type([wxFlexGridSizer/0]). -%% @hidden -doc false. parent_class(wxGridSizer) -> true; parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Cols, []) +-doc(#{equiv => new(Cols, [])}). -spec new(Cols) -> wxFlexGridSizer() when Cols::integer(). @@ -76,7 +76,7 @@ new(Cols) when is_integer(Cols) -> new(Cols, []). -%% @doc See external documentation. +-doc "". -spec new(Cols, [Option]) -> wxFlexGridSizer() when Cols::integer(), Option :: {'gap', {W::integer(), H::integer()}}. @@ -88,11 +88,7 @@ new(Cols, Options) wxe_util:queue_cmd(Cols, Opts,?get_env(),?wxFlexGridSizer_new_2), wxe_util:rec(?wxFlexGridSizer_new_2). -%% @doc See external documentation. -%%
Also:
-%% new(Rows, Cols, Gap) -> wxFlexGridSizer() when
-%% Rows::integer(), Cols::integer(), Gap::{W::integer(), H::integer()}.
-%% +-doc "". -spec new(Cols, Vgap, Hgap) -> wxFlexGridSizer() when Cols::integer(), Vgap::integer(), Hgap::integer(); (Rows, Cols, Gap) -> wxFlexGridSizer() when @@ -106,7 +102,7 @@ new(Rows,Cols,{GapW,GapH} = Gap) wxe_util:queue_cmd(Rows,Cols,Gap,?get_env(),?wxFlexGridSizer_new_3_1), wxe_util:rec(?wxFlexGridSizer_new_3_1). -%% @doc See external documentation. +-doc "". -spec new(Rows, Cols, Vgap, Hgap) -> wxFlexGridSizer() when Rows::integer(), Cols::integer(), Vgap::integer(), Hgap::integer(). new(Rows,Cols,Vgap,Hgap) @@ -114,7 +110,7 @@ new(Rows,Cols,Vgap,Hgap) wxe_util:queue_cmd(Rows,Cols,Vgap,Hgap,?get_env(),?wxFlexGridSizer_new_4), wxe_util:rec(?wxFlexGridSizer_new_4). -%% @equiv addGrowableCol(This,Idx, []) +-doc(#{equiv => addGrowableCol(This,Idx, [])}). -spec addGrowableCol(This, Idx) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(). @@ -122,19 +118,18 @@ addGrowableCol(This,Idx) when is_record(This, wx_ref),is_integer(Idx) -> addGrowableCol(This,Idx, []). -%% @doc See external documentation. -doc """ -Specifies that column `idx` (starting from zero) should be grown if there is -extra space available to the sizer. +Specifies that column `idx` (starting from zero) should be grown if there is extra space +available to the sizer. -The `proportion` parameter has the same meaning as the stretch factor for the -sizers (see `m:wxBoxSizer`) except that if all proportions are 0, then all -columns are resized equally (instead of not being resized at all). +The `proportion` parameter has the same meaning as the stretch factor for the sizers (see `m:wxBoxSizer`) +except that if all proportions are 0, then all columns are resized equally (instead of not +being resized at all). -Notice that the column must not be already growable, if you need to change the -proportion you must call `removeGrowableCol/2` first and then make it growable -(with a different proportion) again. You can use `IsColGrowable()` (not -implemented in wx) to check whether a column is already growable. +Notice that the column must not be already growable, if you need to change the proportion +you must call `removeGrowableCol/2` first and then make it growable (with a different proportion) again. You +can use `IsColGrowable()` (not implemented in wx) to check whether a column is already +growable. """. -spec addGrowableCol(This, Idx, [Option]) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(), @@ -147,7 +142,7 @@ addGrowableCol(#wx_ref{type=ThisT}=This,Idx, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Idx, Opts,?get_env(),?wxFlexGridSizer_AddGrowableCol). -%% @equiv addGrowableRow(This,Idx, []) +-doc(#{equiv => addGrowableRow(This,Idx, [])}). -spec addGrowableRow(This, Idx) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(). @@ -155,13 +150,11 @@ addGrowableRow(This,Idx) when is_record(This, wx_ref),is_integer(Idx) -> addGrowableRow(This,Idx, []). -%% @doc See external documentation. -doc """ -Specifies that row idx (starting from zero) should be grown if there is extra -space available to the sizer. +Specifies that row idx (starting from zero) should be grown if there is extra space +available to the sizer. -This is identical to `addGrowableCol/3` except that it works with rows and not -columns. +This is identical to `addGrowableCol/3` except that it works with rows and not columns. """. -spec addGrowableRow(This, Idx, [Option]) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(), @@ -174,13 +167,18 @@ addGrowableRow(#wx_ref{type=ThisT}=This,Idx, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Idx, Opts,?get_env(),?wxFlexGridSizer_AddGrowableRow). -%% @doc See external documentation. -doc """ -Returns a ?wxOrientation value that specifies whether the sizer flexibly resizes -its columns, rows, or both (default). +Returns a ?wxOrientation value that specifies whether the sizer flexibly resizes its +columns, rows, or both (default). Return: One of the following values: +* wxVERTICAL: Rows are flexibly sized. + +* wxHORIZONTAL: Columns are flexibly sized. + +* wxBOTH: Both rows and columns are flexibly sized (this is the default value). + See: `setFlexibleDirection/2` """. -spec getFlexibleDirection(This) -> integer() when @@ -190,23 +188,32 @@ getFlexibleDirection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFlexGridSizer_GetFlexibleDirection), wxe_util:rec(?wxFlexGridSizer_GetFlexibleDirection). -%% @doc See external documentation. -%%
Res = ?wxFLEX_GROWMODE_NONE | ?wxFLEX_GROWMODE_SPECIFIED | ?wxFLEX_GROWMODE_ALL -doc """ -Returns the value that specifies how the sizer grows in the "non-flexible" -direction if there is one. +Returns the value that specifies how the sizer grows in the "non-flexible" direction if +there is one. -The behaviour of the elements in the flexible direction (i.e. both rows and -columns by default, or rows only if `getFlexibleDirection/1` is `wxVERTICAL` or -columns only if it is `wxHORIZONTAL`) is always governed by their proportion as -specified in the call to `addGrowableRow/3` or `addGrowableCol/3`. What happens -in the other direction depends on the value of returned by this function as -described below. +The behaviour of the elements in the flexible direction (i.e. both rows and columns by +default, or rows only if `getFlexibleDirection/1` is `wxVERTICAL` or columns only if it is `wxHORIZONTAL`) is +always governed by their proportion as specified in the call to `addGrowableRow/3` or `addGrowableCol/3`. What happens in the +other direction depends on the value of returned by this function as described below. Return: One of the following values: -See: `setFlexibleDirection/2`, `setNonFlexibleGrowMode/2` +* wxFLEX_GROWMODE_NONE: Sizer doesn't grow its elements at all in the non-flexible direction. + +* wxFLEX_GROWMODE_SPECIFIED: Sizer honors growable columns/rows set with `addGrowableCol/3` and `addGrowableRow/3` in the +non-flexible direction as well. In this case equal sizing applies to minimum sizes of +columns or rows (this is the default value). + +* wxFLEX_GROWMODE_ALL: Sizer equally stretches all columns or rows in the non-flexible +direction, independently of the proportions applied in the flexible direction. + +See: +* `setFlexibleDirection/2` + +* `setNonFlexibleGrowMode/2` """. +%% Res = ?wxFLEX_GROWMODE_NONE | ?wxFLEX_GROWMODE_SPECIFIED | ?wxFLEX_GROWMODE_ALL -spec getNonFlexibleGrowMode(This) -> wx:wx_enum() when This::wxFlexGridSizer(). getNonFlexibleGrowMode(#wx_ref{type=ThisT}=This) -> @@ -214,7 +221,6 @@ getNonFlexibleGrowMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFlexGridSizer_GetNonFlexibleGrowMode), wxe_util:rec(?wxFlexGridSizer_GetNonFlexibleGrowMode). -%% @doc See external documentation. -doc "Specifies that the `idx` column index is no longer growable.". -spec removeGrowableCol(This, Idx) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(). @@ -223,7 +229,6 @@ removeGrowableCol(#wx_ref{type=ThisT}=This,Idx) ?CLASS(ThisT,wxFlexGridSizer), wxe_util:queue_cmd(This,Idx,?get_env(),?wxFlexGridSizer_RemoveGrowableCol). -%% @doc See external documentation. -doc "Specifies that the `idx` row index is no longer growable.". -spec removeGrowableRow(This, Idx) -> 'ok' when This::wxFlexGridSizer(), Idx::integer(). @@ -232,15 +237,14 @@ removeGrowableRow(#wx_ref{type=ThisT}=This,Idx) ?CLASS(ThisT,wxFlexGridSizer), wxe_util:queue_cmd(This,Idx,?get_env(),?wxFlexGridSizer_RemoveGrowableRow). -%% @doc See external documentation. -doc """ Specifies whether the sizer should flexibly resize its columns, rows, or both. -Argument `direction` can be `wxVERTICAL`, `wxHORIZONTAL` or `wxBOTH` (which is -the default value). Any other value is ignored. +Argument `direction` can be `wxVERTICAL`, `wxHORIZONTAL` or `wxBOTH` (which is the +default value). Any other value is ignored. -See `getFlexibleDirection/1` for the explanation of these values. Note that this -method does not trigger relayout. +See `getFlexibleDirection/1` for the explanation of these values. Note that this method does not trigger +relayout. """. -spec setFlexibleDirection(This, Direction) -> 'ok' when This::wxFlexGridSizer(), Direction::integer(). @@ -249,16 +253,14 @@ setFlexibleDirection(#wx_ref{type=ThisT}=This,Direction) ?CLASS(ThisT,wxFlexGridSizer), wxe_util:queue_cmd(This,Direction,?get_env(),?wxFlexGridSizer_SetFlexibleDirection). -%% @doc See external documentation. -%%
Mode = ?wxFLEX_GROWMODE_NONE | ?wxFLEX_GROWMODE_SPECIFIED | ?wxFLEX_GROWMODE_ALL -doc """ -Specifies how the sizer should grow in the non-flexible direction if there is -one (so `setFlexibleDirection/2` must have been called previously). +Specifies how the sizer should grow in the non-flexible direction if there is one (so `setFlexibleDirection/2` +must have been called previously). -Argument `mode` can be one of those documented in `getNonFlexibleGrowMode/1`, -please see there for their explanation. Note that this method does not trigger -relayout. +Argument `mode` can be one of those documented in `getNonFlexibleGrowMode/1`, please see there for their +explanation. Note that this method does not trigger relayout. """. +%% Mode = ?wxFLEX_GROWMODE_NONE | ?wxFLEX_GROWMODE_SPECIFIED | ?wxFLEX_GROWMODE_ALL -spec setNonFlexibleGrowMode(This, Mode) -> 'ok' when This::wxFlexGridSizer(), Mode::wx:wx_enum(). setNonFlexibleGrowMode(#wx_ref{type=ThisT}=This,Mode) @@ -266,183 +268,125 @@ setNonFlexibleGrowMode(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxFlexGridSizer), wxe_util:queue_cmd(This,Mode,?get_env(),?wxFlexGridSizer_SetNonFlexibleGrowMode). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFlexGridSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFlexGridSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxGridSizer -%% @hidden -doc false. setVGap(This,Gap) -> wxGridSizer:setVGap(This,Gap). -%% @hidden -doc false. setRows(This,Rows) -> wxGridSizer:setRows(This,Rows). -%% @hidden -doc false. setHGap(This,Gap) -> wxGridSizer:setHGap(This,Gap). -%% @hidden -doc false. setCols(This,Cols) -> wxGridSizer:setCols(This,Cols). -%% @hidden -doc false. getVGap(This) -> wxGridSizer:getVGap(This). -%% @hidden -doc false. getRows(This) -> wxGridSizer:getRows(This). -%% @hidden -doc false. getHGap(This) -> wxGridSizer:getHGap(This). -%% @hidden -doc false. getCols(This) -> wxGridSizer:getCols(This). %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. calcMin(This) -> wxSizer:calcMin(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). -%% @hidden -doc false. add(This,Width,Height, Options) -> wxSizer:add(This,Width,Height, Options). -%% @hidden -doc false. add(This,Width,Height) -> wxSizer:add(This,Width,Height). -%% @hidden -doc false. add(This,Window) -> wxSizer:add(This,Window). diff --git a/lib/wx/src/gen/wxFocusEvent.erl b/lib/wx/src/gen/wxFocusEvent.erl index 1852fc4b0a6e..f1e2f2a5b1e8 100644 --- a/lib/wx/src/gen/wxFocusEvent.erl +++ b/lib/wx/src/gen/wxFocusEvent.erl @@ -20,36 +20,31 @@ -module(wxFocusEvent). -moduledoc """ -Functions for wxFocusEvent class +A focus event is sent when a window's focus changes. -A focus event is sent when a window's focus changes. The window losing focus -receives a "kill focus" event while the window gaining it gets a "set focus" -one. +The window losing focus receives a "kill focus" event while the window gaining it gets a +"set focus" one. -Notice that the set focus event happens both when the user gives focus to the -window (whether using the mouse or keyboard) and when it is done from the -program itself using `wxWindow:setFocus/1`. +Notice that the set focus event happens both when the user gives focus to the window +(whether using the mouse or keyboard) and when it is done from the program itself using `wxWindow:setFocus/1`. -The focus event handlers should almost invariably call `wxEvent:skip/2` on their -event argument to allow the default handling to take place. Failure to do this -may result in incorrect behaviour of the native controls. Also note that -wxEVT_KILL_FOCUS handler must not call `wxWindow:setFocus/1` as this, again, is -not supported by all native controls. If you need to do this, consider using the -`Delayed Action Mechanism` (not implemented in wx) described in `m:wxIdleEvent` -documentation. +The focus event handlers should almost invariably call `wxEvent:skip/2` on their event argument to allow +the default handling to take place. Failure to do this may result in incorrect behaviour +of the native controls. Also note that wxEVT_KILL_FOCUS handler must not call `wxWindow:setFocus/1` as this, +again, is not supported by all native controls. If you need to do this, consider using the `Delayed Action Mechanism` +(not implemented in wx) described in `m:wxIdleEvent` documentation. -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxFocusEvent](https://docs.wxwidgets.org/3.1/classwx_focus_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxFocusEvent](https://docs.wxwidgets.org/3.2/classwx_focus_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxFocusEventType`](`t:wxFocusEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxFocusEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getWindow/1]). @@ -62,18 +57,16 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxFocusEventType() :: 'set_focus' | 'kill_focus'. -export_type([wxFocusEvent/0, wxFocus/0, wxFocusEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns the window associated with this event, that is the window which had the -focus before for the `wxEVT_SET_FOCUS` event and the window which is going to -receive focus for the `wxEVT_KILL_FOCUS` one. +Returns the window associated with this event, that is the window which had the focus +before for the `wxEVT\_SET\_FOCUS` event and the window which is going to receive focus +for the `wxEVT\_KILL\_FOCUS` one. -Warning: the window pointer may be NULL\! +Warning: the window pointer may be NULL! """. -spec getWindow(This) -> wxWindow:wxWindow() when This::wxFocusEvent(). @@ -83,30 +76,21 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxFocusEvent_GetWindow). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxFont.erl b/lib/wx/src/gen/wxFont.erl index 91908b740fc7..beefb3e590de 100644 --- a/lib/wx/src/gen/wxFont.erl +++ b/lib/wx/src/gen/wxFont.erl @@ -20,38 +20,42 @@ -module(wxFont). -moduledoc """ -Functions for wxFont class - A font is an object which determines the appearance of text. -Fonts are used for drawing text to a device context, and setting the appearance -of a window's text, see `wxDC:setFont/2` and `wxWindow:setFont/2`. +Fonts are used for drawing text to a device context, and setting the appearance of a +window's text, see `wxDC:setFont/2` and `wxWindow:setFont/2`. -The easiest way to create a custom font is to use `wxFontInfo` (not implemented -in wx) object to specify the font attributes and then use `new/5` constructor. -Alternatively, you could start with one of the pre-defined fonts or use -`wxWindow:getFont/1` and modify the font, e.g. by increasing its size using -`MakeLarger()` (not implemented in wx) or changing its weight using `MakeBold()` +The easiest way to create a custom font is to use `wxFontInfo` (not implemented in wx) +object to specify the font attributes and then use `new/5` constructor. Alternatively, you could +start with one of the pre-defined fonts or use `wxWindow:getFont/1` and modify the font, e.g. by increasing +its size using `MakeLarger()` (not implemented in wx) or changing its weight using `MakeBold()` (not implemented in wx). -This class uses reference counting and copy-on-write internally so that -assignments between two instances of this class are very cheap. You can -therefore use actual objects instead of pointers without efficiency problems. If -an instance of this class is changed it will create its own data internally so -that other instances, which previously shared the data using the reference -counting, are not affected. +This class uses reference counting and copy-on-write internally so that assignments +between two instances of this class are very cheap. You can therefore use actual objects +instead of pointers without efficiency problems. If an instance of this class is changed +it will create its own data internally so that other instances, which previously shared +the data using the reference counting, are not affected. You can retrieve the current system font settings with `m:wxSystemSettings`. -Predefined objects (include wx.hrl): ?wxNullFont, ?wxNORMAL_FONT, ?wxSMALL_FONT, -?wxITALIC_FONT, ?wxSWISS_FONT +Predefined objects (include wx.hrl): ?wxNullFont, ?wxNORMAL\_FONT, ?wxSMALL\_FONT, +?wxITALIC\_FONT, ?wxSWISS\_FONT See: -[Overview font](https://docs.wxwidgets.org/3.1/overview_font.html#overview_font), -`wxDC:setFont/2`, `wxDC:drawText/3`, `wxDC:getTextExtent/3`, `m:wxFontDialog`, -`m:wxSystemSettings` +* [Overview font](https://docs.wxwidgets.org/3.2/overview_font.html#overview_font) + +* `wxDC:setFont/2` + +* `wxDC:drawText/3` + +* `wxDC:getTextExtent/3` + +* `m:wxFontDialog` -wxWidgets docs: [wxFont](https://docs.wxwidgets.org/3.1/classwx_font.html) +* `m:wxSystemSettings` + +wxWidgets docs: [wxFont](https://docs.wxwidgets.org/3.2/classwx_font.html) """. -include("wxe.hrl"). -export([destroy/1,getDefaultEncoding/0,getFaceName/1,getFamily/1,getNativeFontInfoDesc/1, @@ -65,22 +69,15 @@ wxWidgets docs: [wxFont](https://docs.wxwidgets.org/3.1/classwx_font.html) -type wxFont() :: wx:wx_object(). -export_type([wxFont/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxFont(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFont_new_0), wxe_util:rec(?wxFont_new_0). -%% @doc See external documentation. -%%
Also:
-%% new(Font) -> wxFont() when
-%% Font::wxFont().
-%% -doc "Copy constructor, uses reference counting.". -spec new(NativeInfoString) -> wxFont() when NativeInfoString::unicode:chardata(); @@ -96,15 +93,11 @@ new(#wx_ref{type=FontT}=Font) -> wxe_util:queue_cmd(Font,?get_env(),?wxFont_new_1_1), wxe_util:rec(?wxFont_new_1_1). -%% @doc See external documentation. -%%
Also:
-%% new(PixelSize, Family, Style, Weight) -> wxFont() when
-%% PixelSize::{W::integer(), H::integer()}, Family::wx:wx_enum(), Style::wx:wx_enum(), Weight::wx:wx_enum().
-%% -%%
Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -%%
Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -%%
Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -%%
Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX +-doc "Equivalent to: `new/5`". +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE +%% Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN +%% Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX +%% Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec new(PointSize, Family, Style, Weight) -> wxFont() when PointSize::integer(), Family::wx:wx_enum(), Style::wx:wx_enum(), Weight::wx:wx_enum(); (PixelSize, Family, Style, Weight) -> wxFont() when @@ -118,28 +111,20 @@ new({PixelSizeW,PixelSizeH} = PixelSize,Family,Style,Weight) when is_integer(PixelSizeW),is_integer(PixelSizeH),is_integer(Family),is_integer(Style),is_integer(Weight) -> new(PixelSize,Family,Style,Weight, []). -%% @doc See external documentation. -%%
Also:
-%% new(PixelSize, Family, Style, Weight, [Option]) -> wxFont() when
-%% PixelSize::{W::integer(), H::integer()}, Family::wx:wx_enum(), Style::wx:wx_enum(), Weight::wx:wx_enum(),
-%% Option :: {'underline', boolean()}
-%% | {'faceName', unicode:chardata()}
-%% | {'encoding', wx:wx_enum()}.
-%% -%%
Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -%%
Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -%%
Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -%%
Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -doc """ Creates a font object with the specified attributes and size in pixels. -Notice that the use of this constructor is often more verbose and less readable -than the use of constructor from `wxFontInfo` (not implemented in wx), consider -using that constructor instead. +Notice that the use of this constructor is often more verbose and less readable than the +use of constructor from `wxFontInfo` (not implemented in wx), consider using that +constructor instead. -Remark: If the desired font does not exist, the closest match will be chosen. -Under Windows, only scalable TrueType fonts are used. +Remark: If the desired font does not exist, the closest match will be chosen. Under +Windows, only scalable TrueType fonts are used. """. +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE +%% Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN +%% Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX +%% Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec new(PointSize, Family, Style, Weight, [Option]) -> wxFont() when PointSize::integer(), Family::wx:wx_enum(), Style::wx:wx_enum(), Weight::wx:wx_enum(), Option :: {'underlined', boolean()} @@ -169,15 +154,13 @@ new({PixelSizeW,PixelSizeH} = PixelSize,Family,Style,Weight, Options) wxe_util:queue_cmd(PixelSize,Family,Style,Weight, Opts,?get_env(),?wxFont_new_5_1), wxe_util:rec(?wxFont_new_5_1). -%% @doc See external documentation. -doc """ Returns true if the font is a fixed width (or monospaced) font, false if it is a proportional one or font is invalid. -Note that this function under some platforms is different from just testing for -the font family being equal to `wxFONTFAMILY_TELETYPE` because native -platform-specific functions are used for the check (resulting in a more accurate -return value). +Note that this function under some platforms is different from just testing for the font +family being equal to `wxFONTFAMILY_TELETYPE` because native platform-specific functions +are used for the check (resulting in a more accurate return value). """. -spec isFixedWidth(This) -> boolean() when This::wxFont(). @@ -186,24 +169,23 @@ isFixedWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_IsFixedWidth), wxe_util:rec(?wxFont_IsFixedWidth). -%% @doc See external documentation. -%%
Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc """ Returns the current application's default encoding. See: -[Overview fontencoding](https://docs.wxwidgets.org/3.1/overview_fontencoding.html#overview_fontencoding), -`setDefaultEncoding/1` +* [Overview fontencoding](https://docs.wxwidgets.org/3.2/overview_fontencoding.html#overview_fontencoding) + +* `setDefaultEncoding/1` """. +%% Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec getDefaultEncoding() -> wx:wx_enum(). getDefaultEncoding() -> wxe_util:queue_cmd(?get_env(), ?wxFont_GetDefaultEncoding), wxe_util:rec(?wxFont_GetDefaultEncoding). -%% @doc See external documentation. -doc """ -Returns the face name associated with the font, or the empty string if there is -no face information. +Returns the face name associated with the font, or the empty string if there is no face +information. See: `setFaceName/2` """. @@ -214,23 +196,21 @@ getFaceName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetFaceName), wxe_util:rec(?wxFont_GetFaceName). -%% @doc See external documentation. -%%
Res = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -doc """ Gets the font family if possible. As described in ?wxFontFamily docs the returned value acts as a rough, basic classification of the main font properties (look, spacing). -If the current font face name is not recognized by `m:wxFont` or by the -underlying system, `wxFONTFAMILY_DEFAULT` is returned. +If the current font face name is not recognized by `m:wxFont` or by the underlying +system, `wxFONTFAMILY_DEFAULT` is returned. -Note that currently this function is not very precise and so not particularly -useful. Font families mostly make sense only for font creation, see -`setFamily/2`. +Note that currently this function is not very precise and so not particularly useful. +Font families mostly make sense only for font creation, see `setFamily/2`. See: `setFamily/2` """. +%% Res = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -spec getFamily(This) -> wx:wx_enum() when This::wxFont(). getFamily(#wx_ref{type=ThisT}=This) -> @@ -238,19 +218,16 @@ getFamily(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetFamily), wxe_util:rec(?wxFont_GetFamily). -%% @doc See external documentation. -doc """ Returns the platform-dependent string completely describing this font. -Returned string is always non-empty unless the font is invalid (in which case an -assert is triggered). +Returned string is always non-empty unless the font is invalid (in which case an assert +is triggered). -Note that the returned string is not meant to be shown or edited by the user: a -typical use of this function is for serializing in string-form a `m:wxFont` -object. +Note that the returned string is not meant to be shown or edited by the user: a typical +use of this function is for serializing in string-form a `m:wxFont` object. -See: `SetNativeFontInfo()` (not implemented in wx), -`getNativeFontInfoUserDesc/1` +See: `getNativeFontInfoUserDesc/1` """. -spec getNativeFontInfoDesc(This) -> unicode:charlist() when This::wxFont(). @@ -259,21 +236,19 @@ getNativeFontInfoDesc(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetNativeFontInfoDesc), wxe_util:rec(?wxFont_GetNativeFontInfoDesc). -%% @doc See external documentation. -doc """ Returns a user-friendly string for this font object. -Returned string is always non-empty unless the font is invalid (in which case an -assert is triggered). +Returned string is always non-empty unless the font is invalid (in which case an assert +is triggered). -The string does not encode all `m:wxFont` infos under all platforms; e.g. under -wxMSW the font family is not present in the returned string. +The string does not encode all `m:wxFont` infos under all platforms; e.g. under wxMSW the +font family is not present in the returned string. -Some examples of the formats of returned strings (which are platform-dependent) -are in `SetNativeFontInfoUserDesc()` (not implemented in wx). +Some examples of the formats of returned strings (which are platform-dependent) are in `SetNativeFontInfoUserDesc()` +(not implemented in wx). -See: `SetNativeFontInfoUserDesc()` (not implemented in wx), -`getNativeFontInfoDesc/1` +See: `getNativeFontInfoDesc/1` """. -spec getNativeFontInfoUserDesc(This) -> unicode:charlist() when This::wxFont(). @@ -282,17 +257,13 @@ getNativeFontInfoUserDesc(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetNativeFontInfoUserDesc), wxe_util:rec(?wxFont_GetNativeFontInfoUserDesc). -%% @doc See external documentation. -doc """ Gets the point size as an integer number. -This function is kept for compatibility reasons. New code should use -`GetFractionalPointSize()` (not implemented in wx) and support fractional point -sizes. +This function is kept for compatibility reasons. New code should use `GetFractionalPointSize()` +(not implemented in wx) and support fractional point sizes. See: `setPointSize/2` - -See: `GetFractionalPointSize()` (not implemented in wx) """. -spec getPointSize(This) -> integer() when This::wxFont(). @@ -301,8 +272,6 @@ getPointSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetPointSize), wxe_util:rec(?wxFont_GetPointSize). -%% @doc See external documentation. -%%
Res = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -doc """ Gets the font style. @@ -310,6 +279,7 @@ See ?wxFontStyle for a list of valid styles. See: `setStyle/2` """. +%% Res = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -spec getStyle(This) -> wx:wx_enum() when This::wxFont(). getStyle(#wx_ref{type=ThisT}=This) -> @@ -317,7 +287,6 @@ getStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetStyle), wxe_util:rec(?wxFont_GetStyle). -%% @doc See external documentation. -doc """ Returns true if the font is underlined, false otherwise. @@ -330,8 +299,6 @@ getUnderlined(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetUnderlined), wxe_util:rec(?wxFont_GetUnderlined). -%% @doc See external documentation. -%%
Res = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -doc """ Gets the font weight. @@ -339,6 +306,7 @@ See ?wxFontWeight for a list of valid weight identifiers. See: `setWeight/2` """. +%% Res = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec getWeight(This) -> wx:wx_enum() when This::wxFont(). getWeight(#wx_ref{type=ThisT}=This) -> @@ -346,8 +314,7 @@ getWeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_GetWeight), wxe_util:rec(?wxFont_GetWeight). -%% @doc See external documentation. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxFont(). @@ -355,7 +322,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See external documentation. -doc "Returns true if this object is a valid font, false otherwise.". -spec isOk(This) -> boolean() when This::wxFont(). @@ -364,33 +330,34 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFont_IsOk), wxe_util:rec(?wxFont_IsOk). -%% @doc See external documentation. -%%
Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc """ Sets the default font encoding. See: -[Overview fontencoding](https://docs.wxwidgets.org/3.1/overview_fontencoding.html#overview_fontencoding), -`getDefaultEncoding/0` +* [Overview fontencoding](https://docs.wxwidgets.org/3.2/overview_fontencoding.html#overview_fontencoding) + +* `getDefaultEncoding/0` """. +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec setDefaultEncoding(Encoding) -> 'ok' when Encoding::wx:wx_enum(). setDefaultEncoding(Encoding) when is_integer(Encoding) -> wxe_util:queue_cmd(Encoding,?get_env(),?wxFont_SetDefaultEncoding). -%% @doc See external documentation. -doc """ Sets the facename for the font. -Remark: To avoid portability problems, don't rely on a specific face, but -specify the font family instead (see ?wxFontFamily and `setFamily/2`). +Remark: To avoid portability problems, don't rely on a specific face, but specify the +font family instead (see ?wxFontFamily and `setFamily/2`). + +Return: true if the given face name exists; if the face name doesn't exist in the user's +system then the font is invalidated (so that `isOk/1` will return false) and false is returned. -Return: true if the given face name exists; if the face name doesn't exist in -the user's system then the font is invalidated (so that `isOk/1` will return -false) and false is returned. +See: +* `getFaceName/1` -See: `getFaceName/1`, `setFamily/2` +* `setFamily/2` """. -spec setFaceName(This, FaceName) -> boolean() when This::wxFont(), FaceName::unicode:chardata(). @@ -401,18 +368,20 @@ setFaceName(#wx_ref{type=ThisT}=This,FaceName) wxe_util:queue_cmd(This,FaceName_UC,?get_env(),?wxFont_SetFaceName), wxe_util:rec(?wxFont_SetFaceName). -%% @doc See external documentation. -%%
Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -doc """ Sets the font family. -As described in ?wxFontFamily docs the given `family` value acts as a rough, -basic indication of the main font properties (look, spacing). +As described in ?wxFontFamily docs the given `family` value acts as a rough, basic +indication of the main font properties (look, spacing). Note that changing the font family results in changing the font face name. -See: `getFamily/1`, `setFaceName/2` +See: +* `getFamily/1` + +* `setFaceName/2` """. +%% Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -spec setFamily(This, Family) -> 'ok' when This::wxFont(), Family::wx:wx_enum(). setFamily(#wx_ref{type=ThisT}=This,Family) @@ -420,14 +389,13 @@ setFamily(#wx_ref{type=ThisT}=This,Family) ?CLASS(ThisT,wxFont), wxe_util:queue_cmd(This,Family,?get_env(),?wxFont_SetFamily). -%% @doc See external documentation. -doc """ Sets the font size in points to an integer value. -This is a legacy version of the function only supporting integer point sizes. It -can still be used, but to avoid unnecessarily restricting the font size in -points to integer values, consider using the new (added in wxWidgets 3.1.2) -`SetFractionalPointSize()` (not implemented in wx) function instead. +This is a legacy version of the function only supporting integer point sizes. It can +still be used, but to avoid unnecessarily restricting the font size in points to integer +values, consider using the new (added in wxWidgets 3.1.2) `SetFractionalPointSize()` (not +implemented in wx) function instead. """. -spec setPointSize(This, PointSize) -> 'ok' when This::wxFont(), PointSize::integer(). @@ -436,13 +404,12 @@ setPointSize(#wx_ref{type=ThisT}=This,PointSize) ?CLASS(ThisT,wxFont), wxe_util:queue_cmd(This,PointSize,?get_env(),?wxFont_SetPointSize). -%% @doc See external documentation. -%%
Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -doc """ Sets the font style. See: `getStyle/1` """. +%% Style = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -spec setStyle(This, Style) -> 'ok' when This::wxFont(), Style::wx:wx_enum(). setStyle(#wx_ref{type=ThisT}=This,Style) @@ -450,7 +417,6 @@ setStyle(#wx_ref{type=ThisT}=This,Style) ?CLASS(ThisT,wxFont), wxe_util:queue_cmd(This,Style,?get_env(),?wxFont_SetStyle). -%% @doc See external documentation. -doc """ Sets underlining. @@ -463,13 +429,12 @@ setUnderlined(#wx_ref{type=ThisT}=This,Underlined) ?CLASS(ThisT,wxFont), wxe_util:queue_cmd(This,Underlined,?get_env(),?wxFont_SetUnderlined). -%% @doc See external documentation. -%%
Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -doc """ Sets the font weight. See: `getWeight/1` """. +%% Weight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec setWeight(This, Weight) -> 'ok' when This::wxFont(), Weight::wx:wx_enum(). setWeight(#wx_ref{type=ThisT}=This,Weight) @@ -477,17 +442,7 @@ setWeight(#wx_ref{type=ThisT}=This,Weight) ?CLASS(ThisT,wxFont), wxe_util:queue_cmd(This,Weight,?get_env(),?wxFont_SetWeight). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See reference-counted object destruction for more info. - -Remark: Although all remaining fonts are deleted when the application exits, the -application should try to clean up all fonts itself. This is because wxWidgets -cannot know if a pointer to the font object is stored in an application data -structure, and there is a risk of double deletion. -""". +-doc "Destroys the object". -spec destroy(This::wxFont()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFont), diff --git a/lib/wx/src/gen/wxFontData.erl b/lib/wx/src/gen/wxFontData.erl index b06494e6c7fc..975b4508ebed 100644 --- a/lib/wx/src/gen/wxFontData.erl +++ b/lib/wx/src/gen/wxFontData.erl @@ -20,16 +20,16 @@ -module(wxFontData). -moduledoc """ -Functions for wxFontData class - This class holds a variety of information related to font dialogs. See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_font), -`m:wxFont`, `m:wxFontDialog` +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_font) + +* `m:wxFont` + +* `m:wxFontDialog` -wxWidgets docs: -[wxFontData](https://docs.wxwidgets.org/3.1/classwx_font_data.html) +wxWidgets docs: [wxFontData](https://docs.wxwidgets.org/3.2/classwx_font_data.html) """. -include("wxe.hrl"). -export([destroy/1,enableEffects/2,getAllowSymbols/1,getChosenFont/1,getColour/1, @@ -41,23 +41,20 @@ wxWidgets docs: -type wxFontData() :: wx:wx_object(). -export_type([wxFontData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Constructor. -Initializes `fontColour` to black, `showHelp` to false, `allowSymbols` to true, -`enableEffects` to true, `minSize` to 0 and `maxSize` to 0. +Initializes `fontColour` to black, `showHelp` to false, `allowSymbols` to true, `enableEffects` +to true, `minSize` to 0 and `maxSize` to 0. """. -spec new() -> wxFontData(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFontData_new_0), wxe_util:rec(?wxFontData_new_0). -%% @doc See external documentation. -doc "Copy Constructor.". -spec new(Data) -> wxFontData() when Data::wxFontData(). @@ -66,12 +63,10 @@ new(#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(Data,?get_env(),?wxFontData_new_1), wxe_util:rec(?wxFontData_new_1). -%% @doc See external documentation. -doc """ Enables or disables "effects" under Windows or generic only. -This refers to the controls for manipulating colour, strikeout and underline -properties. +This refers to the controls for manipulating colour, strikeout and underline properties. The default value is true. """. @@ -82,7 +77,6 @@ enableEffects(#wx_ref{type=ThisT}=This,Enable) ?CLASS(ThisT,wxFontData), wxe_util:queue_cmd(This,Enable,?get_env(),?wxFontData_EnableEffects). -%% @doc See external documentation. -doc """ Under Windows, returns a flag determining whether symbol fonts can be selected. @@ -97,7 +91,6 @@ getAllowSymbols(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetAllowSymbols), wxe_util:rec(?wxFontData_GetAllowSymbols). -%% @doc See external documentation. -doc """ Gets the colour associated with the font dialog. @@ -110,10 +103,9 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetColour), wxe_util:rec(?wxFontData_GetColour). -%% @doc See external documentation. -doc """ -Gets the font chosen by the user if the user pressed OK -(`wxFontDialog::ShowModal()` (not implemented in wx) returned wxID_OK). +Gets the font chosen by the user if the user pressed OK (`wxFontDialog::ShowModal()` (not +implemented in wx) returned wxID\_OK). """. -spec getChosenFont(This) -> wxFont:wxFont() when This::wxFontData(). @@ -122,12 +114,10 @@ getChosenFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetChosenFont), wxe_util:rec(?wxFontData_GetChosenFont). -%% @doc See external documentation. -doc """ Determines whether "effects" are enabled under Windows. -This refers to the controls for manipulating colour, strikeout and underline -properties. +This refers to the controls for manipulating colour, strikeout and underline properties. The default value is true. """. @@ -138,7 +128,6 @@ getEnableEffects(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetEnableEffects), wxe_util:rec(?wxFontData_GetEnableEffects). -%% @doc See external documentation. -doc """ Gets the font that will be initially used by the font dialog. @@ -151,7 +140,6 @@ getInitialFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetInitialFont), wxe_util:rec(?wxFontData_GetInitialFont). -%% @doc See external documentation. -doc """ Returns true if the Help button will be shown (Windows only). @@ -164,7 +152,6 @@ getShowHelp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontData_GetShowHelp), wxe_util:rec(?wxFontData_GetShowHelp). -%% @doc See external documentation. -doc """ Under Windows, determines whether symbol fonts can be selected. @@ -179,7 +166,6 @@ setAllowSymbols(#wx_ref{type=ThisT}=This,AllowSymbols) ?CLASS(ThisT,wxFontData), wxe_util:queue_cmd(This,AllowSymbols,?get_env(),?wxFontData_SetAllowSymbols). -%% @doc See external documentation. -doc "Sets the font that will be returned to the user (for internal use only).". -spec setChosenFont(This, Font) -> 'ok' when This::wxFontData(), Font::wxFont:wxFont(). @@ -188,7 +174,6 @@ setChosenFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxFontData_SetChosenFont). -%% @doc See external documentation. -doc """ Sets the colour that will be used for the font foreground colour. @@ -201,7 +186,6 @@ setColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxFontData), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxFontData_SetColour). -%% @doc See external documentation. -doc "Sets the font that will be initially used by the font dialog.". -spec setInitialFont(This, Font) -> 'ok' when This::wxFontData(), Font::wxFont:wxFont(). @@ -210,7 +194,6 @@ setInitialFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxFontData_SetInitialFont). -%% @doc See external documentation. -doc """ Sets the valid range for the font point size (Windows only). @@ -223,10 +206,8 @@ setRange(#wx_ref{type=ThisT}=This,Min,Max) ?CLASS(ThisT,wxFontData), wxe_util:queue_cmd(This,Min,Max,?get_env(),?wxFontData_SetRange). -%% @doc See external documentation. -doc """ -Determines whether the Help button will be displayed in the font dialog (Windows -only). +Determines whether the Help button will be displayed in the font dialog (Windows only). The default value is false. """. @@ -237,8 +218,7 @@ setShowHelp(#wx_ref{type=ThisT}=This,ShowHelp) ?CLASS(ThisT,wxFontData), wxe_util:queue_cmd(This,ShowHelp,?get_env(),?wxFontData_SetShowHelp). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFontData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFontData), diff --git a/lib/wx/src/gen/wxFontDialog.erl b/lib/wx/src/gen/wxFontDialog.erl index cea67b0a64d3..e956ae757380 100644 --- a/lib/wx/src/gen/wxFontDialog.erl +++ b/lib/wx/src/gen/wxFontDialog.erl @@ -20,19 +20,26 @@ -module(wxFontDialog). -moduledoc """ -Functions for wxFontDialog class - This class represents the font chooser dialog. See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_font), -`m:wxFontData`, ?wxGetFontFromUser() +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_font) + +* `m:wxFontData` + +* ?wxGetFontFromUser() + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxFontDialog](https://docs.wxwidgets.org/3.1/classwx_font_dialog.html) +wxWidgets docs: [wxFontDialog](https://docs.wxwidgets.org/3.2/classwx_font_dialog.html) """. -include("wxe.hrl"). -export([create/3,destroy/1,getFontData/1,new/0,new/2]). @@ -84,7 +91,6 @@ wxWidgets docs: -type wxFontDialog() :: wx:wx_object(). -export_type([wxFontDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -92,7 +98,6 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default ctor. @@ -103,12 +108,11 @@ new() -> wxe_util:queue_cmd(?get_env(), ?wxFontDialog_new_0), wxe_util:rec(?wxFontDialog_new_0). -%% @doc See external documentation. -doc """ Constructor. -Pass a parent window, and the `m:wxFontData` object to be used to initialize the -dialog controls. +Pass a parent window, and the `m:wxFontData` object to be used to initialize the dialog +controls. """. -spec new(Parent, Data) -> wxFontDialog() when Parent::wxWindow:wxWindow(), Data::wxFontData:wxFontData(). @@ -118,10 +122,9 @@ new(#wx_ref{type=ParentT}=Parent,#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(Parent,Data,?get_env(),?wxFontDialog_new_2), wxe_util:rec(?wxFontDialog_new_2). -%% @doc See external documentation. -doc """ -Creates the dialog if the `m:wxFontDialog` object had been initialized using the -default constructor. +Creates the dialog if the `m:wxFontDialog` object had been initialized using the default +constructor. Return: true on success and false if an error occurred. """. @@ -134,7 +137,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,#wx_ref{type=DataT} wxe_util:queue_cmd(This,Parent,Data,?get_env(),?wxFontDialog_Create), wxe_util:rec(?wxFontDialog_Create). -%% @doc See external documentation. -doc "Returns the `m:wxFontData` associated with the font dialog.". -spec getFontData(This) -> wxFontData:wxFontData() when This::wxFontDialog(). @@ -143,659 +145,443 @@ getFontData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontDialog_GetFontData), wxe_util:rec(?wxFontDialog_GetFontData). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFontDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFontDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxFontPickerCtrl.erl b/lib/wx/src/gen/wxFontPickerCtrl.erl index bfaaf14471ed..a4b4489b6137 100644 --- a/lib/wx/src/gen/wxFontPickerCtrl.erl +++ b/lib/wx/src/gen/wxFontPickerCtrl.erl @@ -20,30 +20,54 @@ -module(wxFontPickerCtrl). -moduledoc """ -Functions for wxFontPickerCtrl class +This control allows the user to select a font. -This control allows the user to select a font. The generic implementation is a -button which brings up a `m:wxFontDialog` when clicked. Native implementation -may differ but this is usually a (small) widget which give access to the -font-chooser dialog. It is only available if `wxUSE_FONTPICKERCTRL` is set to 1 -(the default). +The generic implementation is a button which brings up a `m:wxFontDialog` when clicked. +Native implementation may differ but this is usually a (small) widget which give access to +the font-chooser dialog. It is only available if `wxUSE_FONTPICKERCTRL` is set to 1 (the default). -Styles +## Styles This class supports the following styles: -See: `m:wxFontDialog`, `m:wxFontPickerEvent` +* wxFNTP_DEFAULT_STYLE: The default style: wxFNTP_FONTDESC_AS_LABEL | +wxFNTP_USEFONT_FOR_LABEL. -This class is derived (and can use functions) from: `m:wxPickerBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* wxFNTP_USE_TEXTCTRL: Creates a text control to the left of the picker button which is +completely managed by the `m:wxFontPickerCtrl` and which can be used by the user to +specify a font (see SetSelectedFont). The text control is automatically synchronized with +button's value. Use functions defined in `m:wxPickerBase` to modify the text control. -wxWidgets docs: -[wxFontPickerCtrl](https://docs.wxwidgets.org/3.1/classwx_font_picker_ctrl.html) +* wxFNTP_FONTDESC_AS_LABEL: Keeps the label of the button updated with the fontface name +and the font size. E.g. choosing "Times New Roman bold, italic with size 10" from the +fontdialog, will update the label (overwriting any previous label) with the "Times New +Roman, 10" text. + +* wxFNTP_USEFONT_FOR_LABEL: Uses the currently selected font to draw the label of the +button. + +See: +* `m:wxFontDialog` + +* `m:wxFontPickerEvent` + +This class is derived, and can use functions, from: + +* `m:wxPickerBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxFontPickerCtrl](https://docs.wxwidgets.org/3.2/classwx_font_picker_ctrl.html) ## Events Event types emitted from this class: -[`command_fontpicker_changed`](`m:wxFontPickerEvent`) + +* [`command_fontpicker_changed`](`m:wxFontPickerEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getMaxPointSize/1,getSelectedFont/1,new/0, @@ -94,7 +118,6 @@ Event types emitted from this class: -type wxFontPickerCtrl() :: wx:wx_object(). -export_type([wxFontPickerCtrl/0]). -%% @hidden -doc false. parent_class(wxPickerBase) -> true; parent_class(wxControl) -> true; @@ -102,13 +125,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxFontPickerCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFontPickerCtrl_new_0), wxe_util:rec(?wxFontPickerCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxFontPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -116,7 +139,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc "Initializes the object and calls `create/4` with all the parameters.". -spec new(Parent, Id, [Option]) -> wxFontPickerCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -138,7 +160,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxFontPickerCtrl_new_3), wxe_util:rec(?wxFontPickerCtrl_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxFontPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -146,12 +168,10 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See external documentation. -doc """ Creates this widget with given parameters. -Return: true if the control was successfully created or false if creation -failed. +Return: true if the control was successfully created or false if creation failed. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxFontPickerCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -174,7 +194,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxFontPickerCtrl_Create), wxe_util:rec(?wxFontPickerCtrl_Create). -%% @doc See external documentation. -doc """ Returns the currently selected font. @@ -187,7 +206,6 @@ getSelectedFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontPickerCtrl_GetSelectedFont), wxe_util:rec(?wxFontPickerCtrl_GetSelectedFont). -%% @doc See external documentation. -doc """ Sets the currently selected font. @@ -200,7 +218,6 @@ setSelectedFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxFontPickerCtrl_SetSelectedFont). -%% @doc See external documentation. -doc "Returns the maximum point size value allowed for the user-chosen font.". -spec getMaxPointSize(This) -> integer() when This::wxFontPickerCtrl(). @@ -209,15 +226,13 @@ getMaxPointSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFontPickerCtrl_GetMaxPointSize), wxe_util:rec(?wxFontPickerCtrl_GetMaxPointSize). -%% @doc See external documentation. -doc """ Sets the maximum point size value allowed for the user-chosen font. -The default value is 100. Note that big fonts can require a lot of memory and -CPU time both for creation and for rendering; thus, specially because the user -has the option to specify the fontsize through a text control (see -wxFNTP_USE_TEXTCTRL), it's a good idea to put a limit to the maximum font size -when huge fonts do not make much sense. +The default value is 100. Note that big fonts can require a lot of memory and CPU time +both for creation and for rendering; thus, specially because the user has the option to +specify the fontsize through a text control (see wxFNTP_USE_TEXTCTRL), it's a good idea to +put a limit to the maximum font size when huge fonts do not make much sense. """. -spec setMaxPointSize(This, Max) -> 'ok' when This::wxFontPickerCtrl(), Max::integer(). @@ -226,605 +241,407 @@ setMaxPointSize(#wx_ref{type=ThisT}=This,Max) ?CLASS(ThisT,wxFontPickerCtrl), wxe_util:queue_cmd(This,Max,?get_env(),?wxFontPickerCtrl_SetMaxPointSize). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxFontPickerCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFontPickerCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPickerBase -%% @hidden -doc false. isPickerCtrlGrowable(This) -> wxPickerBase:isPickerCtrlGrowable(This). -%% @hidden -doc false. setTextCtrlGrowable(This, Options) -> wxPickerBase:setTextCtrlGrowable(This, Options). -%% @hidden -doc false. setTextCtrlGrowable(This) -> wxPickerBase:setTextCtrlGrowable(This). -%% @hidden -doc false. setPickerCtrlGrowable(This, Options) -> wxPickerBase:setPickerCtrlGrowable(This, Options). -%% @hidden -doc false. setPickerCtrlGrowable(This) -> wxPickerBase:setPickerCtrlGrowable(This). -%% @hidden -doc false. isTextCtrlGrowable(This) -> wxPickerBase:isTextCtrlGrowable(This). -%% @hidden -doc false. getTextCtrl(This) -> wxPickerBase:getTextCtrl(This). -%% @hidden -doc false. hasTextCtrl(This) -> wxPickerBase:hasTextCtrl(This). -%% @hidden -doc false. getPickerCtrlProportion(This) -> wxPickerBase:getPickerCtrlProportion(This). -%% @hidden -doc false. getTextCtrlProportion(This) -> wxPickerBase:getTextCtrlProportion(This). -%% @hidden -doc false. setPickerCtrlProportion(This,Prop) -> wxPickerBase:setPickerCtrlProportion(This,Prop). -%% @hidden -doc false. setTextCtrlProportion(This,Prop) -> wxPickerBase:setTextCtrlProportion(This,Prop). -%% @hidden -doc false. getInternalMargin(This) -> wxPickerBase:getInternalMargin(This). -%% @hidden -doc false. setInternalMargin(This,Margin) -> wxPickerBase:setInternalMargin(This,Margin). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxFontPickerEvent.erl b/lib/wx/src/gen/wxFontPickerEvent.erl index dcedd82d541f..525f6d8127cb 100644 --- a/lib/wx/src/gen/wxFontPickerEvent.erl +++ b/lib/wx/src/gen/wxFontPickerEvent.erl @@ -20,23 +20,21 @@ -module(wxFontPickerEvent). -moduledoc """ -Functions for wxFontPickerEvent class - This event class is used for the events generated by `m:wxFontPickerCtrl`. See: `m:wxFontPickerCtrl` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxFontPickerEvent](https://docs.wxwidgets.org/3.1/classwx_font_picker_event.html) +wxWidgets docs: [wxFontPickerEvent](https://docs.wxwidgets.org/3.2/classwx_font_picker_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxFontPickerEventType`](`t:wxFontPickerEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxFontPickerEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getFont/1]). @@ -51,13 +49,11 @@ this type. -include("wx.hrl"). -type wxFontPickerEventType() :: 'command_fontpicker_changed'. -export_type([wxFontPickerEvent/0, wxFontPicker/0, wxFontPickerEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Retrieve the font the user has just selected.". -spec getFont(This) -> wxFont:wxFont() when This::wxFontPickerEvent(). @@ -67,58 +63,40 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxFontPickerEvent_GetFont). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxFrame.erl b/lib/wx/src/gen/wxFrame.erl index 11855a7c0116..ff82ee2a9bdf 100644 --- a/lib/wx/src/gen/wxFrame.erl +++ b/lib/wx/src/gen/wxFrame.erl @@ -20,50 +20,131 @@ -module(wxFrame). -moduledoc """ -Functions for wxFrame class +A frame is a window whose size and position can (usually) be changed by the user. -A frame is a window whose size and position can (usually) be changed by the -user. +It usually has thick borders and a title bar, and can optionally contain a menu bar, +toolbar and status bar. A frame can contain any window that is not a frame or dialog. -It usually has thick borders and a title bar, and can optionally contain a menu -bar, toolbar and status bar. A frame can contain any window that is not a frame -or dialog. +A frame that has a status bar and toolbar, created via the `createStatusBar/2` and `createToolBar/2` functions, manages these +windows and adjusts the value returned by `wxWindow:getClientSize/1` to reflect the remaining size available to +application windows. -A frame that has a status bar and toolbar, created via the `createStatusBar/2` -and `createToolBar/2` functions, manages these windows and adjusts the value -returned by `wxWindow:getClientSize/1` to reflect the remaining size available -to application windows. - -Remark: An application should normally define an `m:wxCloseEvent` handler for -the frame to respond to system close events, for example so that related data -and subwindows can be cleaned up. +Remark: An application should normally define an `m:wxCloseEvent` handler for the frame +to respond to system close events, for example so that related data and subwindows can be +cleaned up. Default event processing `m:wxFrame` processes the following events: -Styles +* `wxEVT_SIZE:` if the frame has exactly one child window, not counting the status and +toolbar, this child is resized to take the entire frame client area. If two or more +windows are present, they should be laid out explicitly either by manually handling `wxEVT_SIZE` +or using sizers; + +* `wxEVT_MENU_HIGHLIGHT:` the default implementation displays the help string associated +with the selected item in the first pane of the status bar, if there is one. + +## Styles This class supports the following styles: +* wxDEFAULT_FRAME_STYLE: Defined as wxMINIMIZE_BOX | wxMAXIMIZE_BOX | wxRESIZE_BORDER | +wxSYSTEM_MENU | wxCAPTION | wxCLOSE_BOX | wxCLIP_CHILDREN. + +* wxICONIZE: Display the frame iconized (minimized). Windows only. + +* wxCAPTION: Puts a caption on the frame. Notice that this flag is required by +wxMINIMIZE_BOX, wxMAXIMIZE_BOX and wxCLOSE_BOX on most systems as the corresponding +buttons cannot be shown if the window has no title bar at all. I.e. if wxCAPTION is not +specified those styles would be simply ignored. + +* wxMINIMIZE: Identical to wxICONIZE. Windows only. + +* wxMINIMIZE_BOX: Displays a minimize box on the frame. + +* wxMAXIMIZE: Displays the frame maximized. Windows and GTK+ only. + +* wxMAXIMIZE_BOX: Displays a maximize box on the frame. Notice that under wxGTK +wxRESIZE_BORDER must be used as well or this style is ignored. + +* wxCLOSE_BOX: Displays a close box on the frame. + +* wxSTAY_ON_TOP: Stay on top of all other windows, see also wxFRAME_FLOAT_ON_PARENT. + +* wxSYSTEM_MENU: Displays a system menu containing the list of various windows commands in +the window title bar. Unlike wxMINIMIZE_BOX, wxMAXIMIZE_BOX and wxCLOSE_BOX styles this +style can be used without wxCAPTION, at least under Windows, and makes the system menu +available without showing it on screen in this case. However it is recommended to only use +it together with wxCAPTION for consistent behaviour under all platforms. + +* wxRESIZE_BORDER: Displays a resizable border around the window. + +* wxFRAME_TOOL_WINDOW: Causes a frame with a small title bar to be created; the frame does +not appear in the taskbar under Windows or GTK+. + +* wxFRAME_NO_TASKBAR: Creates an otherwise normal frame but it does not appear in the +taskbar under Windows or GTK+ (note that it will minimize to the desktop window under +Windows which may seem strange to the users and thus it might be better to use this style +only without wxMINIMIZE_BOX style). In wxGTK, the flag is respected only if the window +manager supports _NET_WM_STATE_SKIP_TASKBAR hint. + +* wxFRAME_FLOAT_ON_PARENT: The frame will always be on top of its parent (unlike +wxSTAY_ON_TOP). A frame created with this style must have a non-NULL parent. + +* wxFRAME_SHAPED: Windows with this style are allowed to have their shape changed with the `wxTopLevelWindow:setShape/2` +method. The default frame style is for normal, resizable frames. To create a frame which +cannot be resized by user, you may use the following combination of styles: + See also the overview_windowstyles. -Extra Styles +## Extra Styles This class supports the following extra styles: -See: `m:wxMDIParentFrame`, `m:wxMDIChildFrame`, `m:wxMiniFrame`, `m:wxDialog` +* wxFRAME_EX_CONTEXTHELP: Under Windows, puts a query button on the caption. When pressed, +Windows will go into a context-sensitive help mode and wxWidgets will send a `wxEVT_HELP` +event if the user clicked on an application window. Note that this is an extended style +and must be set by calling SetExtraStyle before Create is called (two-step construction). +You cannot use this style together with wxMAXIMIZE_BOX or wxMINIMIZE_BOX, so you should +use wxDEFAULT_FRAME_STYLE ~ (wxMINIMIZE_BOX | wxMAXIMIZE_BOX) for the frames having this +style (the dialogs don't have a minimize or a maximize box by default) + +* wxFRAME_EX_METAL: On macOS, frames with this style will be shown with a metallic look. +This is an extra style. + +See: +* `m:wxMDIParentFrame` + +* `m:wxMDIChildFrame` + +* `m:wxMiniFrame` + +* `m:wxDialog` + +This class is derived, and can use functions, from: + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxTopLevelWindow` -`m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: [wxFrame](https://docs.wxwidgets.org/3.1/classwx_frame.html) +wxWidgets docs: [wxFrame](https://docs.wxwidgets.org/3.2/classwx_frame.html) ## Events -Event types emitted from this class: [`close_window`](`m:wxCloseEvent`), -[`iconize`](`m:wxIconizeEvent`), [`menu_open`](`m:wxMenuEvent`), -[`menu_close`](`m:wxMenuEvent`), [`menu_highlight`](`m:wxMenuEvent`) +Event types emitted from this class: + +* [`close_window`](`m:wxCloseEvent`) + +* [`iconize`](`m:wxIconizeEvent`) + +* [`menu_open`](`m:wxMenuEvent`) + +* [`menu_close`](`m:wxMenuEvent`) + +* [`menu_highlight`](`m:wxMenuEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,createStatusBar/1,createStatusBar/2,createToolBar/1, @@ -118,21 +199,19 @@ Event types emitted from this class: [`close_window`](`m:wxCloseEvent`), -type wxFrame() :: wx:wx_object(). -export_type([wxFrame/0]). -%% @hidden -doc false. parent_class(wxTopLevelWindow) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxFrame(). new() -> wxe_util:queue_cmd(?get_env(), ?wxFrame_new_0), wxe_util:rec(?wxFrame_new_0). -%% @equiv new(Parent,Id,Title, []) +-doc(#{equiv => new(Parent,Id,Title, [])}). -spec new(Parent, Id, Title) -> wxFrame() when Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -140,12 +219,11 @@ new(Parent,Id,Title) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> new(Parent,Id,Title, []). -%% @doc See external documentation. -doc """ Constructor, creating the window. -Remark: For Motif, MWM (the Motif Window Manager) should be running for any -window styles to work (otherwise all styles take effect). +Remark: For Motif, MWM (the Motif Window Manager) should be running for any window styles +to work (otherwise all styles take effect). See: `create/5` """. @@ -166,7 +244,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(Parent,Id,Title_UC, Opts,?get_env(),?wxFrame_new_4), wxe_util:rec(?wxFrame_new_4). -%% @equiv create(This,Parent,Id,Title, []) +-doc(#{equiv => create(This,Parent,Id,Title, [])}). -spec create(This, Parent, Id, Title) -> boolean() when This::wxFrame(), Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -174,7 +252,6 @@ create(This,Parent,Id,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> create(This,Parent,Id,Title, []). -%% @doc See external documentation. -doc """ Used in two-step frame construction. @@ -198,7 +275,7 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(This,Parent,Id,Title_UC, Opts,?get_env(),?wxFrame_Create), wxe_util:rec(?wxFrame_Create). -%% @equiv createStatusBar(This, []) +-doc(#{equiv => createStatusBar(This, [])}). -spec createStatusBar(This) -> wxStatusBar:wxStatusBar() when This::wxFrame(). @@ -206,19 +283,19 @@ createStatusBar(This) when is_record(This, wx_ref) -> createStatusBar(This, []). -%% @doc See external documentation. -doc """ Creates a status bar at the bottom of the frame. -Return: A pointer to the status bar if it was created successfully, NULL -otherwise. +Return: A pointer to the status bar if it was created successfully, NULL otherwise. Remark: The width of the status bar is the whole width of the frame (adjusted -automatically when resizing), and the height and text size are chosen by the -host windowing system. +automatically when resizing), and the height and text size are chosen by the host +windowing system. + +See: +* `setStatusText/3` -See: `setStatusText/3`, `OnCreateStatusBar()` (not implemented in wx), -`getStatusBar/1` +* `getStatusBar/1` """. -spec createStatusBar(This, [Option]) -> wxStatusBar:wxStatusBar() when This::wxFrame(), @@ -236,7 +313,7 @@ createStatusBar(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxFrame_CreateStatusBar), wxe_util:rec(?wxFrame_CreateStatusBar). -%% @equiv createToolBar(This, []) +-doc(#{equiv => createToolBar(This, [])}). -spec createToolBar(This) -> wxToolBar:wxToolBar() when This::wxFrame(). @@ -244,24 +321,25 @@ createToolBar(This) when is_record(This, wx_ref) -> createToolBar(This, []). -%% @doc See external documentation. -doc """ Creates a toolbar at the top or left of the frame. Return: A pointer to the toolbar if it was created successfully, NULL otherwise. -Remark: By default, the toolbar is an instance of `m:wxToolBar`. To use a -different class, override `OnCreateToolBar()` (not implemented in wx). When a -toolbar has been created with this function, or made known to the frame with -`setToolBar/2`, the frame will manage the toolbar position and adjust the return -value from `wxWindow:getClientSize/1` to reflect the available space for -application windows. Under Pocket PC, you should always use this function for -creating the toolbar to be managed by the frame, so that wxWidgets can use a -combined menubar and toolbar. Where you manage your own toolbars, create a -`m:wxToolBar` as usual. - -See: `createStatusBar/2`, `OnCreateToolBar()` (not implemented in wx), -`setToolBar/2`, `getToolBar/1` +Remark: By default, the toolbar is an instance of `m:wxToolBar`. To use a different +class, override `OnCreateToolBar()` (not implemented in wx). When a toolbar has been +created with this function, or made known to the frame with `setToolBar/2`, the frame will manage the +toolbar position and adjust the return value from `wxWindow:getClientSize/1` to reflect the available space for +application windows. Under Pocket PC, you should always use this function for creating the +toolbar to be managed by the frame, so that wxWidgets can use a combined menubar and +toolbar. Where you manage your own toolbars, create a `m:wxToolBar` as usual. + +See: +* `createStatusBar/2` + +* `setToolBar/2` + +* `getToolBar/1` """. -spec createToolBar(This, [Option]) -> wxToolBar:wxToolBar() when This::wxFrame(), @@ -277,7 +355,6 @@ createToolBar(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxFrame_CreateToolBar), wxe_util:rec(?wxFrame_CreateToolBar). -%% @doc See external documentation. -doc """ Returns the origin of the frame client area (in client coordinates). @@ -290,11 +367,15 @@ getClientAreaOrigin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFrame_GetClientAreaOrigin), wxe_util:rec(?wxFrame_GetClientAreaOrigin). -%% @doc See external documentation. -doc """ Returns a pointer to the menubar currently associated with the frame (if any). -See: `setMenuBar/2`, `m:wxMenuBar`, `m:wxMenu` +See: +* `setMenuBar/2` + +* `m:wxMenuBar` + +* `m:wxMenu` """. -spec getMenuBar(This) -> wxMenuBar:wxMenuBar() when This::wxFrame(). @@ -303,12 +384,13 @@ getMenuBar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFrame_GetMenuBar), wxe_util:rec(?wxFrame_GetMenuBar). -%% @doc See external documentation. -doc """ -Returns a pointer to the status bar currently associated with the frame (if -any). +Returns a pointer to the status bar currently associated with the frame (if any). + +See: +* `createStatusBar/2` -See: `createStatusBar/2`, `m:wxStatusBar` +* `m:wxStatusBar` """. -spec getStatusBar(This) -> wxStatusBar:wxStatusBar() when This::wxFrame(). @@ -317,7 +399,6 @@ getStatusBar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFrame_GetStatusBar), wxe_util:rec(?wxFrame_GetStatusBar). -%% @doc See external documentation. -doc """ Returns the status bar pane used to display menu and toolbar help. @@ -330,11 +411,15 @@ getStatusBarPane(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFrame_GetStatusBarPane), wxe_util:rec(?wxFrame_GetStatusBarPane). -%% @doc See external documentation. -doc """ Returns a pointer to the toolbar currently associated with the frame (if any). -See: `createToolBar/2`, `m:wxToolBar`, `setToolBar/2` +See: +* `createToolBar/2` + +* `m:wxToolBar` + +* `setToolBar/2` """. -spec getToolBar(This) -> wxToolBar:wxToolBar() when This::wxFrame(). @@ -343,7 +428,6 @@ getToolBar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxFrame_GetToolBar), wxe_util:rec(?wxFrame_GetToolBar). -%% @doc See external documentation. -doc "Simulate a menu command.". -spec processCommand(This, Id) -> boolean() when This::wxFrame(), Id::integer(). @@ -353,7 +437,7 @@ processCommand(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxFrame_ProcessCommand), wxe_util:rec(?wxFrame_ProcessCommand). -%% @equiv sendSizeEvent(This, []) +-doc(#{equiv => sendSizeEvent(This, [])}). -spec sendSizeEvent(This) -> 'ok' when This::wxFrame(). @@ -361,20 +445,18 @@ sendSizeEvent(This) when is_record(This, wx_ref) -> sendSizeEvent(This, []). -%% @doc See external documentation. -doc """ -This function sends a dummy `m:wxSizeEvent` to the window allowing it to -re-layout its children positions. - -It is sometimes useful to call this function after adding or deleting a children -after the frame creation or if a child size changes. Note that if the frame is -using either sizers or constraints for the children layout, it is enough to call -`wxWindow:layout/1` directly and this function should not be used in this case. - -If `flags` includes `wxSEND_EVENT_POST` value, this function posts the event, -i.e. schedules it for later processing, instead of dispatching it directly. You -can also use `PostSizeEvent()` (not implemented in wx) as a more readable -equivalent of calling this function with this flag. +This function sends a dummy `m:wxSizeEvent` to the window allowing it to re-layout its +children positions. + +It is sometimes useful to call this function after adding or deleting a children after +the frame creation or if a child size changes. Note that if the frame is using either +sizers or constraints for the children layout, it is enough to call `wxWindow:layout/1` directly and this +function should not be used in this case. + +If `flags` includes `wxSEND_EVENT_POST` value, this function posts the event, i.e. +schedules it for later processing, instead of dispatching it directly. You can also use `PostSizeEvent()` +(not implemented in wx) as a more readable equivalent of calling this function with this flag. """. -spec sendSizeEvent(This, [Option]) -> 'ok' when This::wxFrame(), @@ -387,18 +469,21 @@ sendSizeEvent(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxFrame_SendSizeEvent). -%% @doc See external documentation. -doc """ Tells the frame to show the given menu bar. -Remark: If the frame is destroyed, the menu bar and its menus will be destroyed -also, so do not delete the menu bar explicitly (except by resetting the frame's -menu bar to another frame or NULL). Under Windows, a size event is generated, so -be sure to initialize data members properly before calling `setMenuBar/2`. Note -that on some platforms, it is not possible to call this function twice for the -same frame object. +Remark: If the frame is destroyed, the menu bar and its menus will be destroyed also, so +do not delete the menu bar explicitly (except by resetting the frame's menu bar to another +frame or NULL). Under Windows, a size event is generated, so be sure to initialize data +members properly before calling `setMenuBar/2`. Note that on some platforms, it is not possible to call +this function twice for the same frame object. -See: `getMenuBar/1`, `m:wxMenuBar`, `m:wxMenu` +See: +* `getMenuBar/1` + +* `m:wxMenuBar` + +* `m:wxMenu` """. -spec setMenuBar(This, MenuBar) -> 'ok' when This::wxFrame(), MenuBar::wxMenuBar:wxMenuBar(). @@ -407,14 +492,18 @@ setMenuBar(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuBarT}=MenuBar) -> ?CLASS(MenuBarT,wxMenuBar), wxe_util:queue_cmd(This,MenuBar,?get_env(),?wxFrame_SetMenuBar). -%% @doc See external documentation. -doc """ Associates a status bar with the frame. -If `statusBar` is NULL, then the status bar, if present, is detached from the -frame, but `not` deleted. +If `statusBar` is NULL, then the status bar, if present, is detached from the frame, but `not` +deleted. + +See: +* `createStatusBar/2` -See: `createStatusBar/2`, `m:wxStatusBar`, `getStatusBar/1` +* `m:wxStatusBar` + +* `getStatusBar/1` """. -spec setStatusBar(This, StatusBar) -> 'ok' when This::wxFrame(), StatusBar::wxStatusBar:wxStatusBar(). @@ -423,7 +512,6 @@ setStatusBar(#wx_ref{type=ThisT}=This,#wx_ref{type=StatusBarT}=StatusBar) -> ?CLASS(StatusBarT,wxStatusBar), wxe_util:queue_cmd(This,StatusBar,?get_env(),?wxFrame_SetStatusBar). -%% @doc See external documentation. -doc """ Set the status bar pane used to display menu and toolbar help. @@ -436,7 +524,7 @@ setStatusBarPane(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxFrame), wxe_util:queue_cmd(This,N,?get_env(),?wxFrame_SetStatusBarPane). -%% @equiv setStatusText(This,Text, []) +-doc(#{equiv => setStatusText(This,Text, [])}). -spec setStatusText(This, Text) -> 'ok' when This::wxFrame(), Text::unicode:chardata(). @@ -444,16 +532,18 @@ setStatusText(This,Text) when is_record(This, wx_ref),?is_chardata(Text) -> setStatusText(This,Text, []). -%% @doc See external documentation. -doc """ Sets the status bar text and updates the status bar display. -This is a simple wrapper for `wxStatusBar:setStatusText/3` which doesn't do -anything if the frame has no status bar, i.e. `getStatusBar/1` returns NULL. +This is a simple wrapper for `wxStatusBar:setStatusText/3` which doesn't do anything if the frame has no status bar, +i.e. `getStatusBar/1` returns NULL. Remark: Use an empty string to clear the status bar. -See: `createStatusBar/2`, `m:wxStatusBar` +See: +* `createStatusBar/2` + +* `m:wxStatusBar` """. -spec setStatusText(This, Text, [Option]) -> 'ok' when This::wxFrame(), Text::unicode:chardata(), @@ -467,13 +557,12 @@ setStatusText(#wx_ref{type=ThisT}=This,Text, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Text_UC, Opts,?get_env(),?wxFrame_SetStatusText). -%% @doc See external documentation. -doc """ Sets the widths of the fields in the status bar. -Remark: The widths of the variable fields are calculated from the total width of -all fields, minus the sum of widths of the non-variable fields, divided by the -number of variable fields. +Remark: The widths of the variable fields are calculated from the total width of all +fields, minus the sum of widths of the non-variable fields, divided by the number of +variable fields. """. -spec setStatusWidths(This, Widths_field) -> 'ok' when This::wxFrame(), Widths_field::[integer()]. @@ -482,7 +571,6 @@ setStatusWidths(#wx_ref{type=ThisT}=This,Widths_field) ?CLASS(ThisT,wxFrame), wxe_util:queue_cmd(This,Widths_field,?get_env(),?wxFrame_SetStatusWidths). -%% @doc See external documentation. -doc "Associates a toolbar with the frame.". -spec setToolBar(This, ToolBar) -> 'ok' when This::wxFrame(), ToolBar::wxToolBar:wxToolBar(). @@ -491,637 +579,424 @@ setToolBar(#wx_ref{type=ThisT}=This,#wx_ref{type=ToolBarT}=ToolBar) -> ?CLASS(ToolBarT,wxToolBar), wxe_util:queue_cmd(This,ToolBar,?get_env(),?wxFrame_SetToolBar). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Destroys all child windows and menu bar if present. - -See overview_windowdeletion for more info. -""". +-doc "Destroys the object". -spec destroy(This::wxFrame()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxFrame), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxGBSizerItem.erl b/lib/wx/src/gen/wxGBSizerItem.erl index 4f9dc461f71a..6e8493f55986 100644 --- a/lib/wx/src/gen/wxGBSizerItem.erl +++ b/lib/wx/src/gen/wxGBSizerItem.erl @@ -20,19 +20,19 @@ -module(wxGBSizerItem). -moduledoc """ -Functions for wxGBSizerItem class +The `m:wxGBSizerItem` class is used by the `m:wxGridBagSizer` for tracking the items in +the sizer. -The `m:wxGBSizerItem` class is used by the `m:wxGridBagSizer` for tracking the -items in the sizer. It adds grid position and spanning information to the normal -`m:wxSizerItem` by adding `wxGBPosition` (not implemented in wx) and `wxGBSpan` -(not implemented in wx) attributes. Most of the time you will not need to use a -`m:wxGBSizerItem` directly in your code, but there are a couple of cases where -it is handy. +It adds grid position and spanning information to the normal `m:wxSizerItem` by adding `wxGBPosition` +(not implemented in wx) and `wxGBSpan` (not implemented in wx) attributes. Most of the +time you will not need to use a `m:wxGBSizerItem` directly in your code, but there are a +couple of cases where it is handy. -This class is derived (and can use functions) from: `m:wxSizerItem` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGBSizerItem](https://docs.wxwidgets.org/3.1/classwx_g_b_sizer_item.html) +* `m:wxSizerItem` + +wxWidgets docs: [wxGBSizerItem](https://docs.wxwidgets.org/3.2/classwx_g_b_sizer_item.html) """. -include("wxe.hrl"). -export([]). @@ -47,108 +47,74 @@ wxWidgets docs: -type wxGBSizerItem() :: wx:wx_object(). -export_type([wxGBSizerItem/0]). -%% @hidden -doc false. parent_class(wxSizerItem) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxSizerItem -%% @hidden -doc false. show(This,Show) -> wxSizerItem:show(This,Show). -%% @hidden -doc false. assignWindow(This,Window) -> wxSizerItem:assignWindow(This,Window). -%% @hidden -doc false. assignSpacer(This,W,H) -> wxSizerItem:assignSpacer(This,W,H). -%% @hidden -doc false. assignSpacer(This,Size) -> wxSizerItem:assignSpacer(This,Size). -%% @hidden -doc false. assignSizer(This,Sizer) -> wxSizerItem:assignSizer(This,Sizer). -%% @hidden -doc false. setRatio(This,Width,Height) -> wxSizerItem:setRatio(This,Width,Height). -%% @hidden -doc false. setRatio(This,Ratio) -> wxSizerItem:setRatio(This,Ratio). -%% @hidden -doc false. setProportion(This,Proportion) -> wxSizerItem:setProportion(This,Proportion). -%% @hidden -doc false. setMinSize(This,X,Y) -> wxSizerItem:setMinSize(This,X,Y). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizerItem:setMinSize(This,Size). -%% @hidden -doc false. setInitSize(This,X,Y) -> wxSizerItem:setInitSize(This,X,Y). -%% @hidden -doc false. setFlag(This,Flag) -> wxSizerItem:setFlag(This,Flag). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizerItem:setDimension(This,Pos,Size). -%% @hidden -doc false. setBorder(This,Border) -> wxSizerItem:setBorder(This,Border). -%% @hidden -doc false. isWindow(This) -> wxSizerItem:isWindow(This). -%% @hidden -doc false. isSpacer(This) -> wxSizerItem:isSpacer(This). -%% @hidden -doc false. isShown(This) -> wxSizerItem:isShown(This). -%% @hidden -doc false. isSizer(This) -> wxSizerItem:isSizer(This). -%% @hidden -doc false. getWindow(This) -> wxSizerItem:getWindow(This). -%% @hidden -doc false. getUserData(This) -> wxSizerItem:getUserData(This). -%% @hidden -doc false. getSpacer(This) -> wxSizerItem:getSpacer(This). -%% @hidden -doc false. getSizer(This) -> wxSizerItem:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxSizerItem:getSize(This). -%% @hidden -doc false. getRect(This) -> wxSizerItem:getRect(This). -%% @hidden -doc false. getRatio(This) -> wxSizerItem:getRatio(This). -%% @hidden -doc false. getProportion(This) -> wxSizerItem:getProportion(This). -%% @hidden -doc false. getPosition(This) -> wxSizerItem:getPosition(This). -%% @hidden -doc false. getMinSize(This) -> wxSizerItem:getMinSize(This). -%% @hidden -doc false. getFlag(This) -> wxSizerItem:getFlag(This). -%% @hidden -doc false. getBorder(This) -> wxSizerItem:getBorder(This). -%% @hidden -doc false. detachSizer(This) -> wxSizerItem:detachSizer(This). -%% @hidden -doc false. deleteWindows(This) -> wxSizerItem:deleteWindows(This). -%% @hidden -doc false. calcMin(This) -> wxSizerItem:calcMin(This). diff --git a/lib/wx/src/gen/wxGCDC.erl b/lib/wx/src/gen/wxGCDC.erl index 3cf4cdad1855..2dd819837fa8 100644 --- a/lib/wx/src/gen/wxGCDC.erl +++ b/lib/wx/src/gen/wxGCDC.erl @@ -20,18 +20,37 @@ -module(wxGCDC). -moduledoc """ -Functions for wxGCDC class - `m:wxGCDC` is a device context that draws on a `m:wxGraphicsContext`. -`m:wxGCDC` does its best to implement `m:wxDC` API, but the following features -are not (fully) implemented because `m:wxGraphicsContext` doesn't support them: +`m:wxGCDC` does its best to implement `m:wxDC` API, but the following features are not +(fully) implemented because `m:wxGraphicsContext` doesn't support them: + +* `wxDC:getPixel/2` method is not implemented and always returns false because modern graphics layers don't +support retrieving the contents of the drawn pixels. + +* `wxDC:floodFill/4` method is not, and can't be, implemented, as its functionality relies on reading the +pixels from `m:wxGraphicsContext` too. + +* `wxDC:setLogicalFunction/2` method only works with `wxCOPY`, `wxOR`, `wxNO_OP`, `wxCLEAR` and `wxXOR` functions, +attempts to use any other function (including `wxINVERT`) don't do anything. + +* Similarly, ?wxRasterOperationMode parameter of `wxDC:blit/6` and `StretchBlit()` (not implemented in +wx) can only be one of the supported logical functions listed above, using any other +function will result in an assertion failure and not drawing anything. + +* For Direct2D-based `m:wxGraphicsContext`, only true-type fonts can be used in the +font-related functions. + +See: +* `m:wxDC` + +* `m:wxGraphicsContext` -See: `m:wxDC`, `m:wxGraphicsContext` +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxDC` +* `m:wxDC` -wxWidgets docs: [wxGCDC](https://docs.wxwidgets.org/3.1/classwx_g_c_d_c.html) +wxWidgets docs: [wxGCDC](https://docs.wxwidgets.org/3.2/classwx_g_c_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,getGraphicsContext/1,new/0,new/1,setGraphicsContext/2]). @@ -60,18 +79,16 @@ wxWidgets docs: [wxGCDC](https://docs.wxwidgets.org/3.1/classwx_g_c_d_c.html) -type wxGCDC() :: wx:wx_object(). -export_type([wxGCDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxGCDC(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGCDC_new_0), wxe_util:rec(?wxGCDC_new_0). -%% @doc See external documentation. -doc "Constructs a `m:wxGCDC` from a `m:wxWindowDC`.". -spec new(WindowDC) -> wxGCDC() when WindowDC::wxWindowDC:wxWindowDC() | wxMemoryDC:wxMemoryDC() | wxGraphicsContext:wxGraphicsContext(). @@ -88,7 +105,6 @@ new(#wx_ref{type=WindowDCT}=WindowDC) -> wxe_util:queue_cmd(wx:typeCast(WindowDC, WindowDCType),?get_env(),?wxGCDC_new_1), wxe_util:rec(?wxGCDC_new_1). -%% @doc See external documentation. -doc "Retrieves associated `m:wxGraphicsContext`.". -spec getGraphicsContext(This) -> wxGraphicsContext:wxGraphicsContext() when This::wxGCDC(). @@ -97,17 +113,15 @@ getGraphicsContext(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGCDC_GetGraphicsContext), wxe_util:rec(?wxGCDC_GetGraphicsContext). -%% @doc See external documentation. -doc """ Set the graphics context to be used for this `m:wxGCDC`. Note that this object takes ownership of `context` and will delete it when it is destroyed or when `setGraphicsContext/2` is called again. -Also, unlike the constructor taking `m:wxGraphicsContext`, this method will -reapply the current font, pen and brush, so that this object continues to use -them, if they had been changed before (which is never the case when constructing -`m:wxGCDC` directly from `m:wxGraphicsContext`). +Also, unlike the constructor taking `m:wxGraphicsContext`, this method will reapply the +current font, pen and brush, so that this object continues to use them, if they had been +changed before (which is never the case when constructing `m:wxGCDC` directly from `m:wxGraphicsContext`). """. -spec setGraphicsContext(This, Context) -> 'ok' when This::wxGCDC(), Context::wxGraphicsContext:wxGraphicsContext(). @@ -116,286 +130,194 @@ setGraphicsContext(#wx_ref{type=ThisT}=This,#wx_ref{type=ContextT}=Context) -> ?CLASS(ContextT,wxGraphicsContext), wxe_util:queue_cmd(This,Context,?get_env(),?wxGCDC_SetGraphicsContext). -%% @doc Destroys this object, do not use object again +-doc "Destroys the object". -spec destroy(This::wxGCDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGCDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxGLCanvas.erl b/lib/wx/src/gen/wxGLCanvas.erl index b0c6eb8a4f33..3601d40df12a 100644 --- a/lib/wx/src/gen/wxGLCanvas.erl +++ b/lib/wx/src/gen/wxGLCanvas.erl @@ -20,57 +20,51 @@ -module(wxGLCanvas). -moduledoc """ -Functions for wxGLCanvas class +`m:wxGLCanvas` is a class for displaying OpenGL graphics. -`m:wxGLCanvas` is a class for displaying OpenGL graphics. It is always used in -conjunction with `m:wxGLContext` as the context can only be made current (i.e. -active for the OpenGL commands) when it is associated to a `m:wxGLCanvas`. +It is always used in conjunction with `m:wxGLContext` as the context can only be made +current (i.e. active for the OpenGL commands) when it is associated to a `m:wxGLCanvas`. -More precisely, you first need to create a `m:wxGLCanvas` window and then create -an instance of a `m:wxGLContext` that is initialized with this `m:wxGLCanvas` -and then later use either `setCurrent/2` with the instance of the -`m:wxGLContext` or `wxGLContext:setCurrent/2` with the instance of the -`m:wxGLCanvas` (which might be not the same as was used for the creation of the -context) to bind the OpenGL state that is represented by the rendering context -to the canvas, and then finally call `swapBuffers/1` to swap the buffers of the -OpenGL canvas and thus show your current output. +More precisely, you first need to create a `m:wxGLCanvas` window and then create an +instance of a `m:wxGLContext` that is initialized with this `m:wxGLCanvas` and then later +use either `setCurrent/2` with the instance of the `m:wxGLContext` or `wxGLContext:setCurrent/2` with the instance of the `m:wxGLCanvas` +(which might be not the same as was used for the creation of the context) to bind the +OpenGL state that is represented by the rendering context to the canvas, and then finally +call `swapBuffers/1` to swap the buffers of the OpenGL canvas and thus show your current output. -Please note that `m:wxGLContext` always uses physical pixels, even on the -platforms where `m:wxWindow` uses logical pixels, affected by the coordinate -scaling, on high DPI displays. Thus, if you want to set the OpenGL view port to -the size of entire window, you must multiply the result returned by -`wxWindow:getClientSize/1` by `wxWindow:getContentScaleFactor/1` before passing -it to `glViewport()`. Same considerations apply to other OpenGL functions and -other coordinates, notably those retrieved from `m:wxMouseEvent` in the event -handlers. +Please note that `m:wxGLContext` always uses physical pixels, even on the platforms where `m:wxWindow` +uses logical pixels, affected by the coordinate scaling, on high DPI displays. Thus, if +you want to set the OpenGL view port to the size of entire window, you must multiply the +result returned by `wxWindow:getClientSize/1` by `wxWindow:getContentScaleFactor/1` before passing it to `glViewport()`. Same considerations apply to +other OpenGL functions and other coordinates, notably those retrieved from `m:wxMouseEvent` +in the event handlers. -Notice that versions of wxWidgets previous to 2.9 used to implicitly create a -`m:wxGLContext` inside `m:wxGLCanvas` itself. This is still supported in the -current version but is deprecated now and will be removed in the future, please -update your code to create the rendering contexts explicitly. +Notice that versions of wxWidgets previous to 2.9 used to implicitly create a `m:wxGLContext` +inside `m:wxGLCanvas` itself. This is still supported in the current version but is +deprecated now and will be removed in the future, please update your code to create the +rendering contexts explicitly. -To set up the attributes for the canvas (number of bits for the depth buffer, -number of bits for the stencil buffer and so on) you pass them in the -constructor using a `wxGLAttributes` (not implemented in wx) instance. You can -still use the way before 3.1.0 (setting up the correct values of the -`attribList` parameter) but it's discouraged. +To set up the attributes for the canvas (number of bits for the depth buffer, number of +bits for the stencil buffer and so on) you pass them in the constructor using a `wxGLAttributes` +(not implemented in wx) instance. You can still use the way before 3.1.0 (setting up the +correct values of the `attribList` parameter) but it's discouraged. -Note: On those platforms which use a configure script (e.g. Linux and macOS) -OpenGL support is automatically enabled if the relative headers and libraries -are found. To switch it on under the other platforms (e.g. Windows), you need to -edit the `setup.h` file and set `wxUSE_GLCANVAS` to `1` and then also pass -`USE_OPENGL=1` to the make utility. You may also need to add `opengl32.lib` (and -`glu32.lib` for old OpenGL versions) to the list of the libraries your program -is linked with. +Note: On those platforms which use a configure script (e.g. Linux and macOS) OpenGL +support is automatically enabled if the relative headers and libraries are found. To +switch it on under the other platforms (e.g. Windows), you need to edit the `setup.h` file +and set `wxUSE_GLCANVAS` to `1` and then also pass `USE_OPENGL=1` to the make utility. You +may also need to add `opengl32.lib` (and `glu32.lib` for old OpenGL versions) to the list +of the libraries your program is linked with. -See: `m:wxGLContext`, `wxGLAttributes` (not implemented in wx), -`wxGLContextAttrs` (not implemented in wx) +See: `m:wxGLContext` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGLCanvas](https://docs.wxwidgets.org/3.1/classwx_g_l_canvas.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxGLCanvas](https://docs.wxwidgets.org/3.2/classwx_g_l_canvas.html) """. -include("wxe.hrl"). -export([createSurface/1,destroy/1,isDisplaySupported/1,new/1,new/2,setCurrent/2, @@ -118,13 +112,12 @@ wxWidgets docs: -type wxGLCanvas() :: wx:wx_object(). -export_type([wxGLCanvas/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxGLCanvas() when Parent::wxWindow:wxWindow(). @@ -132,15 +125,13 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ This constructor is still available only for compatibility reasons. -Please use the constructor with `wxGLAttributes` (not implemented in wx) -instead. +Please use the constructor with `wxGLAttributes` (not implemented in wx) instead. -If `attribList` is not specified, `wxGLAttributes::PlatformDefaults()` (not -implemented in wx) is used, plus some other attributes (see below). +If `attribList` is not specified, `wxGLAttributes::PlatformDefaults()` (not implemented +in wx) is used, plus some other attributes (see below). """. -spec new(Parent, [Option]) -> wxGLCanvas() when Parent::wxWindow:wxWindow(), @@ -167,19 +158,16 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxGLCanvas_new), wxe_util:rec(?wxGLCanvas_new). -%% @doc See external documentation. -doc """ -Makes the OpenGL state that is represented by the OpenGL rendering context -`context` current, i.e. +Makes the OpenGL state that is represented by the OpenGL rendering context `context` +current, i.e. it will be used by all subsequent OpenGL calls. -This is equivalent to `wxGLContext:setCurrent/2` called with this window as -parameter. +This is equivalent to `wxGLContext:setCurrent/2` called with this window as parameter. -Note: This function may only be called when the window is shown on screen, in -particular it can't usually be called from the constructor as the window isn't -yet shown at this moment. +Note: This function may only be called when the window is shown on screen, in particular +it can't usually be called from the constructor as the window isn't yet shown at this moment. Return: false if an error occurred. """. @@ -191,7 +179,7 @@ setCurrent(#wx_ref{type=ThisT}=This,#wx_ref{type=ContextT}=Context) -> wxe_util:queue_cmd(This,Context,?get_env(),?wxGLCanvas_SetCurrent), wxe_util:rec(?wxGLCanvas_SetCurrent). -%% @doc See external documentation. +-doc "". -spec createSurface(This) -> boolean() when This::wxGLCanvas(). createSurface(#wx_ref{type=ThisT}=This) -> @@ -199,13 +187,11 @@ createSurface(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGLCanvas_CreateSurface), wxe_util:rec(?wxGLCanvas_CreateSurface). -%% @doc See external documentation. -doc """ Determines if a canvas having the specified attributes is available. -This only applies for visual attributes, not rendering context attributes. -Please, use the new form of this method, using `wxGLAttributes` (not implemented -in wx). +This only applies for visual attributes, not rendering context attributes. Please, use +the new form of this method, using `wxGLAttributes` (not implemented in wx). Return: true if attributes are supported. """. @@ -216,11 +202,9 @@ isDisplaySupported(AttribList) wxe_util:queue_cmd(AttribList,?get_env(),?wxGLCanvas_IsDisplaySupported), wxe_util:rec(?wxGLCanvas_IsDisplaySupported). -%% @doc See external documentation. -doc """ -Swaps the double-buffer of this window, making the back-buffer the front-buffer -and vice versa, so that the output of the previous OpenGL commands is displayed -on the window. +Swaps the double-buffer of this window, making the back-buffer the front-buffer and vice +versa, so that the output of the previous OpenGL commands is displayed on the window. Return: false if an error occurred. """. @@ -231,561 +215,377 @@ swapBuffers(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGLCanvas_SwapBuffers), wxe_util:rec(?wxGLCanvas_SwapBuffers). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGLCanvas()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGLCanvas), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxGLContext.erl b/lib/wx/src/gen/wxGLContext.erl index b0bb479fc126..97f4bfc490c5 100644 --- a/lib/wx/src/gen/wxGLContext.erl +++ b/lib/wx/src/gen/wxGLContext.erl @@ -20,54 +20,46 @@ -module(wxGLContext). -moduledoc """ -Functions for wxGLContext class +An instance of a `m:wxGLContext` represents the state of an OpenGL state machine and the +connection between OpenGL and the system. -An instance of a `m:wxGLContext` represents the state of an OpenGL state machine -and the connection between OpenGL and the system. +The OpenGL state includes everything that can be set with the OpenGL API: colors, +rendering variables, buffer data ids, texture objects, etc. It is possible to have +multiple rendering contexts share buffer data and textures. This feature is specially +useful when the application use multiple threads for updating data into the memory of the +graphics card. -The OpenGL state includes everything that can be set with the OpenGL API: -colors, rendering variables, buffer data ids, texture objects, etc. It is -possible to have multiple rendering contexts share buffer data and textures. -This feature is specially useful when the application use multiple threads for -updating data into the memory of the graphics card. +Whether one only rendering context is used with or bound to multiple output windows or if +each window has its own bound context is a developer decision. It is important to take +into account that GPU makers may set different pointers to the same OGL function for +different contexts. The way these pointers are retrieved from the OGL driver should be +used again for each new context. -Whether one only rendering context is used with or bound to multiple output -windows or if each window has its own bound context is a developer decision. It -is important to take into account that GPU makers may set different pointers to -the same OGL function for different contexts. The way these pointers are -retrieved from the OGL driver should be used again for each new context. +Binding (making current) a rendering context with another instance of a `m:wxGLCanvas` +however works only if the both `m:wxGLCanvas` instances were created with the same attributes. -Binding (making current) a rendering context with another instance of a -`m:wxGLCanvas` however works only if the both `m:wxGLCanvas` instances were -created with the same attributes. - -OpenGL version 3 introduced a new type of specification profile, the modern core -profile. The old compatibility profile maintains all legacy features. Since -wxWidgets 3.1.0 you can choose the type of context and even ask for a specified -OGL version number. However, its advised to use only core profile as the -compatibility profile may run a bit slower. +OpenGL version 3 introduced a new type of specification profile, the modern core profile. +The old compatibility profile maintains all legacy features. Since wxWidgets 3.1.0 you can +choose the type of context and even ask for a specified OGL version number. However, its +advised to use only core profile as the compatibility profile may run a bit slower. OpenGL core profile specification defines several flags at context creation that -determine not only the type of context but also some features. Some of these -flags can be set in the list of attributes used at `m:wxGLCanvas` ctor. But -since wxWidgets 3.1.0 it is strongly encouraged to use the new mechanism: -setting the context attributes with a `wxGLContextAttrs` (not implemented in wx) -object and the canvas attributes with a `wxGLAttributes` (not implemented in wx) -object. - -The best way of knowing if your OpenGL environment supports a specific type of -context is creating a `m:wxGLContext` instance and checking `isOK/1`. If it -returns false, then simply delete that instance and create a new one with other -attributes. - -wxHAS_OPENGL_ES is defined on platforms that only have this implementation -available (e.g. the iPhone) and don't support the full specification. - -See: `m:wxGLCanvas`, `wxGLContextAttrs` (not implemented in wx), -`wxGLAttributes` (not implemented in wx) - -wxWidgets docs: -[wxGLContext](https://docs.wxwidgets.org/3.1/classwx_g_l_context.html) +determine not only the type of context but also some features. Some of these flags can be +set in the list of attributes used at `m:wxGLCanvas` ctor. But since wxWidgets 3.1.0 it is +strongly encouraged to use the new mechanism: setting the context attributes with a `wxGLContextAttrs` +(not implemented in wx) object and the canvas attributes with a `wxGLAttributes` (not +implemented in wx) object. + +The best way of knowing if your OpenGL environment supports a specific type of context is +creating a `m:wxGLContext` instance and checking `isOK/1`. If it returns false, then simply delete +that instance and create a new one with other attributes. + +wxHAS_OPENGL_ES is defined on platforms that only have this implementation available +(e.g. the iPhone) and don't support the full specification. + +See: `m:wxGLCanvas` + +wxWidgets docs: [wxGLContext](https://docs.wxwidgets.org/3.2/classwx_g_l_context.html) """. -include("wxe.hrl"). -export([destroy/1,isOK/1,new/1,new/2,setCurrent/2]). @@ -77,11 +69,10 @@ wxWidgets docs: -type wxGLContext() :: wx:wx_object(). -export_type([wxGLContext/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Win, []) +-doc(#{equiv => new(Win, [])}). -spec new(Win) -> wxGLContext() when Win::wxGLCanvas:wxGLCanvas(). @@ -89,7 +80,6 @@ new(Win) when is_record(Win, wx_ref) -> new(Win, []). -%% @doc See external documentation. -doc "Constructor.". -spec new(Win, [Option]) -> wxGLContext() when Win::wxGLCanvas:wxGLCanvas(), @@ -103,15 +93,13 @@ new(#wx_ref{type=WinT}=Win, Options) wxe_util:queue_cmd(Win, Opts,?get_env(),?wxGLContext_new), wxe_util:rec(?wxGLContext_new). -%% @doc See external documentation. -doc """ -Makes the OpenGL state that is represented by this rendering context current -with the `m:wxGLCanvas` `win`. +Makes the OpenGL state that is represented by this rendering context current with the `m:wxGLCanvas` +`win`. -Note: `win` can be a different `m:wxGLCanvas` window than the one that was -passed to the constructor of this rendering context. If `RC` is an object of -type `m:wxGLContext`, the statements `"RC.SetCurrent(win);"` and -`"win.SetCurrent(RC);"` are equivalent, see `wxGLCanvas:setCurrent/2`. +Note: `win` can be a different `m:wxGLCanvas` window than the one that was passed to the +constructor of this rendering context. If `RC` is an object of type `m:wxGLContext`, the +statements `"RC.SetCurrent(win);"` and `"win.SetCurrent(RC);"` are equivalent, see `wxGLCanvas:setCurrent/2`. """. -spec setCurrent(This, Win) -> boolean() when This::wxGLContext(), Win::wxGLCanvas:wxGLCanvas(). @@ -121,13 +109,12 @@ setCurrent(#wx_ref{type=ThisT}=This,#wx_ref{type=WinT}=Win) -> wxe_util:queue_cmd(This,Win,?get_env(),?wxGLContext_SetCurrent), wxe_util:rec(?wxGLContext_SetCurrent). -%% @doc See external documentation. -doc """ -Checks if the underlying OpenGL rendering context was correctly created by the -system with the requested attributes. +Checks if the underlying OpenGL rendering context was correctly created by the system +with the requested attributes. -If this function returns false then the `m:wxGLContext` object is useless and -should be deleted and recreated with different attributes. +If this function returns false then the `m:wxGLContext` object is useless and should be +deleted and recreated with different attributes. Since: 3.1.0 """. @@ -138,8 +125,7 @@ isOK(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGLContext_IsOK), wxe_util:rec(?wxGLContext_IsOK). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGLContext()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGLContext), diff --git a/lib/wx/src/gen/wxGauge.erl b/lib/wx/src/gen/wxGauge.erl index ffb52a0ea91d..83cd682f8d40 100644 --- a/lib/wx/src/gen/wxGauge.erl +++ b/lib/wx/src/gen/wxGauge.erl @@ -20,33 +20,53 @@ -module(wxGauge). -moduledoc """ -Functions for wxGauge class - A gauge is a horizontal or vertical bar which shows a quantity (often time). `m:wxGauge` supports two working modes: determinate and indeterminate progress. -The first is the usual working mode (see `setValue/2` and `setRange/2`) while -the second can be used when the program is doing some processing but you don't -know how much progress is being done. In this case, you can periodically call -the `pulse/1` function to make the progress bar switch to indeterminate mode -(graphically it's usually a set of blocks which move or bounce in the bar -control). +The first is the usual working mode (see `setValue/2` and `setRange/2`) while the second can be used when the +program is doing some processing but you don't know how much progress is being done. In +this case, you can periodically call the `pulse/1` function to make the progress bar switch to +indeterminate mode (graphically it's usually a set of blocks which move or bounce in the +bar control). `m:wxGauge` supports dynamic switch between these two work modes. There are no user commands for the gauge. -Styles +## Styles This class supports the following styles: -See: `m:wxSlider`, `m:wxScrollBar` +* wxGA_HORIZONTAL: Creates a horizontal gauge. + +* wxGA_VERTICAL: Creates a vertical gauge. + +* wxGA_SMOOTH: Creates smooth progress bar with one pixel wide update step (not supported +by all platforms). + +* wxGA_TEXT: Display the current value in percents in the gauge itself. This style is only +supported in wxQt and ignored under the other platforms. This flag is only available in +wxWidgets 3.1.0 and later. + +* wxGA_PROGRESS: Reflect the value of gauge in the application taskbar button under Windows +7 and later and the dock icon under macOS, ignored under the other platforms. This flag is +only available in wxWidgets 3.1.0 and later. + +See: +* `m:wxSlider` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxScrollBar` -wxWidgets docs: [wxGauge](https://docs.wxwidgets.org/3.1/classwx_gauge.html) +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxGauge](https://docs.wxwidgets.org/3.2/classwx_gauge.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getRange/1,getValue/1,isVertical/1,new/0, @@ -94,21 +114,19 @@ wxWidgets docs: [wxGauge](https://docs.wxwidgets.org/3.1/classwx_gauge.html) -type wxGauge() :: wx:wx_object(). -export_type([wxGauge/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxGauge(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGauge_new_0), wxe_util:rec(?wxGauge_new_0). -%% @equiv new(Parent,Id,Range, []) +-doc(#{equiv => new(Parent,Id,Range, [])}). -spec new(Parent, Id, Range) -> wxGauge() when Parent::wxWindow:wxWindow(), Id::integer(), Range::integer(). @@ -116,7 +134,6 @@ new(Parent,Id,Range) when is_record(Parent, wx_ref),is_integer(Id),is_integer(Range) -> new(Parent,Id,Range, []). -%% @doc See external documentation. -doc """ Constructor, creating and showing a gauge. @@ -140,7 +157,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Range, Options) wxe_util:queue_cmd(Parent,Id,Range, Opts,?get_env(),?wxGauge_new_4), wxe_util:rec(?wxGauge_new_4). -%% @equiv create(This,Parent,Id,Range, []) +-doc(#{equiv => create(This,Parent,Id,Range, [])}). -spec create(This, Parent, Id, Range) -> boolean() when This::wxGauge(), Parent::wxWindow:wxWindow(), Id::integer(), Range::integer(). @@ -148,7 +165,6 @@ create(This,Parent,Id,Range) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_integer(Range) -> create(This,Parent,Id,Range, []). -%% @doc See external documentation. -doc """ Creates the gauge for two-step construction. @@ -173,7 +189,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Range, Options) wxe_util:queue_cmd(This,Parent,Id,Range, Opts,?get_env(),?wxGauge_Create), wxe_util:rec(?wxGauge_Create). -%% @doc See external documentation. -doc """ Returns the maximum position of the gauge. @@ -186,7 +201,6 @@ getRange(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGauge_GetRange), wxe_util:rec(?wxGauge_GetRange). -%% @doc See external documentation. -doc """ Returns the current position of the gauge. @@ -199,11 +213,7 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGauge_GetValue), wxe_util:rec(?wxGauge_GetValue). -%% @doc See external documentation. --doc """ -Returns true if the gauge is vertical (has `wxGA_VERTICAL` style) and false -otherwise. -""". +-doc "Returns true if the gauge is vertical (has `wxGA\_VERTICAL` style) and false otherwise.". -spec isVertical(This) -> boolean() when This::wxGauge(). isVertical(#wx_ref{type=ThisT}=This) -> @@ -211,15 +221,13 @@ isVertical(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGauge_IsVertical), wxe_util:rec(?wxGauge_IsVertical). -%% @doc See external documentation. -doc """ Sets the range (maximum value) of the gauge. This function makes the gauge switch to determinate mode, if it's not already. -When the gauge is in indeterminate mode, under wxMSW the gauge repeatedly goes -from zero to `range` and back; under other ports when in indeterminate mode, the -`range` setting is ignored. +When the gauge is in indeterminate mode, under wxMSW the gauge repeatedly goes from zero +to `range` and back; under other ports when in indeterminate mode, the `range` setting is ignored. See: `getRange/1` """. @@ -230,15 +238,12 @@ setRange(#wx_ref{type=ThisT}=This,Range) ?CLASS(ThisT,wxGauge), wxe_util:queue_cmd(This,Range,?get_env(),?wxGauge_SetRange). -%% @doc See external documentation. -doc """ Sets the position of the gauge. -The `pos` must be between 0 and the gauge range as returned by `getRange/1`, -inclusive. +The `pos` must be between 0 and the gauge range as returned by `getRange/1`, inclusive. -This function makes the gauge switch to determinate mode, if it was in -indeterminate mode before. +This function makes the gauge switch to determinate mode, if it was in indeterminate mode before. See: `getValue/1` """. @@ -249,14 +254,12 @@ setValue(#wx_ref{type=ThisT}=This,Pos) ?CLASS(ThisT,wxGauge), wxe_util:queue_cmd(This,Pos,?get_env(),?wxGauge_SetValue). -%% @doc See external documentation. -doc """ -Switch the gauge to indeterminate mode (if required) and makes the gauge move a -bit to indicate the user that some progress has been made. +Switch the gauge to indeterminate mode (if required) and makes the gauge move a bit to +indicate the user that some progress has been made. -Note: After calling this function the value returned by `getValue/1` is -undefined and thus you need to explicitly call `setValue/2` if you want to -restore the determinate mode. +Note: After calling this function the value returned by `getValue/1` is undefined and thus you need +to explicitly call `setValue/2` if you want to restore the determinate mode. """. -spec pulse(This) -> 'ok' when This::wxGauge(). @@ -264,562 +267,378 @@ pulse(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGauge), wxe_util:queue_cmd(This,?get_env(),?wxGauge_Pulse). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the gauge.". +-doc "Destroys the object". -spec destroy(This::wxGauge()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGauge), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxGenericDirCtrl.erl b/lib/wx/src/gen/wxGenericDirCtrl.erl index a2bf31b882f6..5018a990836c 100644 --- a/lib/wx/src/gen/wxGenericDirCtrl.erl +++ b/lib/wx/src/gen/wxGenericDirCtrl.erl @@ -20,29 +20,46 @@ -module(wxGenericDirCtrl). -moduledoc """ -Functions for wxGenericDirCtrl class +This control can be used to place a directory listing (with optional files) on an +arbitrary window. -This control can be used to place a directory listing (with optional files) on -an arbitrary window. +The control contains a `m:wxTreeCtrl` window representing the directory hierarchy, and +optionally, a `m:wxChoice` window containing a list of filters. -The control contains a `m:wxTreeCtrl` window representing the directory -hierarchy, and optionally, a `m:wxChoice` window containing a list of filters. - -Styles +## Styles This class supports the following styles: -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* wxDIRCTRL_DIR_ONLY: Only show directories, and not files. + +* wxDIRCTRL_3D_INTERNAL: Use 3D borders for internal controls. This is the default. + +* wxDIRCTRL_SELECT_FIRST: When setting the default path, select the first file in the +directory. + +* wxDIRCTRL_SHOW_FILTERS: Show the drop-down filter list. + +* wxDIRCTRL_EDIT_LABELS: Allow the folder and file labels to be editable. + +* wxDIRCTRL_MULTIPLE: Allows multiple files and folders to be selected. -wxWidgets docs: -[wxGenericDirCtrl](https://docs.wxwidgets.org/3.1/classwx_generic_dir_ctrl.html) +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxGenericDirCtrl](https://docs.wxwidgets.org/3.2/classwx_generic_dir_ctrl.html) ## Events Event types emitted from this class: -[`dirctrl_selectionchanged`](`m:wxTreeEvent`), -[`dirctrl_fileactivated`](`m:wxTreeEvent`) + +* [`dirctrl_selectionchanged`](`m:wxTreeEvent`) + +* [`dirctrl_fileactivated`](`m:wxTreeEvent`) """. -include("wxe.hrl"). -export([collapseTree/1,create/2,create/3,destroy/1,expandPath/2,getDefaultPath/1, @@ -92,21 +109,19 @@ Event types emitted from this class: -type wxGenericDirCtrl() :: wx:wx_object(). -export_type([wxGenericDirCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxGenericDirCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGenericDirCtrl_new_0), wxe_util:rec(?wxGenericDirCtrl_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxGenericDirCtrl() when Parent::wxWindow:wxWindow(). @@ -114,7 +129,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc "Main constructor.". -spec new(Parent, [Option]) -> wxGenericDirCtrl() when Parent::wxWindow:wxWindow(), @@ -140,7 +154,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxGenericDirCtrl_new_2), wxe_util:rec(?wxGenericDirCtrl_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxGenericDirCtrl(), Parent::wxWindow:wxWindow(). @@ -148,7 +162,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See external documentation. -doc """ Create function for two-step construction. @@ -179,7 +192,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxGenericDirCtrl_Create), wxe_util:rec(?wxGenericDirCtrl_Create). -%% @doc See external documentation. -doc "Initializes variables.". -spec init(This) -> 'ok' when This::wxGenericDirCtrl(). @@ -187,7 +199,6 @@ init(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGenericDirCtrl), wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_Init). -%% @doc See external documentation. -doc "Collapses the entire tree.". -spec collapseTree(This) -> 'ok' when This::wxGenericDirCtrl(). @@ -195,7 +206,6 @@ collapseTree(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGenericDirCtrl), wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_CollapseTree). -%% @doc See external documentation. -doc """ Tries to expand as much of the given `path` as possible, so that the filename or directory is visible in the tree control. @@ -209,7 +219,6 @@ expandPath(#wx_ref{type=ThisT}=This,Path) wxe_util:queue_cmd(This,Path_UC,?get_env(),?wxGenericDirCtrl_ExpandPath), wxe_util:rec(?wxGenericDirCtrl_ExpandPath). -%% @doc See external documentation. -doc "Gets the default path.". -spec getDefaultPath(This) -> unicode:charlist() when This::wxGenericDirCtrl(). @@ -218,7 +227,6 @@ getDefaultPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetDefaultPath), wxe_util:rec(?wxGenericDirCtrl_GetDefaultPath). -%% @doc See external documentation. -doc "Gets the currently-selected directory or filename.". -spec getPath(This) -> unicode:charlist() when This::wxGenericDirCtrl(). @@ -227,7 +235,6 @@ getPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetPath_0), wxe_util:rec(?wxGenericDirCtrl_GetPath_0). -%% @doc See external documentation. -doc """ Gets the path corresponding to the given tree control item. @@ -241,7 +248,6 @@ getPath(#wx_ref{type=ThisT}=This,ItemId) wxe_util:queue_cmd(This,ItemId,?get_env(),?wxGenericDirCtrl_GetPath_1), wxe_util:rec(?wxGenericDirCtrl_GetPath_1). -%% @doc See external documentation. -doc """ Gets selected filename path only (else empty string). @@ -254,7 +260,6 @@ getFilePath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetFilePath), wxe_util:rec(?wxGenericDirCtrl_GetFilePath). -%% @doc See external documentation. -doc "Returns the filter string.". -spec getFilter(This) -> unicode:charlist() when This::wxGenericDirCtrl(). @@ -263,7 +268,6 @@ getFilter(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetFilter), wxe_util:rec(?wxGenericDirCtrl_GetFilter). -%% @doc See external documentation. -doc "Returns the current filter index (zero-based).". -spec getFilterIndex(This) -> integer() when This::wxGenericDirCtrl(). @@ -272,7 +276,6 @@ getFilterIndex(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetFilterIndex), wxe_util:rec(?wxGenericDirCtrl_GetFilterIndex). -%% @doc See external documentation. -doc "Returns the root id for the tree control.". -spec getRootId(This) -> integer() when This::wxGenericDirCtrl(). @@ -281,7 +284,6 @@ getRootId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetRootId), wxe_util:rec(?wxGenericDirCtrl_GetRootId). -%% @doc See external documentation. -doc "Returns a pointer to the tree control.". -spec getTreeCtrl(This) -> wxTreeCtrl:wxTreeCtrl() when This::wxGenericDirCtrl(). @@ -290,7 +292,6 @@ getTreeCtrl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_GetTreeCtrl), wxe_util:rec(?wxGenericDirCtrl_GetTreeCtrl). -%% @doc See external documentation. -doc """ Collapse and expand the tree, thus re-creating it from scratch. @@ -302,7 +303,6 @@ reCreateTree(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGenericDirCtrl), wxe_util:queue_cmd(This,?get_env(),?wxGenericDirCtrl_ReCreateTree). -%% @doc See external documentation. -doc "Sets the default path.". -spec setDefaultPath(This, Path) -> 'ok' when This::wxGenericDirCtrl(), Path::unicode:chardata(). @@ -312,7 +312,6 @@ setDefaultPath(#wx_ref{type=ThisT}=This,Path) Path_UC = unicode:characters_to_binary(Path), wxe_util:queue_cmd(This,Path_UC,?get_env(),?wxGenericDirCtrl_SetDefaultPath). -%% @doc See external documentation. -doc "Sets the filter string.". -spec setFilter(This, Filter) -> 'ok' when This::wxGenericDirCtrl(), Filter::unicode:chardata(). @@ -322,7 +321,6 @@ setFilter(#wx_ref{type=ThisT}=This,Filter) Filter_UC = unicode:characters_to_binary(Filter), wxe_util:queue_cmd(This,Filter_UC,?get_env(),?wxGenericDirCtrl_SetFilter). -%% @doc See external documentation. -doc "Sets the current filter index (zero-based).". -spec setFilterIndex(This, N) -> 'ok' when This::wxGenericDirCtrl(), N::integer(). @@ -331,7 +329,6 @@ setFilterIndex(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxGenericDirCtrl), wxe_util:queue_cmd(This,N,?get_env(),?wxGenericDirCtrl_SetFilterIndex). -%% @doc See external documentation. -doc "Sets the current path.". -spec setPath(This, Path) -> 'ok' when This::wxGenericDirCtrl(), Path::unicode:chardata(). @@ -341,562 +338,378 @@ setPath(#wx_ref{type=ThisT}=This,Path) Path_UC = unicode:characters_to_binary(Path), wxe_util:queue_cmd(This,Path_UC,?get_env(),?wxGenericDirCtrl_SetPath). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxGenericDirCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGenericDirCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxGraphicsBrush.erl b/lib/wx/src/gen/wxGraphicsBrush.erl index 19dc0e6bf88a..6e83d52cd412 100644 --- a/lib/wx/src/gen/wxGraphicsBrush.erl +++ b/lib/wx/src/gen/wxGraphicsBrush.erl @@ -20,17 +20,17 @@ -module(wxGraphicsBrush). -moduledoc """ -Functions for wxGraphicsBrush class +A `m:wxGraphicsBrush` is a native representation of a brush. -A `m:wxGraphicsBrush` is a native representation of a brush. The contents are -specific and private to the respective renderer. Instances are ref counted and -can therefore be assigned as usual. The only way to get a valid instance is via -`wxGraphicsContext:createBrush/2` or `wxGraphicsRenderer:createBrush/2`. +The contents are specific and private to the respective renderer. Instances are ref +counted and can therefore be assigned as usual. The only way to get a valid instance is +via `wxGraphicsContext:createBrush/2` or `wxGraphicsRenderer:createBrush/2`. -This class is derived (and can use functions) from: `m:wxGraphicsObject` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGraphicsBrush](https://docs.wxwidgets.org/3.1/classwx_graphics_brush.html) +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsBrush](https://docs.wxwidgets.org/3.2/classwx_graphics_brush.html) """. -include("wxe.hrl"). -export([]). @@ -40,15 +40,12 @@ wxWidgets docs: -type wxGraphicsBrush() :: wx:wx_object(). -export_type([wxGraphicsBrush/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsContext.erl b/lib/wx/src/gen/wxGraphicsContext.erl index f0d5e2cdc914..d55ad79a1911 100644 --- a/lib/wx/src/gen/wxGraphicsContext.erl +++ b/lib/wx/src/gen/wxGraphicsContext.erl @@ -20,27 +20,30 @@ -module(wxGraphicsContext). -moduledoc """ -Functions for wxGraphicsContext class +A `m:wxGraphicsContext` instance is the object that is drawn upon. -A `m:wxGraphicsContext` instance is the object that is drawn upon. It is created -by a renderer using `wxGraphicsRenderer:createContext/2`. This can be either -directly using a renderer instance, or indirectly using the static convenience -`create/1` functions of `m:wxGraphicsContext` that always delegate the task to -the default renderer. +It is created by a renderer using `wxGraphicsRenderer:createContext/2`. This can be either directly using a renderer +instance, or indirectly using the static convenience `create/1` functions of `m:wxGraphicsContext` +that always delegate the task to the default renderer. -Remark: For some renderers (like Direct2D or Cairo) processing of drawing -operations may be deferred (Direct2D render target normally builds up a batch of -rendering commands but defers processing of these commands, Cairo operates on a -separate surface) so to make drawing results visible you need to update the -content of the context by calling `wxGraphicsContext::Flush()` (not implemented -in wx) or by destroying the context. +Remark: For some renderers (like Direct2D or Cairo) processing of drawing operations may +be deferred (Direct2D render target normally builds up a batch of rendering commands but +defers processing of these commands, Cairo operates on a separate surface) so to make +drawing results visible you need to update the content of the context by calling `wxGraphicsContext::Flush()` +(not implemented in wx) or by destroying the context. -See: `wxGraphicsRenderer:createContext/2`, `m:wxGCDC`, `m:wxDC` +See: +* `wxGraphicsRenderer:createContext/2` -This class is derived (and can use functions) from: `m:wxGraphicsObject` +* `m:wxGCDC` -wxWidgets docs: -[wxGraphicsContext](https://docs.wxwidgets.org/3.1/classwx_graphics_context.html) +* `m:wxDC` + +This class is derived, and can use functions, from: + +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsContext](https://docs.wxwidgets.org/3.2/classwx_graphics_context.html) """. -include("wxe.hrl"). -export([clip/2,clip/5,concatTransform/2,create/0,create/1,createBrush/2,createFont/2, @@ -58,19 +61,16 @@ wxWidgets docs: -type wxGraphicsContext() :: wx:wx_object(). -export_type([wxGraphicsContext/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Create a lightweight context that can be used only for measuring text.". -spec create() -> wxGraphicsContext(). create() -> wxe_util:queue_cmd(?get_env(), ?wxGraphicsContext_Create_STAT_0), wxe_util:rec(?wxGraphicsContext_Create_STAT_0). -%% @doc See external documentation. -doc """ Creates a `m:wxGraphicsContext` from a `m:wxWindowDC`. @@ -93,13 +93,11 @@ create(#wx_ref{type=WindowDCT}=WindowDC) -> wxe_util:queue_cmd(wx:typeCast(WindowDC, WindowDCType),?get_env(),?wxGraphicsContext_Create_STAT_1), wxe_util:rec(?wxGraphicsContext_Create_STAT_1). -%% @doc See external documentation. -doc """ Creates a native pen from a `m:wxPen`. -Prefer to use the overload taking `wxGraphicsPenInfo` (not implemented in wx) -unless you already have a `m:wxPen` as constructing one only to pass it to this -method is wasteful. +Prefer to use the overload taking `wxGraphicsPenInfo` (not implemented in wx) unless you +already have a `m:wxPen` as constructing one only to pass it to this method is wasteful. """. -spec createPen(This, Pen) -> wxGraphicsPen:wxGraphicsPen() when This::wxGraphicsContext(), Pen::wxPen:wxPen(). @@ -109,7 +107,6 @@ createPen(#wx_ref{type=ThisT}=This,#wx_ref{type=PenT}=Pen) -> wxe_util:queue_cmd(This,Pen,?get_env(),?wxGraphicsContext_CreatePen), wxe_util:rec(?wxGraphicsContext_CreatePen). -%% @doc See external documentation. -doc "Creates a native brush from a `m:wxBrush`.". -spec createBrush(This, Brush) -> wxGraphicsBrush:wxGraphicsBrush() when This::wxGraphicsContext(), Brush::wxBrush:wxBrush(). @@ -119,10 +116,9 @@ createBrush(#wx_ref{type=ThisT}=This,#wx_ref{type=BrushT}=Brush) -> wxe_util:queue_cmd(This,Brush,?get_env(),?wxGraphicsContext_CreateBrush), wxe_util:rec(?wxGraphicsContext_CreateBrush). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec createRadialGradientBrush(This, StartX, StartY, EndX, EndY, Radius, Stops) -> wxGraphicsBrush:wxGraphicsBrush() when This::wxGraphicsContext(), StartX::number(), StartY::number(), EndX::number(), EndY::number(), Radius::number(), Stops::wxGraphicsGradientStops:wxGraphicsGradientStops(). @@ -133,10 +129,12 @@ createRadialGradientBrush(#wx_ref{type=ThisT}=This,StartX,StartY,EndX,EndY,Radiu wxe_util:queue_cmd(This,StartX,StartY,EndX,EndY,Radius,Stops,?get_env(),?wxGraphicsContext_CreateRadialGradientBrush_6), wxe_util:rec(?wxGraphicsContext_CreateRadialGradientBrush_6). -%% @doc See external documentation. -doc """ -`Creates a native brush with a radial gradient. The brush originates at (@a startX, @a startY) and ends on a circle around (@a endX, @a endY) with the given @a radius. The gradient may be specified either by its start and end colours @a oColor and @a cColor or by a full set of gradient @a stops. The version taking wxGraphicsGradientStops is new in wxWidgets 2.9.1.` - +` Creates a native brush with a radial gradient. The brush originates at (@a startX, @a +startY) and ends on a circle around (@a endX, @a endY) with the given @a radius. The +gradient may be specified either by its start and end colours @a oColor and @a cColor or +by a full set of gradient @a stops. The version taking wxGraphicsGradientStops is new in +wxWidgets 2.9.1. ` The ability to apply a transformation matrix to the gradient was added in 3.1.3 """. -spec createRadialGradientBrush(This, StartX, StartY, EndX, EndY, Radius, OColor, CColor) -> wxGraphicsBrush:wxGraphicsBrush() when @@ -147,10 +145,9 @@ createRadialGradientBrush(#wx_ref{type=ThisT}=This,StartX,StartY,EndX,EndY,Radiu wxe_util:queue_cmd(This,StartX,StartY,EndX,EndY,Radius,wxe_util:color(OColor),wxe_util:color(CColor),?get_env(),?wxGraphicsContext_CreateRadialGradientBrush_7), wxe_util:rec(?wxGraphicsContext_CreateRadialGradientBrush_7). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec createLinearGradientBrush(This, X1, Y1, X2, Y2, Stops) -> wxGraphicsBrush:wxGraphicsBrush() when This::wxGraphicsContext(), X1::number(), Y1::number(), X2::number(), Y2::number(), Stops::wxGraphicsGradientStops:wxGraphicsGradientStops(). @@ -161,10 +158,11 @@ createLinearGradientBrush(#wx_ref{type=ThisT}=This,X1,Y1,X2,Y2,#wx_ref{type=Stop wxe_util:queue_cmd(This,X1,Y1,X2,Y2,Stops,?get_env(),?wxGraphicsContext_CreateLinearGradientBrush_5), wxe_util:rec(?wxGraphicsContext_CreateLinearGradientBrush_5). -%% @doc See external documentation. -doc """ -`Creates a native brush with a linear gradient. The brush starts at (@a x1, @a y1) and ends at (@a x2, @a y2). Either just the start and end gradient colours (@a c1 and @a c2) or full set of gradient @a stops can be specified. The version taking wxGraphicsGradientStops is new in wxWidgets 2.9.1.` - +` Creates a native brush with a linear gradient. The brush starts at (@a x1, @a y1) and +ends at (@a x2, @a y2). Either just the start and end gradient colours (@a c1 and @a c2) +or full set of gradient @a stops can be specified. The version taking +wxGraphicsGradientStops is new in wxWidgets 2.9.1. ` The `matrix` parameter was added in wxWidgets 3.1.3 """. -spec createLinearGradientBrush(This, X1, Y1, X2, Y2, C1, C2) -> wxGraphicsBrush:wxGraphicsBrush() when @@ -175,7 +173,7 @@ createLinearGradientBrush(#wx_ref{type=ThisT}=This,X1,Y1,X2,Y2,C1,C2) wxe_util:queue_cmd(This,X1,Y1,X2,Y2,wxe_util:color(C1),wxe_util:color(C2),?get_env(),?wxGraphicsContext_CreateLinearGradientBrush_6), wxe_util:rec(?wxGraphicsContext_CreateLinearGradientBrush_6). -%% @equiv createFont(This,Font, []) +-doc(#{equiv => createFont(This,Font, [])}). -spec createFont(This, Font) -> wxGraphicsFont:wxGraphicsFont() when This::wxGraphicsContext(), Font::wxFont:wxFont(). @@ -183,12 +181,6 @@ createFont(This,Font) when is_record(This, wx_ref),is_record(Font, wx_ref) -> createFont(This,Font, []). -%% @doc See external documentation. -%%
Also:
-%% createFont(This, Font, [Option]) -> wxGraphicsFont:wxGraphicsFont() when
-%% This::wxGraphicsContext(), Font::wxFont:wxFont(),
-%% Option :: {'col', wx:wx_colour()}.
-%% -doc """ Creates a native graphics font from a `m:wxFont` and a text colour. @@ -213,12 +205,10 @@ createFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font, Options) wxe_util:queue_cmd(This,Font, Opts,?get_env(),?wxGraphicsContext_CreateFont_2), wxe_util:rec(?wxGraphicsContext_CreateFont_2). -%% @doc See external documentation. -doc """ Creates a font object with the specified attributes. -The use of overload taking `m:wxFont` is preferred, see -`wxGraphicsRenderer:createFont/4` for more details. +The use of overload taking `m:wxFont` is preferred, see `wxGraphicsRenderer:createFont/4` for more details. Remark: For Direct2D graphics fonts can be created from TrueType fonts only. @@ -239,7 +229,7 @@ createFont(#wx_ref{type=ThisT}=This,SizeInPixels,Facename, Options) wxe_util:queue_cmd(This,SizeInPixels,Facename_UC, Opts,?get_env(),?wxGraphicsContext_CreateFont_3), wxe_util:rec(?wxGraphicsContext_CreateFont_3). -%% @equiv createMatrix(This, []) +-doc(#{equiv => createMatrix(This, [])}). -spec createMatrix(This) -> wxGraphicsMatrix:wxGraphicsMatrix() when This::wxGraphicsContext(). @@ -247,7 +237,6 @@ createMatrix(This) when is_record(This, wx_ref) -> createMatrix(This, []). -%% @doc See external documentation. -doc """ Creates a native affine transformation matrix from the passed in values. @@ -275,7 +264,6 @@ createMatrix(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGraphicsContext_CreateMatrix), wxe_util:rec(?wxGraphicsContext_CreateMatrix). -%% @doc See external documentation. -doc "Creates a native graphics path which is initially empty.". -spec createPath(This) -> wxGraphicsPath:wxGraphicsPath() when This::wxGraphicsContext(). @@ -284,14 +272,22 @@ createPath(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsContext_CreatePath), wxe_util:rec(?wxGraphicsContext_CreatePath). -%% @doc See external documentation. -doc """ -Sets the clipping region to the intersection of the given region and the -previously set clipping region. +Sets the clipping region to the intersection of the given region and the previously set +clipping region. The clipping region is an area to which drawing is restricted. Remark: + +* Clipping region should be given in logical coordinates. + +* Calling this function can only make the clipping region smaller, never larger. + +* You need to call `resetClip/1` first if you want to set the clipping region exactly to the region specified. + +* If resulting clipping region is empty, then all drawing upon the context is clipped out +(all changes made by drawing operations are masked out). """. -spec clip(This, Region) -> 'ok' when This::wxGraphicsContext(), Region::wxRegion:wxRegion(). @@ -300,10 +296,9 @@ clip(#wx_ref{type=ThisT}=This,#wx_ref{type=RegionT}=Region) -> ?CLASS(RegionT,wxRegion), wxe_util:queue_cmd(This,Region,?get_env(),?wxGraphicsContext_Clip_1). -%% @doc See external documentation. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec clip(This, X, Y, W, H) -> 'ok' when This::wxGraphicsContext(), X::number(), Y::number(), W::number(), H::number(). @@ -312,7 +307,6 @@ clip(#wx_ref{type=ThisT}=This,X,Y,W,H) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxGraphicsContext_Clip_4). -%% @doc See external documentation. -doc "Resets the clipping to original shape.". -spec resetClip(This) -> 'ok' when This::wxGraphicsContext(). @@ -320,12 +314,11 @@ resetClip(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,?get_env(),?wxGraphicsContext_ResetClip). -%% @doc See external documentation. -doc """ Draws the bitmap. -In case of a mono bitmap, this is treated as a mask and the current brushed is -used for filling. +In case of a mono bitmap, this is treated as a mask and the current brushed is used for +filling. """. -spec drawBitmap(This, Bmp, X, Y, W, H) -> 'ok' when This::wxGraphicsContext(), Bmp::wxBitmap:wxBitmap(), X::number(), Y::number(), W::number(), H::number(). @@ -335,7 +328,6 @@ drawBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=BmpT}=Bmp,X,Y,W,H) ?CLASS(BmpT,wxBitmap), wxe_util:queue_cmd(This,Bmp,X,Y,W,H,?get_env(),?wxGraphicsContext_DrawBitmap). -%% @doc See external documentation. -doc "Draws an ellipse.". -spec drawEllipse(This, X, Y, W, H) -> 'ok' when This::wxGraphicsContext(), X::number(), Y::number(), W::number(), H::number(). @@ -344,7 +336,6 @@ drawEllipse(#wx_ref{type=ThisT}=This,X,Y,W,H) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxGraphicsContext_DrawEllipse). -%% @doc See external documentation. -doc "Draws the icon.". -spec drawIcon(This, Icon, X, Y, W, H) -> 'ok' when This::wxGraphicsContext(), Icon::wxIcon:wxIcon(), X::number(), Y::number(), W::number(), H::number(). @@ -354,7 +345,7 @@ drawIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon,X,Y,W,H) ?CLASS(IconT,wxIcon), wxe_util:queue_cmd(This,Icon,X,Y,W,H,?get_env(),?wxGraphicsContext_DrawIcon). -%% @equiv drawLines(This,Points, []) +-doc(#{equiv => drawLines(This,Points, [])}). -spec drawLines(This, Points) -> 'ok' when This::wxGraphicsContext(), Points::[{X::float(), Y::float()}]. @@ -362,9 +353,8 @@ drawLines(This,Points) when is_record(This, wx_ref),is_list(Points) -> drawLines(This,Points, []). -%% @doc See external documentation. -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc "Draws a polygon.". +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec drawLines(This, Points, [Option]) -> 'ok' when This::wxGraphicsContext(), Points::[{X::float(), Y::float()}], Option :: {'fillStyle', wx:wx_enum()}. @@ -376,7 +366,7 @@ drawLines(#wx_ref{type=ThisT}=This,Points, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Points, Opts,?get_env(),?wxGraphicsContext_DrawLines). -%% @equiv drawPath(This,Path, []) +-doc(#{equiv => drawPath(This,Path, [])}). -spec drawPath(This, Path) -> 'ok' when This::wxGraphicsContext(), Path::wxGraphicsPath:wxGraphicsPath(). @@ -384,9 +374,8 @@ drawPath(This,Path) when is_record(This, wx_ref),is_record(Path, wx_ref) -> drawPath(This,Path, []). -%% @doc See external documentation. -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc "Draws the path by first filling and then stroking.". +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec drawPath(This, Path, [Option]) -> 'ok' when This::wxGraphicsContext(), Path::wxGraphicsPath:wxGraphicsPath(), Option :: {'fillStyle', wx:wx_enum()}. @@ -399,7 +388,6 @@ drawPath(#wx_ref{type=ThisT}=This,#wx_ref{type=PathT}=Path, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Path, Opts,?get_env(),?wxGraphicsContext_DrawPath). -%% @doc See external documentation. -doc "Draws a rectangle.". -spec drawRectangle(This, X, Y, W, H) -> 'ok' when This::wxGraphicsContext(), X::number(), Y::number(), W::number(), H::number(). @@ -408,7 +396,6 @@ drawRectangle(#wx_ref{type=ThisT}=This,X,Y,W,H) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxGraphicsContext_DrawRectangle). -%% @doc See external documentation. -doc "Draws a rounded rectangle.". -spec drawRoundedRectangle(This, X, Y, W, H, Radius) -> 'ok' when This::wxGraphicsContext(), X::number(), Y::number(), W::number(), H::number(), Radius::number(). @@ -417,7 +404,6 @@ drawRoundedRectangle(#wx_ref{type=ThisT}=This,X,Y,W,H,Radius) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,X,Y,W,H,Radius,?get_env(),?wxGraphicsContext_DrawRoundedRectangle). -%% @doc See external documentation. -doc "Draws text at the defined position.". -spec drawText(This, Str, X, Y) -> 'ok' when This::wxGraphicsContext(), Str::unicode:chardata(), X::number(), Y::number(). @@ -427,11 +413,6 @@ drawText(#wx_ref{type=ThisT}=This,Str,X,Y) Str_UC = unicode:characters_to_binary(Str), wxe_util:queue_cmd(This,Str_UC,X,Y,?get_env(),?wxGraphicsContext_DrawText_3). -%% @doc See external documentation. -%%
Also:
-%% drawText(This, Str, X, Y, BackgroundBrush) -> 'ok' when
-%% This::wxGraphicsContext(), Str::unicode:chardata(), X::number(), Y::number(), BackgroundBrush::wxGraphicsBrush:wxGraphicsBrush().
-%% -doc "Draws text at the defined position.". -spec drawText(This, Str, X, Y, Angle) -> 'ok' when This::wxGraphicsContext(), Str::unicode:chardata(), X::number(), Y::number(), Angle::number(); @@ -449,7 +430,6 @@ drawText(#wx_ref{type=ThisT}=This,Str,X,Y,#wx_ref{type=BackgroundBrushT}=Backgro ?CLASS(BackgroundBrushT,wxGraphicsBrush), wxe_util:queue_cmd(This,Str_UC,X,Y,BackgroundBrush,?get_env(),?wxGraphicsContext_DrawText_4_1). -%% @doc See external documentation. -doc "Draws text at the defined position.". -spec drawText(This, Str, X, Y, Angle, BackgroundBrush) -> 'ok' when This::wxGraphicsContext(), Str::unicode:chardata(), X::number(), Y::number(), Angle::number(), BackgroundBrush::wxGraphicsBrush:wxGraphicsBrush(). @@ -460,7 +440,7 @@ drawText(#wx_ref{type=ThisT}=This,Str,X,Y,Angle,#wx_ref{type=BackgroundBrushT}=B ?CLASS(BackgroundBrushT,wxGraphicsBrush), wxe_util:queue_cmd(This,Str_UC,X,Y,Angle,BackgroundBrush,?get_env(),?wxGraphicsContext_DrawText_5). -%% @equiv fillPath(This,Path, []) +-doc(#{equiv => fillPath(This,Path, [])}). -spec fillPath(This, Path) -> 'ok' when This::wxGraphicsContext(), Path::wxGraphicsPath:wxGraphicsPath(). @@ -468,9 +448,8 @@ fillPath(This,Path) when is_record(This, wx_ref),is_record(Path, wx_ref) -> fillPath(This,Path, []). -%% @doc See external documentation. -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc "Fills the path with the current brush.". +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec fillPath(This, Path, [Option]) -> 'ok' when This::wxGraphicsContext(), Path::wxGraphicsPath:wxGraphicsPath(), Option :: {'fillStyle', wx:wx_enum()}. @@ -483,7 +462,6 @@ fillPath(#wx_ref{type=ThisT}=This,#wx_ref{type=PathT}=Path, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Path, Opts,?get_env(),?wxGraphicsContext_FillPath). -%% @doc See external documentation. -doc "Strokes along a path with the current pen.". -spec strokePath(This, Path) -> 'ok' when This::wxGraphicsContext(), Path::wxGraphicsPath:wxGraphicsPath(). @@ -492,7 +470,6 @@ strokePath(#wx_ref{type=ThisT}=This,#wx_ref{type=PathT}=Path) -> ?CLASS(PathT,wxGraphicsPath), wxe_util:queue_cmd(This,Path,?get_env(),?wxGraphicsContext_StrokePath). -%% @doc See external documentation. -doc """ Fills the `widths` array with the widths from the beginning of `text` to the corresponding character of `text`. @@ -506,7 +483,6 @@ getPartialTextExtents(#wx_ref{type=ThisT}=This,Text) wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxGraphicsContext_GetPartialTextExtents), wxe_util:rec(?wxGraphicsContext_GetPartialTextExtents). -%% @doc See external documentation. -doc "Gets the dimensions of the string using the currently selected font.". -spec getTextExtent(This, Text) -> Result when Result ::{Width::number(), Height::number(), Descent::number(), ExternalLeading::number()}, @@ -518,7 +494,6 @@ getTextExtent(#wx_ref{type=ThisT}=This,Text) wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxGraphicsContext_GetTextExtent), wxe_util:rec(?wxGraphicsContext_GetTextExtent). -%% @doc See external documentation. -doc "Rotates the current transformation matrix (in radians).". -spec rotate(This, Angle) -> 'ok' when This::wxGraphicsContext(), Angle::number(). @@ -527,7 +502,6 @@ rotate(#wx_ref{type=ThisT}=This,Angle) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,Angle,?get_env(),?wxGraphicsContext_Rotate). -%% @doc See external documentation. -doc "Scales the current transformation matrix.". -spec scale(This, XScale, YScale) -> 'ok' when This::wxGraphicsContext(), XScale::number(), YScale::number(). @@ -536,7 +510,6 @@ scale(#wx_ref{type=ThisT}=This,XScale,YScale) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,XScale,YScale,?get_env(),?wxGraphicsContext_Scale). -%% @doc See external documentation. -doc "Translates the current transformation matrix.". -spec translate(This, Dx, Dy) -> 'ok' when This::wxGraphicsContext(), Dx::number(), Dy::number(). @@ -545,7 +518,6 @@ translate(#wx_ref{type=ThisT}=This,Dx,Dy) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,Dx,Dy,?get_env(),?wxGraphicsContext_Translate). -%% @doc See external documentation. -doc "Gets the current transformation matrix of this context.". -spec getTransform(This) -> wxGraphicsMatrix:wxGraphicsMatrix() when This::wxGraphicsContext(). @@ -554,7 +526,6 @@ getTransform(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsContext_GetTransform), wxe_util:rec(?wxGraphicsContext_GetTransform). -%% @doc See external documentation. -doc "Sets the current transformation matrix of this context.". -spec setTransform(This, Matrix) -> 'ok' when This::wxGraphicsContext(), Matrix::wxGraphicsMatrix:wxGraphicsMatrix(). @@ -563,7 +534,6 @@ setTransform(#wx_ref{type=ThisT}=This,#wx_ref{type=MatrixT}=Matrix) -> ?CLASS(MatrixT,wxGraphicsMatrix), wxe_util:queue_cmd(This,Matrix,?get_env(),?wxGraphicsContext_SetTransform). -%% @doc See external documentation. -doc "Concatenates the passed in transform with the current transform of this context.". -spec concatTransform(This, Matrix) -> 'ok' when This::wxGraphicsContext(), Matrix::wxGraphicsMatrix:wxGraphicsMatrix(). @@ -572,7 +542,6 @@ concatTransform(#wx_ref{type=ThisT}=This,#wx_ref{type=MatrixT}=Matrix) -> ?CLASS(MatrixT,wxGraphicsMatrix), wxe_util:queue_cmd(This,Matrix,?get_env(),?wxGraphicsContext_ConcatTransform). -%% @doc See external documentation. -doc "Sets the brush for filling paths.". -spec setBrush(This, Brush) -> 'ok' when This::wxGraphicsContext(), Brush::wxGraphicsBrush:wxGraphicsBrush() | wxBrush:wxBrush(). @@ -587,7 +556,6 @@ setBrush(#wx_ref{type=ThisT}=This,#wx_ref{type=BrushT}=Brush) -> end, wxe_util:queue_cmd(This,wx:typeCast(Brush, BrushType),?get_env(),?wxGraphicsContext_SetBrush). -%% @doc See external documentation. -doc "Sets the font for drawing text.". -spec setFont(This, Font) -> 'ok' when This::wxGraphicsContext(), Font::wxGraphicsFont:wxGraphicsFont(). @@ -596,7 +564,6 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxGraphicsFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxGraphicsContext_SetFont_1). -%% @doc See external documentation. -doc """ Sets the font for drawing text. @@ -610,7 +577,6 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font,Colour) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,wxe_util:color(Colour),?get_env(),?wxGraphicsContext_SetFont_2). -%% @doc See external documentation. -doc "Sets the pen used for stroking.". -spec setPen(This, Pen) -> 'ok' when This::wxGraphicsContext(), Pen::wxPen:wxPen() | wxGraphicsPen:wxGraphicsPen(). @@ -625,7 +591,6 @@ setPen(#wx_ref{type=ThisT}=This,#wx_ref{type=PenT}=Pen) -> end, wxe_util:queue_cmd(This,wx:typeCast(Pen, PenType),?get_env(),?wxGraphicsContext_SetPen). -%% @doc See external documentation. -doc "Strokes a single line.". -spec strokeLine(This, X1, Y1, X2, Y2) -> 'ok' when This::wxGraphicsContext(), X1::number(), Y1::number(), X2::number(), Y2::number(). @@ -634,12 +599,11 @@ strokeLine(#wx_ref{type=ThisT}=This,X1,Y1,X2,Y2) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,X1,Y1,X2,Y2,?get_env(),?wxGraphicsContext_StrokeLine). -%% @doc See external documentation. -doc """ Stroke lines connecting all the points. -Unlike the other overload of this function, this method draws a single polyline -and not a number of disconnected lines. +Unlike the other overload of this function, this method draws a single polyline and not a +number of disconnected lines. """. -spec strokeLines(This, Points) -> 'ok' when This::wxGraphicsContext(), Points::[{X::float(), Y::float()}]. @@ -648,21 +612,14 @@ strokeLines(#wx_ref{type=ThisT}=This,Points) ?CLASS(ThisT,wxGraphicsContext), wxe_util:queue_cmd(This,Points,?get_env(),?wxGraphicsContext_StrokeLines). -%% @doc Destroys this object, do not use object again --doc """ -Creates a `m:wxGraphicsContext` from a `m:wxWindow`. - -See: `wxGraphicsRenderer:createContext/2` -""". +-doc "Destroys the object". -spec destroy(This::wxGraphicsContext()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGraphicsContext), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsFont.erl b/lib/wx/src/gen/wxGraphicsFont.erl index cb90cf2d4a69..75707a316424 100644 --- a/lib/wx/src/gen/wxGraphicsFont.erl +++ b/lib/wx/src/gen/wxGraphicsFont.erl @@ -20,17 +20,17 @@ -module(wxGraphicsFont). -moduledoc """ -Functions for wxGraphicsFont class +A `m:wxGraphicsFont` is a native representation of a font. -A `m:wxGraphicsFont` is a native representation of a font. The contents are -specific and private to the respective renderer. Instances are ref counted and -can therefore be assigned as usual. The only way to get a valid instance is via -`wxGraphicsContext:createFont/4` or `wxGraphicsRenderer:createFont/4`. +The contents are specific and private to the respective renderer. Instances are ref +counted and can therefore be assigned as usual. The only way to get a valid instance is +via `wxGraphicsContext:createFont/4` or `wxGraphicsRenderer:createFont/4`. -This class is derived (and can use functions) from: `m:wxGraphicsObject` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGraphicsFont](https://docs.wxwidgets.org/3.1/classwx_graphics_font.html) +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsFont](https://docs.wxwidgets.org/3.2/classwx_graphics_font.html) """. -include("wxe.hrl"). -export([]). @@ -40,15 +40,12 @@ wxWidgets docs: -type wxGraphicsFont() :: wx:wx_object(). -export_type([wxGraphicsFont/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsGradientStops.erl b/lib/wx/src/gen/wxGraphicsGradientStops.erl index 9fc3ea3d07f5..767ea567dd33 100644 --- a/lib/wx/src/gen/wxGraphicsGradientStops.erl +++ b/lib/wx/src/gen/wxGraphicsGradientStops.erl @@ -23,17 +23,15 @@ Represents a collection of wxGraphicGradientStop values for use with CreateLinearGradientBrush and CreateRadialGradientBrush. -The stops are maintained in order of position. If two or more stops are added -with the same position then the one(s) added later come later. This can be -useful for producing discontinuities in the colour gradient. +The stops are maintained in order of position. If two or more stops are added with the +same position then the one(s) added later come later. This can be useful for producing +discontinuities in the colour gradient. -Notice that this class is write-once, you can't modify the stops once they had -been added. +Notice that this class is write-once, you can't modify the stops once they had been added. Since: 2.9.1 -wxWidgets docs: -[wxGraphicsGradientStops](https://docs.wxwidgets.org/3.1/classwx_graphics_gradient_stops.html) +wxWidgets docs: [wxGraphicsGradientStops](https://docs.wxwidgets.org/3.2/classwx_graphics_gradient_stops.html) """. -include("wxe.hrl"). -export([add/3,destroy/1,getCount/1,getEndColour/1,getStartColour/1,item/2,new/0, @@ -44,22 +42,20 @@ wxWidgets docs: -type wxGraphicsGradientStops() :: wx:wx_object(). -export_type([wxGraphicsGradientStops/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGraphicsGradientStops(). new() -> new([]). -%% @doc See external documentation. -doc """ Initializes the gradient stops with the given boundary colours. -Creates a `m:wxGraphicsGradientStops` instance with start colour given by -`startCol` and end colour given by `endCol`. +Creates a `m:wxGraphicsGradientStops` instance with start colour given by `startCol` and +end colour given by `endCol`. """. -spec new([Option]) -> wxGraphicsGradientStops() when Option :: {'startCol', wx:wx_colour()} @@ -73,7 +69,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGraphicsGradientStops_new), wxe_util:rec(?wxGraphicsGradientStops_new). -%% @doc See external documentation. -doc "Returns the stop at the given index.". -spec item(This, N) -> {wx:wx_colour4(), float()} when This::wxGraphicsGradientStops(), N::integer(). @@ -83,7 +78,6 @@ item(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxGraphicsGradientStops_Item), wxe_util:rec(?wxGraphicsGradientStops_Item). -%% @doc See external documentation. -doc "Returns the number of stops.". -spec getCount(This) -> integer() when This::wxGraphicsGradientStops(). @@ -92,7 +86,6 @@ getCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsGradientStops_GetCount), wxe_util:rec(?wxGraphicsGradientStops_GetCount). -%% @doc See external documentation. -doc "Set the start colour to `col`.". -spec setStartColour(This, Col) -> 'ok' when This::wxGraphicsGradientStops(), Col::wx:wx_colour(). @@ -101,7 +94,6 @@ setStartColour(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxGraphicsGradientStops), wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxGraphicsGradientStops_SetStartColour). -%% @doc See external documentation. -doc "Returns the start colour.". -spec getStartColour(This) -> wx:wx_colour4() when This::wxGraphicsGradientStops(). @@ -110,7 +102,6 @@ getStartColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsGradientStops_GetStartColour), wxe_util:rec(?wxGraphicsGradientStops_GetStartColour). -%% @doc See external documentation. -doc "Set the end colour to `col`.". -spec setEndColour(This, Col) -> 'ok' when This::wxGraphicsGradientStops(), Col::wx:wx_colour(). @@ -119,7 +110,6 @@ setEndColour(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxGraphicsGradientStops), wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxGraphicsGradientStops_SetEndColour). -%% @doc See external documentation. -doc "Returns the end colour.". -spec getEndColour(This) -> wx:wx_colour4() when This::wxGraphicsGradientStops(). @@ -128,7 +118,6 @@ getEndColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsGradientStops_GetEndColour), wxe_util:rec(?wxGraphicsGradientStops_GetEndColour). -%% @doc See external documentation. -doc "Add a new stop.". -spec add(This, Col, Pos) -> 'ok' when This::wxGraphicsGradientStops(), Col::wx:wx_colour(), Pos::number(). @@ -137,8 +126,7 @@ add(#wx_ref{type=ThisT}=This,Col,Pos) ?CLASS(ThisT,wxGraphicsGradientStops), wxe_util:queue_cmd(This,wxe_util:color(Col),Pos,?get_env(),?wxGraphicsGradientStops_Add). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGraphicsGradientStops()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGraphicsGradientStops), diff --git a/lib/wx/src/gen/wxGraphicsMatrix.erl b/lib/wx/src/gen/wxGraphicsMatrix.erl index 0c737370b877..dc74e29f3dff 100644 --- a/lib/wx/src/gen/wxGraphicsMatrix.erl +++ b/lib/wx/src/gen/wxGraphicsMatrix.erl @@ -20,18 +20,17 @@ -module(wxGraphicsMatrix). -moduledoc """ -Functions for wxGraphicsMatrix class +A `m:wxGraphicsMatrix` is a native representation of an affine matrix. -A `m:wxGraphicsMatrix` is a native representation of an affine matrix. The -contents are specific and private to the respective renderer. Instances are ref -counted and can therefore be assigned as usual. The only way to get a valid -instance is via `wxGraphicsContext:createMatrix/2` or -`wxGraphicsRenderer:createMatrix/2`. +The contents are specific and private to the respective renderer. Instances are ref +counted and can therefore be assigned as usual. The only way to get a valid instance is +via `wxGraphicsContext:createMatrix/2` or `wxGraphicsRenderer:createMatrix/2`. -This class is derived (and can use functions) from: `m:wxGraphicsObject` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGraphicsMatrix](https://docs.wxwidgets.org/3.1/classwx_graphics_matrix.html) +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsMatrix](https://docs.wxwidgets.org/3.2/classwx_graphics_matrix.html) """. -include("wxe.hrl"). -export([concat/2,get/1,invert/1,isEqual/2,isIdentity/1,rotate/2,scale/3,set/1, @@ -42,18 +41,15 @@ wxWidgets docs: -type wxGraphicsMatrix() :: wx:wx_object(). -export_type([wxGraphicsMatrix/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Concatenates the matrix passed with the current matrix. -The effect of the resulting transformation is to first apply the transformation -in `t` to the coordinates and then apply the transformation in the current -matrix to the coordinates. +The effect of the resulting transformation is to first apply the transformation in `t` to +the coordinates and then apply the transformation in the current matrix to the coordinates. """. -spec concat(This, T) -> 'ok' when This::wxGraphicsMatrix(), T::wxGraphicsMatrix(). @@ -62,7 +58,6 @@ concat(#wx_ref{type=ThisT}=This,#wx_ref{type=TT}=T) -> ?CLASS(TT,wxGraphicsMatrix), wxe_util:queue_cmd(This,T,?get_env(),?wxGraphicsMatrix_Concat). -%% @doc See external documentation. -doc "Returns the component values of the matrix via the argument pointers.". -spec get(This) -> Result when Result ::{A::number(), B::number(), C::number(), D::number(), Tx::number(), Ty::number()}, @@ -72,7 +67,6 @@ get(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsMatrix_Get), wxe_util:rec(?wxGraphicsMatrix_Get). -%% @doc See external documentation. -doc "Inverts the matrix.". -spec invert(This) -> 'ok' when This::wxGraphicsMatrix(). @@ -80,7 +74,6 @@ invert(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGraphicsMatrix), wxe_util:queue_cmd(This,?get_env(),?wxGraphicsMatrix_Invert). -%% @doc See external documentation. -doc "Returns true if the elements of the transformation matrix are equal.". -spec isEqual(This, T) -> boolean() when This::wxGraphicsMatrix(), T::wxGraphicsMatrix(). @@ -90,7 +83,6 @@ isEqual(#wx_ref{type=ThisT}=This,#wx_ref{type=TT}=T) -> wxe_util:queue_cmd(This,T,?get_env(),?wxGraphicsMatrix_IsEqual), wxe_util:rec(?wxGraphicsMatrix_IsEqual). -%% @doc See external documentation. -doc "Return true if this is the identity matrix.". -spec isIdentity(This) -> boolean() when This::wxGraphicsMatrix(). @@ -99,7 +91,6 @@ isIdentity(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsMatrix_IsIdentity), wxe_util:rec(?wxGraphicsMatrix_IsIdentity). -%% @doc See external documentation. -doc "Rotates this matrix clockwise (in radians).". -spec rotate(This, Angle) -> 'ok' when This::wxGraphicsMatrix(), Angle::number(). @@ -108,7 +99,6 @@ rotate(#wx_ref{type=ThisT}=This,Angle) ?CLASS(ThisT,wxGraphicsMatrix), wxe_util:queue_cmd(This,Angle,?get_env(),?wxGraphicsMatrix_Rotate). -%% @doc See external documentation. -doc "Scales this matrix.". -spec scale(This, XScale, YScale) -> 'ok' when This::wxGraphicsMatrix(), XScale::number(), YScale::number(). @@ -117,7 +107,6 @@ scale(#wx_ref{type=ThisT}=This,XScale,YScale) ?CLASS(ThisT,wxGraphicsMatrix), wxe_util:queue_cmd(This,XScale,YScale,?get_env(),?wxGraphicsMatrix_Scale). -%% @doc See external documentation. -doc "Translates this matrix.". -spec translate(This, Dx, Dy) -> 'ok' when This::wxGraphicsMatrix(), Dx::number(), Dy::number(). @@ -126,7 +115,7 @@ translate(#wx_ref{type=ThisT}=This,Dx,Dy) ?CLASS(ThisT,wxGraphicsMatrix), wxe_util:queue_cmd(This,Dx,Dy,?get_env(),?wxGraphicsMatrix_Translate). -%% @equiv set(This, []) +-doc(#{equiv => set(This, [])}). -spec set(This) -> 'ok' when This::wxGraphicsMatrix(). @@ -134,11 +123,7 @@ set(This) when is_record(This, wx_ref) -> set(This, []). -%% @doc See external documentation. --doc """ -Sets the matrix to the respective values (default values are the identity -matrix). -""". +-doc "Sets the matrix to the respective values (default values are the identity matrix).". -spec set(This, [Option]) -> 'ok' when This::wxGraphicsMatrix(), Option :: {'a', number()} @@ -160,7 +145,6 @@ set(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGraphicsMatrix_Set). -%% @doc See external documentation. -doc "Applies this matrix to a point.". -spec transformPoint(This) -> {X::number(), Y::number()} when This::wxGraphicsMatrix(). @@ -169,7 +153,6 @@ transformPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsMatrix_TransformPoint), wxe_util:rec(?wxGraphicsMatrix_TransformPoint). -%% @doc See external documentation. -doc """ Applies this matrix to a distance (ie. @@ -183,9 +166,7 @@ transformDistance(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxGraphicsMatrix_TransformDistance). %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsObject.erl b/lib/wx/src/gen/wxGraphicsObject.erl index c6b6487ebcff..6c0d7a9e3277 100644 --- a/lib/wx/src/gen/wxGraphicsObject.erl +++ b/lib/wx/src/gen/wxGraphicsObject.erl @@ -20,16 +20,20 @@ -module(wxGraphicsObject). -moduledoc """ -Functions for wxGraphicsObject class +This class is the superclass of native graphics objects like pens etc. -This class is the superclass of native graphics objects like pens etc. It allows -reference counting. Not instantiated by user code. +It allows reference counting. Not instantiated by user code. -See: `m:wxGraphicsBrush`, `m:wxGraphicsPen`, `m:wxGraphicsMatrix`, -`m:wxGraphicsPath` +See: +* `m:wxGraphicsBrush` -wxWidgets docs: -[wxGraphicsObject](https://docs.wxwidgets.org/3.1/classwx_graphics_object.html) +* `m:wxGraphicsPen` + +* `m:wxGraphicsMatrix` + +* `m:wxGraphicsPath` + +wxWidgets docs: [wxGraphicsObject](https://docs.wxwidgets.org/3.2/classwx_graphics_object.html) """. -include("wxe.hrl"). -export([destroy/1,getRenderer/1,isNull/1]). @@ -39,14 +43,12 @@ wxWidgets docs: -type wxGraphicsObject() :: wx:wx_object(). -export_type([wxGraphicsObject/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns the renderer that was used to create this instance, or NULL if it has -not been initialized yet. +Returns the renderer that was used to create this instance, or NULL if it has not been +initialized yet. """. -spec getRenderer(This) -> wxGraphicsRenderer:wxGraphicsRenderer() when This::wxGraphicsObject(). @@ -55,7 +57,6 @@ getRenderer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsObject_GetRenderer), wxe_util:rec(?wxGraphicsObject_GetRenderer). -%% @doc See external documentation. -doc "Return: false if this object is valid, otherwise returns true.". -spec isNull(This) -> boolean() when This::wxGraphicsObject(). @@ -64,7 +65,7 @@ isNull(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsObject_IsNull), wxe_util:rec(?wxGraphicsObject_IsNull). -%% @doc Destroys this object, do not use object again +-doc "Destroys the object". -spec destroy(This::wxGraphicsObject()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGraphicsObject), diff --git a/lib/wx/src/gen/wxGraphicsPath.erl b/lib/wx/src/gen/wxGraphicsPath.erl index 1898c412b83e..f3b7841ab712 100644 --- a/lib/wx/src/gen/wxGraphicsPath.erl +++ b/lib/wx/src/gen/wxGraphicsPath.erl @@ -20,18 +20,17 @@ -module(wxGraphicsPath). -moduledoc """ -Functions for wxGraphicsPath class +A `m:wxGraphicsPath` is a native representation of a geometric path. -A `m:wxGraphicsPath` is a native representation of a geometric path. The -contents are specific and private to the respective renderer. Instances are -reference counted and can therefore be assigned as usual. The only way to get a -valid instance is by using `wxGraphicsContext:createPath/1` or -`wxGraphicsRenderer:createPath/1`. +The contents are specific and private to the respective renderer. Instances are reference +counted and can therefore be assigned as usual. The only way to get a valid instance is by +using `wxGraphicsContext:createPath/1` or `wxGraphicsRenderer:createPath/1`. -This class is derived (and can use functions) from: `m:wxGraphicsObject` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGraphicsPath](https://docs.wxwidgets.org/3.1/classwx_graphics_path.html) +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsPath](https://docs.wxwidgets.org/3.2/classwx_graphics_path.html) """. -include("wxe.hrl"). -export([addArc/6,addArc/7,addArcToPoint/6,addCircle/4,addCurveToPoint/4,addCurveToPoint/7, @@ -45,12 +44,10 @@ wxWidgets docs: -type wxGraphicsPath() :: wx:wx_object(). -export_type([wxGraphicsPath/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Begins a new subpath at `p`.". -spec moveToPoint(This, P) -> 'ok' when This::wxGraphicsPath(), P::{X::float(), Y::float()}. @@ -59,7 +56,6 @@ moveToPoint(#wx_ref{type=ThisT}=This,{PX,PY} = P) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,P,?get_env(),?wxGraphicsPath_MoveToPoint_1). -%% @doc See external documentation. -doc "Begins a new subpath at (`x`,`y`).". -spec moveToPoint(This, X, Y) -> 'ok' when This::wxGraphicsPath(), X::number(), Y::number(). @@ -68,7 +64,7 @@ moveToPoint(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxGraphicsPath_MoveToPoint_2). -%% @doc See external documentation. +-doc "". -spec addArc(This, C, R, StartAngle, EndAngle, Clockwise) -> 'ok' when This::wxGraphicsPath(), C::{X::float(), Y::float()}, R::number(), StartAngle::number(), EndAngle::number(), Clockwise::boolean(). addArc(#wx_ref{type=ThisT}=This,{CX,CY} = C,R,StartAngle,EndAngle,Clockwise) @@ -76,25 +72,23 @@ addArc(#wx_ref{type=ThisT}=This,{CX,CY} = C,R,StartAngle,EndAngle,Clockwise) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,C,R,StartAngle,EndAngle,Clockwise,?get_env(),?wxGraphicsPath_AddArc_5). -%% @doc See external documentation. -doc """ Adds an arc of a circle. -The circle is defined by the coordinates of its centre (`x`, `y`) or `c` and its -radius `r`. The arc goes from the starting angle `startAngle` to `endAngle` -either clockwise or counter-clockwise depending on the value of `clockwise` -argument. +The circle is defined by the coordinates of its centre (`x`, `y`) or `c` and its radius `r`. +The arc goes from the starting angle `startAngle` to `endAngle` either clockwise or +counter-clockwise depending on the value of `clockwise` argument. -The angles are measured in radians but, contrary to the usual mathematical -convention, are always `clockwise` from the horizontal axis. +The angles are measured in radians but, contrary to the usual mathematical convention, +are always `clockwise` from the horizontal axis. -If for clockwise arc `endAngle` is less than `startAngle` it will be -progressively increased by 2*pi until it is greater than `startAngle`. If for -counter-clockwise arc `endAngle` is greater than `startAngle` it will be -progressively decreased by 2*pi until it is less than `startAngle`. +If for clockwise arc `endAngle` is less than `startAngle` it will be progressively +increased by 2*pi until it is greater than `startAngle`. If for counter-clockwise arc `endAngle` +is greater than `startAngle` it will be progressively decreased by 2*pi until it is less +than `startAngle`. -If there is a current point set, an initial line segment will be added to the -path to connect the current point to the beginning of the arc. +If there is a current point set, an initial line segment will be added to the path to +connect the current point to the beginning of the arc. """. -spec addArc(This, X, Y, R, StartAngle, EndAngle, Clockwise) -> 'ok' when This::wxGraphicsPath(), X::number(), Y::number(), R::number(), StartAngle::number(), EndAngle::number(), Clockwise::boolean(). @@ -103,17 +97,14 @@ addArc(#wx_ref{type=ThisT}=This,X,Y,R,StartAngle,EndAngle,Clockwise) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,R,StartAngle,EndAngle,Clockwise,?get_env(),?wxGraphicsPath_AddArc_6). -%% @doc See external documentation. -doc """ -Adds an arc (of a circle with radius `r`) that is tangent to the line connecting -current point and (`x1`, `y1`) and to the line connecting (`x1`, `y1`) and -(`x2`, `y2`). - -If the current point and the starting point of the arc are different, a straight -line connecting these points is also appended. If there is no current point -before the call to `addArcToPoint/6` this function will behave as if preceded by -a call to MoveToPoint(0, 0). After this call the current point will be at the -ending point of the arc. +Adds an arc (of a circle with radius `r`) that is tangent to the line connecting current +point and (`x1`, `y1`) and to the line connecting (`x1`, `y1`) and (`x2`, `y2`). + +If the current point and the starting point of the arc are different, a straight line +connecting these points is also appended. If there is no current point before the call to `addArcToPoint/6` +this function will behave as if preceded by a call to MoveToPoint(0, 0). After this call +the current point will be at the ending point of the arc. """. -spec addArcToPoint(This, X1, Y1, X2, Y2, R) -> 'ok' when This::wxGraphicsPath(), X1::number(), Y1::number(), X2::number(), Y2::number(), R::number(). @@ -122,7 +113,6 @@ addArcToPoint(#wx_ref{type=ThisT}=This,X1,Y1,X2,Y2,R) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X1,Y1,X2,Y2,R,?get_env(),?wxGraphicsPath_AddArcToPoint). -%% @doc See external documentation. -doc """ Appends a circle around (`x`,`y`) with radius `r` as a new closed subpath. @@ -135,13 +125,12 @@ addCircle(#wx_ref{type=ThisT}=This,X,Y,R) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,R,?get_env(),?wxGraphicsPath_AddCircle). -%% @doc See external documentation. -doc """ -Adds a cubic bezier curve from the current point, using two control points and -an end point. +Adds a cubic bezier curve from the current point, using two control points and an end +point. -If there is no current point before the call to `addCurveToPoint/7` this -function will behave as if preceded by a call to MoveToPoint(`c1`). +If there is no current point before the call to `addCurveToPoint/7` this function will behave as if preceded +by a call to MoveToPoint(`c1`). """. -spec addCurveToPoint(This, C1, C2, E) -> 'ok' when This::wxGraphicsPath(), C1::{X::float(), Y::float()}, C2::{X::float(), Y::float()}, E::{X::float(), Y::float()}. @@ -150,13 +139,12 @@ addCurveToPoint(#wx_ref{type=ThisT}=This,{C1X,C1Y} = C1,{C2X,C2Y} = C2,{EX,EY} = ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,C1,C2,E,?get_env(),?wxGraphicsPath_AddCurveToPoint_3). -%% @doc See external documentation. -doc """ -Adds a cubic bezier curve from the current point, using two control points and -an end point. +Adds a cubic bezier curve from the current point, using two control points and an end +point. -If there is no current point before the call to `addCurveToPoint/7` this -function will behave as if preceded by a call to MoveToPoint(`cx1`, `cy1`). +If there is no current point before the call to `addCurveToPoint/7` this function will behave as if preceded +by a call to MoveToPoint(`cx1`, `cy1`). """. -spec addCurveToPoint(This, Cx1, Cy1, Cx2, Cy2, X, Y) -> 'ok' when This::wxGraphicsPath(), Cx1::number(), Cy1::number(), Cx2::number(), Cy2::number(), X::number(), Y::number(). @@ -165,7 +153,6 @@ addCurveToPoint(#wx_ref{type=ThisT}=This,Cx1,Cy1,Cx2,Cy2,X,Y) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,Cx1,Cy1,Cx2,Cy2,X,Y,?get_env(),?wxGraphicsPath_AddCurveToPoint_6). -%% @doc See external documentation. -doc """ Appends an ellipse fitting into the passed in rectangle as a new closed subpath. @@ -178,12 +165,10 @@ addEllipse(#wx_ref{type=ThisT}=This,X,Y,W,H) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxGraphicsPath_AddEllipse). -%% @doc See external documentation. -doc """ Adds a straight line from the current point to `p`. -If current point is not yet set before the call to `addLineToPoint/3` this -function will behave as `moveToPoint/3`. +If current point is not yet set before the call to `addLineToPoint/3` this function will behave as `moveToPoint/3`. """. -spec addLineToPoint(This, P) -> 'ok' when This::wxGraphicsPath(), P::{X::float(), Y::float()}. @@ -192,12 +177,10 @@ addLineToPoint(#wx_ref{type=ThisT}=This,{PX,PY} = P) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,P,?get_env(),?wxGraphicsPath_AddLineToPoint_1). -%% @doc See external documentation. -doc """ Adds a straight line from the current point to (`x`,`y`). -If current point is not yet set before the call to `addLineToPoint/3` this -function will behave as `moveToPoint/3`. +If current point is not yet set before the call to `addLineToPoint/3` this function will behave as `moveToPoint/3`. """. -spec addLineToPoint(This, X, Y) -> 'ok' when This::wxGraphicsPath(), X::number(), Y::number(). @@ -206,13 +189,12 @@ addLineToPoint(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxGraphicsPath_AddLineToPoint_2). -%% @doc See external documentation. -doc """ Adds another path onto the current path. -After this call the current point will be at the added path's current point. For -Direct2D the path being appended shouldn't contain a started non-empty subpath -when this function is called. +After this call the current point will be at the added path's current point. For Direct2D +the path being appended shouldn't contain a started non-empty subpath when this function +is called. """. -spec addPath(This, Path) -> 'ok' when This::wxGraphicsPath(), Path::wxGraphicsPath(). @@ -221,13 +203,12 @@ addPath(#wx_ref{type=ThisT}=This,#wx_ref{type=PathT}=Path) -> ?CLASS(PathT,wxGraphicsPath), wxe_util:queue_cmd(This,Path,?get_env(),?wxGraphicsPath_AddPath). -%% @doc See external documentation. -doc """ -Adds a quadratic bezier curve from the current point, using a control point and -an end point. +Adds a quadratic bezier curve from the current point, using a control point and an end +point. -If there is no current point before the call to `addQuadCurveToPoint/5` this -function will behave as if preceded by a call to MoveToPoint(`cx`, `cy`). +If there is no current point before the call to `addQuadCurveToPoint/5` this function will behave as if preceded +by a call to MoveToPoint(`cx`, `cy`). """. -spec addQuadCurveToPoint(This, Cx, Cy, X, Y) -> 'ok' when This::wxGraphicsPath(), Cx::number(), Cy::number(), X::number(), Y::number(). @@ -236,7 +217,6 @@ addQuadCurveToPoint(#wx_ref{type=ThisT}=This,Cx,Cy,X,Y) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,Cx,Cy,X,Y,?get_env(),?wxGraphicsPath_AddQuadCurveToPoint). -%% @doc See external documentation. -doc """ Appends a rectangle as a new closed subpath. @@ -249,12 +229,11 @@ addRectangle(#wx_ref{type=ThisT}=This,X,Y,W,H) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxGraphicsPath_AddRectangle). -%% @doc See external documentation. -doc """ Appends a rounded rectangle as a new closed subpath. -If `radius` equals 0 this function will behave as `addRectangle/5`, otherwise -after this call the current point will be at (x+`w`, y+`h/2`). +If `radius` equals 0 this function will behave as `addRectangle/5`, otherwise after this call the current +point will be at (x+`w`, y+`h/2`). """. -spec addRoundedRectangle(This, X, Y, W, H, Radius) -> 'ok' when This::wxGraphicsPath(), X::number(), Y::number(), W::number(), H::number(), Radius::number(). @@ -263,12 +242,10 @@ addRoundedRectangle(#wx_ref{type=ThisT}=This,X,Y,W,H,Radius) ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,X,Y,W,H,Radius,?get_env(),?wxGraphicsPath_AddRoundedRectangle). -%% @doc See external documentation. -doc """ Closes the current sub-path. -After this call the current point will be at the joined endpoint of the -sub-path. +After this call the current point will be at the joined endpoint of the sub-path. """. -spec closeSubpath(This) -> 'ok' when This::wxGraphicsPath(). @@ -276,7 +253,7 @@ closeSubpath(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGraphicsPath), wxe_util:queue_cmd(This,?get_env(),?wxGraphicsPath_CloseSubpath). -%% @equiv contains(This,C, []) +-doc(#{equiv => contains(This,C, [])}). -spec contains(This, C) -> boolean() when This::wxGraphicsPath(), C::{X::float(), Y::float()}. @@ -284,14 +261,8 @@ contains(This,{CX,CY} = C) when is_record(This, wx_ref),is_number(CX),is_number(CY) -> contains(This,C, []). -%% @doc See external documentation. -%%
Also:
-%% contains(This, C, [Option]) -> boolean() when
-%% This::wxGraphicsPath(), C::{X::float(), Y::float()},
-%% Option :: {'fillStyle', wx:wx_enum()}.
-%% -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc "Return: true if the point is within the path.". +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec contains(This, X, Y) -> boolean() when This::wxGraphicsPath(), X::number(), Y::number(); (This, C, [Option]) -> boolean() when @@ -310,9 +281,8 @@ contains(#wx_ref{type=ThisT}=This,{CX,CY} = C, Options) wxe_util:queue_cmd(This,C, Opts,?get_env(),?wxGraphicsPath_Contains_2), wxe_util:rec(?wxGraphicsPath_Contains_2). -%% @doc See external documentation. -%%
FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -doc "Return: true if the point is within the path.". +%% FillStyle = ?wxODDEVEN_RULE | ?wxWINDING_RULE -spec contains(This, X, Y, [Option]) -> boolean() when This::wxGraphicsPath(), X::number(), Y::number(), Option :: {'fillStyle', wx:wx_enum()}. @@ -325,7 +295,6 @@ contains(#wx_ref{type=ThisT}=This,X,Y, Options) wxe_util:queue_cmd(This,X,Y, Opts,?get_env(),?wxGraphicsPath_Contains_3), wxe_util:rec(?wxGraphicsPath_Contains_3). -%% @doc See external documentation. -doc "Gets the bounding box enclosing all points (possibly including control points).". -spec getBox(This) -> {X::float(), Y::float(), W::float(), H::float()} when This::wxGraphicsPath(). @@ -334,7 +303,6 @@ getBox(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsPath_GetBox), wxe_util:rec(?wxGraphicsPath_GetBox). -%% @doc See external documentation. -doc "Gets the last point of the current path, (0,0) if not yet set.". -spec getCurrentPoint(This) -> {X::float(), Y::float()} when This::wxGraphicsPath(). @@ -343,12 +311,11 @@ getCurrentPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGraphicsPath_GetCurrentPoint), wxe_util:rec(?wxGraphicsPath_GetCurrentPoint). -%% @doc See external documentation. -doc """ Transforms each point of this path by the matrix. -For Direct2D the current path shouldn't contain a started non-empty subpath when -this function is called. +For Direct2D the current path shouldn't contain a started non-empty subpath when this +function is called. """. -spec transform(This, Matrix) -> 'ok' when This::wxGraphicsPath(), Matrix::wxGraphicsMatrix:wxGraphicsMatrix(). @@ -358,9 +325,7 @@ transform(#wx_ref{type=ThisT}=This,#wx_ref{type=MatrixT}=Matrix) -> wxe_util:queue_cmd(This,Matrix,?get_env(),?wxGraphicsPath_Transform). %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsPen.erl b/lib/wx/src/gen/wxGraphicsPen.erl index 7b9a0c39d1c5..3e98ddbf9443 100644 --- a/lib/wx/src/gen/wxGraphicsPen.erl +++ b/lib/wx/src/gen/wxGraphicsPen.erl @@ -20,18 +20,17 @@ -module(wxGraphicsPen). -moduledoc """ -Functions for wxGraphicsPen class +A `m:wxGraphicsPen` is a native representation of a pen. -A `m:wxGraphicsPen` is a native representation of a pen. The contents are -specific and private to the respective renderer. Instances are ref counted and -can therefore be assigned as usual. The only way to get a valid instance is via -`wxGraphicsContext:createPen/2` or `wxGraphicsRenderer::CreatePen()` (not -implemented in wx). +The contents are specific and private to the respective renderer. Instances are ref +counted and can therefore be assigned as usual. The only way to get a valid instance is +via `wxGraphicsContext:createPen/2` or `wxGraphicsRenderer::CreatePen()` (not implemented in wx). -This class is derived (and can use functions) from: `m:wxGraphicsObject` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxGraphicsPen](https://docs.wxwidgets.org/3.1/classwx_graphics_pen.html) +* `m:wxGraphicsObject` + +wxWidgets docs: [wxGraphicsPen](https://docs.wxwidgets.org/3.2/classwx_graphics_pen.html) """. -include("wxe.hrl"). -export([]). @@ -41,15 +40,12 @@ wxWidgets docs: -type wxGraphicsPen() :: wx:wx_object(). -export_type([wxGraphicsPen/0]). -%% @hidden -doc false. parent_class(wxGraphicsObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxGraphicsObject -%% @hidden -doc false. isNull(This) -> wxGraphicsObject:isNull(This). -%% @hidden -doc false. getRenderer(This) -> wxGraphicsObject:getRenderer(This). diff --git a/lib/wx/src/gen/wxGraphicsRenderer.erl b/lib/wx/src/gen/wxGraphicsRenderer.erl index bdc3cc29b77f..a8accde65a5c 100644 --- a/lib/wx/src/gen/wxGraphicsRenderer.erl +++ b/lib/wx/src/gen/wxGraphicsRenderer.erl @@ -20,19 +20,15 @@ -module(wxGraphicsRenderer). -moduledoc """ -Functions for wxGraphicsRenderer class - -A `m:wxGraphicsRenderer` is the instance corresponding to the rendering engine -used. There may be multiple instances on a system, if there are different -rendering engines present, but there is always only one instance per engine. -This instance is pointed back to by all objects created by it -(`m:wxGraphicsContext`, `m:wxGraphicsPath` etc.) and can be retrieved through -their `wxGraphicsObject:getRenderer/1` method. Therefore you can create an -additional instance of a path etc. by calling `wxGraphicsObject:getRenderer/1` -and then using the appropriate CreateXXX() function of that renderer. - -wxWidgets docs: -[wxGraphicsRenderer](https://docs.wxwidgets.org/3.1/classwx_graphics_renderer.html) +A `m:wxGraphicsRenderer` is the instance corresponding to the rendering engine used. + +There may be multiple instances on a system, if there are different rendering engines +present, but there is always only one instance per engine. This instance is pointed back +to by all objects created by it (`m:wxGraphicsContext`, `m:wxGraphicsPath` etc.) and can +be retrieved through their `wxGraphicsObject:getRenderer/1` method. Therefore you can create an additional instance of a +path etc. by calling `wxGraphicsObject:getRenderer/1` and then using the appropriate CreateXXX() function of that renderer. + +wxWidgets docs: [wxGraphicsRenderer](https://docs.wxwidgets.org/3.2/classwx_graphics_renderer.html) """. -include("wxe.hrl"). -export([createBrush/2,createContext/2,createFont/2,createFont/3,createFont/4, @@ -44,23 +40,20 @@ wxWidgets docs: -type wxGraphicsRenderer() :: wx:wx_object(). -export_type([wxGraphicsRenderer/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Returns the default renderer on this platform. -On macOS this is the Core Graphics (a.k.a. Quartz 2D) renderer, on MSW the -GDIPlus renderer, and on GTK we currently default to the Cairo renderer. +On macOS this is the Core Graphics (a.k.a. Quartz 2D) renderer, on MSW the GDIPlus +renderer, and on GTK we currently default to the Cairo renderer. """. -spec getDefaultRenderer() -> wxGraphicsRenderer(). getDefaultRenderer() -> wxe_util:queue_cmd(?get_env(), ?wxGraphicsRenderer_GetDefaultRenderer), wxe_util:rec(?wxGraphicsRenderer_GetDefaultRenderer). -%% @doc See external documentation. -doc "Creates a `m:wxGraphicsContext` from a `m:wxWindowDC`.". -spec createContext(This, WindowDC) -> wxGraphicsContext:wxGraphicsContext() when This::wxGraphicsRenderer(), WindowDC::wxWindowDC:wxWindowDC() | wxWindow:wxWindow() | wxMemoryDC:wxMemoryDC(). @@ -78,7 +71,6 @@ createContext(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowDCT}=WindowDC) -> wxe_util:queue_cmd(This,wx:typeCast(WindowDC, WindowDCType),?get_env(),?wxGraphicsRenderer_CreateContext), wxe_util:rec(?wxGraphicsRenderer_CreateContext). -%% @doc See external documentation. -doc "Creates a native brush from a `m:wxBrush`.". -spec createBrush(This, Brush) -> wxGraphicsBrush:wxGraphicsBrush() when This::wxGraphicsRenderer(), Brush::wxBrush:wxBrush(). @@ -88,12 +80,11 @@ createBrush(#wx_ref{type=ThisT}=This,#wx_ref{type=BrushT}=Brush) -> wxe_util:queue_cmd(This,Brush,?get_env(),?wxGraphicsRenderer_CreateBrush), wxe_util:rec(?wxGraphicsRenderer_CreateBrush). -%% @doc See external documentation. -doc """ Creates a native brush with a linear gradient. -Stops support is new since wxWidgets 2.9.1, previously only the start and end -colours could be specified. +Stops support is new since wxWidgets 2.9.1, previously only the start and end colours +could be specified. The ability to apply a transformation matrix to the gradient was added in 3.1.3 """. @@ -106,12 +97,11 @@ createLinearGradientBrush(#wx_ref{type=ThisT}=This,X1,Y1,X2,Y2,#wx_ref{type=Stop wxe_util:queue_cmd(This,X1,Y1,X2,Y2,Stops,?get_env(),?wxGraphicsRenderer_CreateLinearGradientBrush), wxe_util:rec(?wxGraphicsRenderer_CreateLinearGradientBrush). -%% @doc See external documentation. -doc """ Creates a native brush with a radial gradient. -Stops support is new since wxWidgets 2.9.1, previously only the start and end -colours could be specified. +Stops support is new since wxWidgets 2.9.1, previously only the start and end colours +could be specified. The ability to apply a transformation matrix to the gradient was added in 3.1.3 """. @@ -124,7 +114,7 @@ createRadialGradientBrush(#wx_ref{type=ThisT}=This,StartX,StartY,EndX,EndY,Radiu wxe_util:queue_cmd(This,StartX,StartY,EndX,EndY,Radius,Stops,?get_env(),?wxGraphicsRenderer_CreateRadialGradientBrush), wxe_util:rec(?wxGraphicsRenderer_CreateRadialGradientBrush). -%% @equiv createFont(This,Font, []) +-doc(#{equiv => createFont(This,Font, [])}). -spec createFont(This, Font) -> wxGraphicsFont:wxGraphicsFont() when This::wxGraphicsRenderer(), Font::wxFont:wxFont(). @@ -132,12 +122,6 @@ createFont(This,Font) when is_record(This, wx_ref),is_record(Font, wx_ref) -> createFont(This,Font, []). -%% @doc See external documentation. -%%
Also:
-%% createFont(This, Font, [Option]) -> wxGraphicsFont:wxGraphicsFont() when
-%% This::wxGraphicsRenderer(), Font::wxFont:wxFont(),
-%% Option :: {'col', wx:wx_colour()}.
-%% -doc "Creates a native graphics font from a `m:wxFont` and a text colour.". -spec createFont(This, SizeInPixels, Facename) -> wxGraphicsFont:wxGraphicsFont() when This::wxGraphicsRenderer(), SizeInPixels::number(), Facename::unicode:chardata(); @@ -158,13 +142,11 @@ createFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font, Options) wxe_util:queue_cmd(This,Font, Opts,?get_env(),?wxGraphicsRenderer_CreateFont_2), wxe_util:rec(?wxGraphicsRenderer_CreateFont_2). -%% @doc See external documentation. -doc """ Creates a graphics font with the given characteristics. -If possible, the `createFont/4` overload taking `m:wxFont` should be used -instead. The main advantage of this overload is that it can be used without X -server connection under Unix when using Cairo. +If possible, the `createFont/4` overload taking `m:wxFont` should be used instead. The main advantage +of this overload is that it can be used without X server connection under Unix when using Cairo. Since: 2.9.3 """. @@ -183,7 +165,7 @@ createFont(#wx_ref{type=ThisT}=This,SizeInPixels,Facename, Options) wxe_util:queue_cmd(This,SizeInPixels,Facename_UC, Opts,?get_env(),?wxGraphicsRenderer_CreateFont_3), wxe_util:rec(?wxGraphicsRenderer_CreateFont_3). -%% @equiv createMatrix(This, []) +-doc(#{equiv => createMatrix(This, [])}). -spec createMatrix(This) -> wxGraphicsMatrix:wxGraphicsMatrix() when This::wxGraphicsRenderer(). @@ -191,7 +173,6 @@ createMatrix(This) when is_record(This, wx_ref) -> createMatrix(This, []). -%% @doc See external documentation. -doc """ Creates a native affine transformation matrix from the passed in values. @@ -219,7 +200,6 @@ createMatrix(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGraphicsRenderer_CreateMatrix), wxe_util:rec(?wxGraphicsRenderer_CreateMatrix). -%% @doc See external documentation. -doc "Creates a native graphics path which is initially empty.". -spec createPath(This) -> wxGraphicsPath:wxGraphicsPath() when This::wxGraphicsRenderer(). diff --git a/lib/wx/src/gen/wxGrid.erl b/lib/wx/src/gen/wxGrid.erl index 76c07364cdc6..e21bd3c67d63 100644 --- a/lib/wx/src/gen/wxGrid.erl +++ b/lib/wx/src/gen/wxGrid.erl @@ -20,48 +20,72 @@ -module(wxGrid). -moduledoc """ -Functions for wxGrid class - -`m:wxGrid` and its related classes are used for displaying and editing tabular -data. They provide a rich set of features for display, editing, and interacting -with a variety of data sources. For simple applications, and to help you get -started, `m:wxGrid` is the only class you need to refer to directly. It will set -up default instances of the other classes and manage them for you. For more -complex applications you can derive your own classes for custom grid views, grid -data tables, cell editors and renderers. The overview_grid has examples of -simple and more complex applications, explains the relationship between the -various grid classes and has a summary of the keyboard shortcuts and mouse -functions provided by `m:wxGrid`. - -A `wxGridTableBase` (not implemented in wx) class holds the actual data to be -displayed by a `m:wxGrid` class. One or more `m:wxGrid` classes may act as a -view for one table class. The default table class is called `wxGridStringTable` -(not implemented in wx) and holds an array of strings. An instance of such a -class is created by `createGrid/4`. - -`m:wxGridCellRenderer` is the abstract base class for rendering contents in a -cell. The following renderers are predefined: - -The look of a cell can be further defined using `m:wxGridCellAttr`. An object of -this type may be returned by `wxGridTableBase::GetAttr()` (not implemented in -wx). - -`m:wxGridCellEditor` is the abstract base class for editing the value of a cell. -The following editors are predefined: - -Please see `m:wxGridEvent`, `wxGridSizeEvent` (not implemented in wx), -`wxGridRangeSelectEvent` (not implemented in wx), and `wxGridEditorCreatedEvent` -(not implemented in wx) for the documentation of all event types you can use -with `m:wxGrid`. +`m:wxGrid` and its related classes are used for displaying and editing tabular data. -See: -[Overview grid](https://docs.wxwidgets.org/3.1/overview_grid.html#overview_grid), -`wxGridUpdateLocker` (not implemented in wx) +They provide a rich set of features for display, editing, and interacting with a variety +of data sources. For simple applications, and to help you get started, `m:wxGrid` is the +only class you need to refer to directly. It will set up default instances of the other +classes and manage them for you. For more complex applications you can derive your own +classes for custom grid views, grid data tables, cell editors and renderers. The +overview_grid has examples of simple and more complex applications, explains the +relationship between the various grid classes and has a summary of the keyboard shortcuts +and mouse functions provided by `m:wxGrid`. + +A `wxGridTableBase` (not implemented in wx) class holds the actual data to be displayed +by a `m:wxGrid` class. One or more `m:wxGrid` classes may act as a view for one table +class. The default table class is called `wxGridStringTable` (not implemented in wx) and +holds an array of strings. An instance of such a class is created by `createGrid/4`. + +`m:wxGridCellRenderer` is the abstract base class for rendering contents in a cell. The +following renderers are predefined: + +* `m:wxGridCellBoolRenderer` + +* `m:wxGridCellFloatRenderer` + +* `m:wxGridCellNumberRenderer` + +* `m:wxGridCellStringRenderer` + +* `wxGridCellDateRenderer` (not implemented in wx) + +* `wxGridCellDateTimeRenderer` (not implemented in wx) + +The look of a cell can be further defined using `m:wxGridCellAttr`. An object of this +type may be returned by `wxGridTableBase::GetAttr()` (not implemented in wx). + +`m:wxGridCellEditor` is the abstract base class for editing the value of a cell. The +following editors are predefined: + +* `m:wxGridCellBoolEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellFloatEditor` + +* `m:wxGridCellNumberEditor` + +* `m:wxGridCellTextEditor` + +* `wxGridCellDateEditor` (not implemented in wx) + +Please see `m:wxGridEvent`, `wxGridSizeEvent` (not implemented in wx), `wxGridRangeSelectEvent` +(not implemented in wx), and `wxGridEditorCreatedEvent` (not implemented in wx) for the +documentation of all event types you can use with `m:wxGrid`. -This class is derived (and can use functions) from: `m:wxScrolledWindow` -`m:wxPanel` `m:wxWindow` `m:wxEvtHandler` +See: [Overview grid](https://docs.wxwidgets.org/3.2/overview_grid.html#overview_grid) -wxWidgets docs: [wxGrid](https://docs.wxwidgets.org/3.1/classwx_grid.html) +This class is derived, and can use functions, from: + +* `m:wxScrolledWindow` + +* `m:wxPanel` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxGrid](https://docs.wxwidgets.org/3.2/classwx_grid.html) """. -include("wxe.hrl"). -export([appendCols/1,appendCols/2,appendRows/1,appendRows/2,autoSize/1,autoSizeColumn/2, @@ -160,7 +184,6 @@ wxWidgets docs: [wxGrid](https://docs.wxwidgets.org/3.1/classwx_grid.html) -type wxGrid() :: wx:wx_object(). -export_type([wxGrid/0]). -%% @hidden -doc false. parent_class(wxScrolledWindow) -> true; parent_class(wxPanel) -> true; @@ -168,20 +191,19 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ Default constructor. -You must call `Create()` (not implemented in wx) to really create the grid -window and also call `createGrid/4` or `SetTable()` (not implemented in wx) or -`AssignTable()` (not implemented in wx) to initialize its contents. +You must call `Create()` (not implemented in wx) to really create the grid window and +also call `createGrid/4` or `SetTable()` (not implemented in wx) or `AssignTable()` (not implemented in +wx) to initialize its contents. """. -spec new() -> wxGrid(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGrid_new_0), wxe_util:rec(?wxGrid_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxGrid() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -189,13 +211,11 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See external documentation. -doc """ Constructor creating the grid window. -You must call either `createGrid/4` or `SetTable()` (not implemented in wx) or -`AssignTable()` (not implemented in wx) to initialize the grid contents before -using it. +You must call either `createGrid/4` or `SetTable()` (not implemented in wx) or `AssignTable()` (not +implemented in wx) to initialize the grid contents before using it. """. -spec new(Parent, Id, [Option]) -> wxGrid() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -213,7 +233,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxGrid_new_3), wxe_util:rec(?wxGrid_new_3). -%% @equiv appendCols(This, []) +-doc(#{equiv => appendCols(This, [])}). -spec appendCols(This) -> boolean() when This::wxGrid(). @@ -221,13 +241,12 @@ appendCols(This) when is_record(This, wx_ref) -> appendCols(This, []). -%% @doc See external documentation. -doc """ Appends one or more new columns to the right of the grid. -The `updateLabels` argument is not used at present. If you are using a derived -grid table class you will need to override `wxGridTableBase::AppendCols()` (not -implemented in wx). See `insertCols/2` for further information. +The `updateLabels` argument is not used at present. If you are using a derived grid table +class you will need to override `wxGridTableBase::AppendCols()` (not implemented in wx). +See `insertCols/2` for further information. Return: true on success or false if appending columns failed. """. @@ -245,7 +264,7 @@ appendCols(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_AppendCols), wxe_util:rec(?wxGrid_AppendCols). -%% @equiv appendRows(This, []) +-doc(#{equiv => appendRows(This, [])}). -spec appendRows(This) -> boolean() when This::wxGrid(). @@ -253,13 +272,12 @@ appendRows(This) when is_record(This, wx_ref) -> appendRows(This, []). -%% @doc See external documentation. -doc """ Appends one or more new rows to the bottom of the grid. -The `updateLabels` argument is not used at present. If you are using a derived -grid table class you will need to override `wxGridTableBase::AppendRows()` (not -implemented in wx). See `insertRows/2` for further information. +The `updateLabels` argument is not used at present. If you are using a derived grid table +class you will need to override `wxGridTableBase::AppendRows()` (not implemented in wx). +See `insertRows/2` for further information. Return: true on success or false if appending rows failed. """. @@ -277,18 +295,14 @@ appendRows(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_AppendRows), wxe_util:rec(?wxGrid_AppendRows). -%% @doc See external documentation. --doc """ -Automatically sets the height and width of all rows and columns to fit their -contents. -""". +-doc "Automatically sets the height and width of all rows and columns to fit their contents.". -spec autoSize(This) -> 'ok' when This::wxGrid(). autoSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_AutoSize). -%% @equiv autoSizeColumn(This,Col, []) +-doc(#{equiv => autoSizeColumn(This,Col, [])}). -spec autoSizeColumn(This, Col) -> 'ok' when This::wxGrid(), Col::integer(). @@ -296,12 +310,11 @@ autoSizeColumn(This,Col) when is_record(This, wx_ref),is_integer(Col) -> autoSizeColumn(This,Col, []). -%% @doc See external documentation. -doc """ Automatically sizes the column to fit its contents. -If `setAsMin` is true the calculated width will also be set as the minimal width -for the column. +If `setAsMin` is true the calculated width will also be set as the minimal width for the +column. """. -spec autoSizeColumn(This, Col, [Option]) -> 'ok' when This::wxGrid(), Col::integer(), @@ -314,7 +327,7 @@ autoSizeColumn(#wx_ref{type=ThisT}=This,Col, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Col, Opts,?get_env(),?wxGrid_AutoSizeColumn). -%% @equiv autoSizeColumns(This, []) +-doc(#{equiv => autoSizeColumns(This, [])}). -spec autoSizeColumns(This) -> 'ok' when This::wxGrid(). @@ -322,12 +335,11 @@ autoSizeColumns(This) when is_record(This, wx_ref) -> autoSizeColumns(This, []). -%% @doc See external documentation. -doc """ Automatically sizes all columns to fit their contents. -If `setAsMin` is true the calculated widths will also be set as the minimal -widths for the columns. +If `setAsMin` is true the calculated widths will also be set as the minimal widths for +the columns. """. -spec autoSizeColumns(This, [Option]) -> 'ok' when This::wxGrid(), @@ -340,7 +352,7 @@ autoSizeColumns(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_AutoSizeColumns). -%% @equiv autoSizeRow(This,Row, []) +-doc(#{equiv => autoSizeRow(This,Row, [])}). -spec autoSizeRow(This, Row) -> 'ok' when This::wxGrid(), Row::integer(). @@ -348,12 +360,11 @@ autoSizeRow(This,Row) when is_record(This, wx_ref),is_integer(Row) -> autoSizeRow(This,Row, []). -%% @doc See external documentation. -doc """ Automatically sizes the row to fit its contents. -If `setAsMin` is true the calculated height will also be set as the minimal -height for the row. +If `setAsMin` is true the calculated height will also be set as the minimal height for +the row. """. -spec autoSizeRow(This, Row, [Option]) -> 'ok' when This::wxGrid(), Row::integer(), @@ -366,7 +377,7 @@ autoSizeRow(#wx_ref{type=ThisT}=This,Row, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Row, Opts,?get_env(),?wxGrid_AutoSizeRow). -%% @equiv autoSizeRows(This, []) +-doc(#{equiv => autoSizeRows(This, [])}). -spec autoSizeRows(This) -> 'ok' when This::wxGrid(). @@ -374,12 +385,11 @@ autoSizeRows(This) when is_record(This, wx_ref) -> autoSizeRows(This, []). -%% @doc See external documentation. -doc """ Automatically sizes all rows to fit their contents. -If `setAsMin` is true the calculated heights will also be set as the minimal -heights for the rows. +If `setAsMin` is true the calculated heights will also be set as the minimal heights for +the rows. """. -spec autoSizeRows(This, [Option]) -> 'ok' when This::wxGrid(), @@ -392,19 +402,17 @@ autoSizeRows(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_AutoSizeRows). -%% @doc See external documentation. -doc """ Increments the grid's batch count. -When the count is greater than zero repainting of the grid is suppressed. Each -call to BeginBatch must be matched by a later call to `endBatch/1`. Code that -does a lot of grid modification can be enclosed between `beginBatch/1` and -`endBatch/1` calls to avoid screen flicker. The final `endBatch/1` call will -cause the grid to be repainted. +When the count is greater than zero repainting of the grid is suppressed. Each call to +BeginBatch must be matched by a later call to `endBatch/1`. Code that does a lot of grid modification +can be enclosed between `beginBatch/1` and `endBatch/1` calls to avoid screen flicker. The final `endBatch/1` call will cause +the grid to be repainted. -Notice that you should use `wxGridUpdateLocker` (not implemented in wx) which -ensures that there is always a matching `endBatch/1` call for this -`beginBatch/1` if possible instead of calling this method directly. +Notice that you should use `wxGridUpdateLocker` (not implemented in wx) which ensures +that there is always a matching `endBatch/1` call for this `beginBatch/1` if possible instead of calling this method +directly. """. -spec beginBatch(This) -> 'ok' when This::wxGrid(). @@ -412,13 +420,11 @@ beginBatch(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_BeginBatch). -%% @doc See external documentation. -doc """ Convert grid cell coordinates to grid window pixel coordinates. -This function returns the rectangle that encloses the block of cells limited by -`topLeft` and `bottomRight` cell in device coords and clipped to the client size -of the grid window. +This function returns the rectangle that encloses the block of cells limited by `topLeft` +and `bottomRight` cell in device coords and clipped to the client size of the grid window. Since: 3.1.3 Parameter `gridWindow` has been added. @@ -432,7 +438,6 @@ blockToDeviceRect(#wx_ref{type=ThisT}=This,{TopLeftR,TopLeftC} = TopLeft,{Bottom wxe_util:queue_cmd(This,TopLeft,BottomRight,?get_env(),?wxGrid_BlockToDeviceRect), wxe_util:rec(?wxGrid_BlockToDeviceRect). -%% @doc See external documentation. -doc "Return true if the dragging of cells is enabled or false otherwise.". -spec canDragCell(This) -> boolean() when This::wxGrid(). @@ -441,7 +446,6 @@ canDragCell(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_CanDragCell), wxe_util:rec(?wxGrid_CanDragCell). -%% @doc See external documentation. -doc """ Returns true if columns can be moved by dragging with the mouse. @@ -454,11 +458,13 @@ canDragColMove(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_CanDragColMove), wxe_util:rec(?wxGrid_CanDragColMove). -%% @doc See external documentation. -doc """ Return true if row edges inside the grid can be dragged to resize the rows. -See: `canDragGridSize/1`, `canDragRowSize/2` +See: +* `canDragGridSize/1` + +* `canDragRowSize/2` Since: 3.1.4 """. @@ -469,14 +475,12 @@ canDragGridRowEdges(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_CanDragGridRowEdges), wxe_util:rec(?wxGrid_CanDragGridRowEdges). -%% @doc See external documentation. -doc """ Returns true if the given column can be resized by dragging with the mouse. -This function returns true if resizing the columns interactively is globally -enabled, i.e. if `disableDragColSize/1` hadn't been called, and if this column -wasn't explicitly marked as non-resizable with `DisableColResize()` (not -implemented in wx). +This function returns true if resizing the columns interactively is globally enabled, +i.e. if `disableDragColSize/1` hadn't been called, and if this column wasn't explicitly marked as non-resizable +with `DisableColResize()` (not implemented in wx). """. -spec canDragColSize(This, Col) -> boolean() when This::wxGrid(), Col::integer(). @@ -486,7 +490,6 @@ canDragColSize(#wx_ref{type=ThisT}=This,Col) wxe_util:queue_cmd(This,Col,?get_env(),?wxGrid_CanDragColSize), wxe_util:rec(?wxGrid_CanDragColSize). -%% @doc See external documentation. -doc """ Returns true if the given row can be resized by dragging with the mouse. @@ -500,10 +503,9 @@ canDragRowSize(#wx_ref{type=ThisT}=This,Row) wxe_util:queue_cmd(This,Row,?get_env(),?wxGrid_CanDragRowSize), wxe_util:rec(?wxGrid_CanDragRowSize). -%% @doc See external documentation. -doc """ -Return true if the dragging of grid lines to resize rows and columns is enabled -or false otherwise. +Return true if the dragging of grid lines to resize rows and columns is enabled or false +otherwise. """. -spec canDragGridSize(This) -> boolean() when This::wxGrid(). @@ -512,10 +514,9 @@ canDragGridSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_CanDragGridSize), wxe_util:rec(?wxGrid_CanDragGridSize). -%% @doc See external documentation. -doc """ -Returns true if the in-place edit control for the current grid cell can be used -and false otherwise. +Returns true if the in-place edit control for the current grid cell can be used and false +otherwise. This function always returns false for the read-only cells. """. @@ -526,10 +527,9 @@ canEnableCellControl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_CanEnableCellControl), wxe_util:rec(?wxGrid_CanEnableCellControl). -%% @doc See external documentation. -doc """ -Return the rectangle corresponding to the grid cell's size and position in -logical coordinates. +Return the rectangle corresponding to the grid cell's size and position in logical +coordinates. See: `blockToDeviceRect/3` """. @@ -541,10 +541,9 @@ cellToRect(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords) wxe_util:queue_cmd(This,Coords,?get_env(),?wxGrid_CellToRect_1), wxe_util:rec(?wxGrid_CellToRect_1). -%% @doc See external documentation. -doc """ -Return the rectangle corresponding to the grid cell's size and position in -logical coordinates. +Return the rectangle corresponding to the grid cell's size and position in logical +coordinates. See: `blockToDeviceRect/3` """. @@ -556,13 +555,12 @@ cellToRect(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_CellToRect_2), wxe_util:rec(?wxGrid_CellToRect_2). -%% @doc See external documentation. -doc """ Clears all data in the underlying grid table and repaints the grid. -The table is not deleted by this function. If you are using a derived table -class then you need to override `wxGridTableBase::Clear()` (not implemented in -wx) for this function to have any effect. +The table is not deleted by this function. If you are using a derived table class then +you need to override `wxGridTableBase::Clear()` (not implemented in wx) for this function +to have any effect. """. -spec clearGrid(This) -> 'ok' when This::wxGrid(). @@ -570,7 +568,6 @@ clearGrid(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_ClearGrid). -%% @doc See external documentation. -doc "Deselects all cells that are currently selected.". -spec clearSelection(This) -> 'ok' when This::wxGrid(). @@ -578,7 +575,7 @@ clearSelection(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_ClearSelection). -%% @equiv createGrid(This,NumRows,NumCols, []) +-doc(#{equiv => createGrid(This,NumRows,NumCols, [])}). -spec createGrid(This, NumRows, NumCols) -> boolean() when This::wxGrid(), NumRows::integer(), NumCols::integer(). @@ -586,20 +583,18 @@ createGrid(This,NumRows,NumCols) when is_record(This, wx_ref),is_integer(NumRows),is_integer(NumCols) -> createGrid(This,NumRows,NumCols, []). -%% @doc See external documentation. -%%
Selmode = ?wxGrid_wxGridSelectCells | ?wxGrid_wxGridSelectRows | ?wxGrid_wxGridSelectColumns | ?wxGrid_wxGridSelectRowsOrColumns -doc """ Creates a grid with the specified initial number of rows and columns. -Call this directly after the grid constructor. When you use this function -`m:wxGrid` will create and manage a simple table of string values for you. All -of the grid data will be stored in memory. +Call this directly after the grid constructor. When you use this function `m:wxGrid` will +create and manage a simple table of string values for you. All of the grid data will be +stored in memory. -For applications with more complex data types or relationships, or for dealing -with very large datasets, you should derive your own grid table class and pass a -table object to the grid with `SetTable()` (not implemented in wx) or -`AssignTable()` (not implemented in wx). +For applications with more complex data types or relationships, or for dealing with very +large datasets, you should derive your own grid table class and pass a table object to the +grid with `SetTable()` (not implemented in wx) or `AssignTable()` (not implemented in wx). """. +%% Selmode = ?wxGrid_wxGridSelectCells | ?wxGrid_wxGridSelectRows | ?wxGrid_wxGridSelectColumns | ?wxGrid_wxGridSelectRowsOrColumns -spec createGrid(This, NumRows, NumCols, [Option]) -> boolean() when This::wxGrid(), NumRows::integer(), NumCols::integer(), Option :: {'selmode', wx:wx_enum()}. @@ -612,7 +607,7 @@ createGrid(#wx_ref{type=ThisT}=This,NumRows,NumCols, Options) wxe_util:queue_cmd(This,NumRows,NumCols, Opts,?get_env(),?wxGrid_CreateGrid), wxe_util:rec(?wxGrid_CreateGrid). -%% @equiv deleteCols(This, []) +-doc(#{equiv => deleteCols(This, [])}). -spec deleteCols(This) -> boolean() when This::wxGrid(). @@ -620,13 +615,12 @@ deleteCols(This) when is_record(This, wx_ref) -> deleteCols(This, []). -%% @doc See external documentation. -doc """ Deletes one or more columns from a grid starting at the specified position. -The `updateLabels` argument is not used at present. If you are using a derived -grid table class you will need to override `wxGridTableBase::DeleteCols()` (not -implemented in wx). See `insertCols/2` for further information. +The `updateLabels` argument is not used at present. If you are using a derived grid table +class you will need to override `wxGridTableBase::DeleteCols()` (not implemented in wx). +See `insertCols/2` for further information. Return: true on success or false if deleting columns failed. """. @@ -646,7 +640,7 @@ deleteCols(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_DeleteCols), wxe_util:rec(?wxGrid_DeleteCols). -%% @equiv deleteRows(This, []) +-doc(#{equiv => deleteRows(This, [])}). -spec deleteRows(This) -> boolean() when This::wxGrid(). @@ -654,13 +648,12 @@ deleteRows(This) when is_record(This, wx_ref) -> deleteRows(This, []). -%% @doc See external documentation. -doc """ Deletes one or more rows from a grid starting at the specified position. -The `updateLabels` argument is not used at present. If you are using a derived -grid table class you will need to override `wxGridTableBase::DeleteRows()` (not -implemented in wx). See `insertRows/2` for further information. +The `updateLabels` argument is not used at present. If you are using a derived grid table +class you will need to override `wxGridTableBase::DeleteRows()` (not implemented in wx). +See `insertRows/2` for further information. Return: true on success or false if deleting rows failed. """. @@ -680,7 +673,6 @@ deleteRows(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_DeleteRows), wxe_util:rec(?wxGrid_DeleteRows). -%% @doc See external documentation. -doc """ Disables in-place editing of grid cells. @@ -692,7 +684,6 @@ disableCellEditControl(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_DisableCellEditControl). -%% @doc See external documentation. -doc """ Disables column sizing by dragging with the mouse. @@ -704,7 +695,6 @@ disableDragColSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_DisableDragColSize). -%% @doc See external documentation. -doc """ Disable mouse dragging of grid lines to resize rows and columns. @@ -716,7 +706,6 @@ disableDragGridSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_DisableDragGridSize). -%% @doc See external documentation. -doc """ Disables row sizing by dragging with the mouse. @@ -728,7 +717,7 @@ disableDragRowSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_DisableDragRowSize). -%% @equiv enableCellEditControl(This, []) +-doc(#{equiv => enableCellEditControl(This, [])}). -spec enableCellEditControl(This) -> 'ok' when This::wxGrid(). @@ -736,21 +725,18 @@ enableCellEditControl(This) when is_record(This, wx_ref) -> enableCellEditControl(This, []). -%% @doc See external documentation. -doc """ Enables or disables in-place editing of grid cell data. -Enabling in-place editing generates `wxEVT_GRID_EDITOR_SHOWN` and, if it isn't -vetoed by the application, shows the in-place editor which allows the user to -change the cell value. +Enabling in-place editing generates `wxEVT_GRID_EDITOR_SHOWN` and, if it isn't vetoed by +the application, shows the in-place editor which allows the user to change the cell value. -Disabling in-place editing does nothing if the in-place editor isn't currently -shown, otherwise the `wxEVT_GRID_EDITOR_HIDDEN` event is generated but, unlike -the "shown" event, it can't be vetoed and the in-place editor is dismissed -unconditionally. +Disabling in-place editing does nothing if the in-place editor isn't currently shown, +otherwise the `wxEVT_GRID_EDITOR_HIDDEN` event is generated but, unlike the "shown" event, +it can't be vetoed and the in-place editor is dismissed unconditionally. -Note that it is an error to call this function if the current cell is read-only, -use `canEnableCellControl/1` to check for this precondition. +Note that it is an error to call this function if the current cell is read-only, use `canEnableCellControl/1` to +check for this precondition. """. -spec enableCellEditControl(This, [Option]) -> 'ok' when This::wxGrid(), @@ -763,7 +749,7 @@ enableCellEditControl(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_EnableCellEditControl). -%% @equiv enableDragColSize(This, []) +-doc(#{equiv => enableDragColSize(This, [])}). -spec enableDragColSize(This) -> 'ok' when This::wxGrid(). @@ -771,12 +757,7 @@ enableDragColSize(This) when is_record(This, wx_ref) -> enableDragColSize(This, []). -%% @doc See external documentation. --doc """ -Enables or disables column sizing by dragging with the mouse. - -See: `DisableColResize()` (not implemented in wx) -""". +-doc "Enables or disables column sizing by dragging with the mouse.". -spec enableDragColSize(This, [Option]) -> 'ok' when This::wxGrid(), Option :: {'enable', boolean()}. @@ -788,7 +769,7 @@ enableDragColSize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_EnableDragColSize). -%% @equiv enableDragGridSize(This, []) +-doc(#{equiv => enableDragGridSize(This, [])}). -spec enableDragGridSize(This) -> 'ok' when This::wxGrid(). @@ -796,11 +777,7 @@ enableDragGridSize(This) when is_record(This, wx_ref) -> enableDragGridSize(This, []). -%% @doc See external documentation. --doc """ -Enables or disables row and column resizing by dragging gridlines with the -mouse. -""". +-doc "Enables or disables row and column resizing by dragging gridlines with the mouse.". -spec enableDragGridSize(This, [Option]) -> 'ok' when This::wxGrid(), Option :: {'enable', boolean()}. @@ -812,7 +789,7 @@ enableDragGridSize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_EnableDragGridSize). -%% @equiv enableDragRowSize(This, []) +-doc(#{equiv => enableDragRowSize(This, [])}). -spec enableDragRowSize(This) -> 'ok' when This::wxGrid(). @@ -820,12 +797,7 @@ enableDragRowSize(This) when is_record(This, wx_ref) -> enableDragRowSize(This, []). -%% @doc See external documentation. --doc """ -Enables or disables row sizing by dragging with the mouse. - -See: `DisableRowResize()` (not implemented in wx) -""". +-doc "Enables or disables row sizing by dragging with the mouse.". -spec enableDragRowSize(This, [Option]) -> 'ok' when This::wxGrid(), Option :: {'enable', boolean()}. @@ -837,18 +809,16 @@ enableDragRowSize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_EnableDragRowSize). -%% @doc See external documentation. -doc """ Makes the grid globally editable or read-only. -If the edit argument is false this function sets the whole grid as read-only. If -the argument is true the grid is set to the default state where cells may be -editable. In the default state you can set single grid cells and whole rows and -columns to be editable or read-only via `wxGridCellAttr:setReadOnly/2`. For -single cells you can also use the shortcut function `setReadOnly/4`. +If the edit argument is false this function sets the whole grid as read-only. If the +argument is true the grid is set to the default state where cells may be editable. In the +default state you can set single grid cells and whole rows and columns to be editable or +read-only via `wxGridCellAttr:setReadOnly/2`. For single cells you can also use the shortcut function `setReadOnly/4`. -For more information about controlling grid cell attributes see the -`m:wxGridCellAttr` class and the overview_grid. +For more information about controlling grid cell attributes see the `m:wxGridCellAttr` +class and the overview_grid. """. -spec enableEditing(This, Edit) -> 'ok' when This::wxGrid(), Edit::boolean(). @@ -857,7 +827,7 @@ enableEditing(#wx_ref{type=ThisT}=This,Edit) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Edit,?get_env(),?wxGrid_EnableEditing). -%% @equiv enableGridLines(This, []) +-doc(#{equiv => enableGridLines(This, [])}). -spec enableGridLines(This) -> 'ok' when This::wxGrid(). @@ -865,7 +835,6 @@ enableGridLines(This) when is_record(This, wx_ref) -> enableGridLines(This, []). -%% @doc See external documentation. -doc "Turns the drawing of grid lines on or off.". -spec enableGridLines(This, [Option]) -> 'ok' when This::wxGrid(), @@ -878,17 +847,13 @@ enableGridLines(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_EnableGridLines). -%% @doc See external documentation. -doc """ Decrements the grid's batch count. -When the count is greater than zero repainting of the grid is suppressed. Each -previous call to `beginBatch/1` must be matched by a later call to `endBatch/1`. -Code that does a lot of grid modification can be enclosed between `beginBatch/1` -and `endBatch/1` calls to avoid screen flicker. The final `endBatch/1` will -cause the grid to be repainted. - -See: `wxGridUpdateLocker` (not implemented in wx) +When the count is greater than zero repainting of the grid is suppressed. Each previous +call to `beginBatch/1` must be matched by a later call to `endBatch/1`. Code that does a lot of grid modification +can be enclosed between `beginBatch/1` and `endBatch/1` calls to avoid screen flicker. The final `endBatch/1` will cause the +grid to be repainted. """. -spec endBatch(This) -> 'ok' when This::wxGrid(). @@ -896,7 +861,6 @@ endBatch(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_EndBatch). -%% @doc See external documentation. -doc "Overridden `m:wxWindow` method.". -spec fit(This) -> 'ok' when This::wxGrid(). @@ -904,7 +868,6 @@ fit(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_Fit). -%% @doc See external documentation. -doc """ Causes immediate repainting of the grid. @@ -916,13 +879,11 @@ forceRefresh(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_ForceRefresh). -%% @doc See external documentation. -doc """ -Returns the number of times that `beginBatch/1` has been called without (yet) -matching calls to `endBatch/1`. +Returns the number of times that `beginBatch/1` has been called without (yet) matching +calls to `endBatch/1`. -While the grid's batch count is greater than zero the display will not be -updated. +While the grid's batch count is greater than zero the display will not be updated. """. -spec getBatchCount(This) -> integer() when This::wxGrid(). @@ -931,16 +892,13 @@ getBatchCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetBatchCount), wxe_util:rec(?wxGrid_GetBatchCount). -%% @doc See external documentation. -doc """ -Sets the arguments to the horizontal and vertical text alignment values for the -grid cell at the specified location. +Sets the arguments to the horizontal and vertical text alignment values for the grid cell +at the specified location. -Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. +Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. -Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or -`wxALIGN_BOTTOM`. +Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec getCellAlignment(This, Row, Col) -> {Horiz::integer(), Vert::integer()} when This::wxGrid(), Row::integer(), Col::integer(). @@ -950,7 +908,6 @@ getCellAlignment(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellAlignment), wxe_util:rec(?wxGrid_GetCellAlignment). -%% @doc See external documentation. -doc "Returns the background colour of the cell at the specified location.". -spec getCellBackgroundColour(This, Row, Col) -> wx:wx_colour4() when This::wxGrid(), Row::integer(), Col::integer(). @@ -960,12 +917,11 @@ getCellBackgroundColour(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellBackgroundColour), wxe_util:rec(?wxGrid_GetCellBackgroundColour). -%% @doc See external documentation. -doc """ Returns a pointer to the editor for the cell at the specified location. -See `m:wxGridCellEditor` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellEditor` and the overview_grid for more information about cell editors +and renderers. The caller must call DecRef() on the returned pointer. """. @@ -977,7 +933,6 @@ getCellEditor(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellEditor), wxe_util:rec(?wxGrid_GetCellEditor). -%% @doc See external documentation. -doc "Returns the font for text in the grid cell at the specified location.". -spec getCellFont(This, Row, Col) -> wxFont:wxFont() when This::wxGrid(), Row::integer(), Col::integer(). @@ -987,12 +942,11 @@ getCellFont(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellFont), wxe_util:rec(?wxGrid_GetCellFont). -%% @doc See external documentation. -doc """ Returns a pointer to the renderer for the grid cell at the specified location. -See `m:wxGridCellRenderer` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellRenderer` and the overview_grid for more information about cell editors +and renderers. The caller must call DecRef() on the returned pointer. """. @@ -1004,7 +958,6 @@ getCellRenderer(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellRenderer), wxe_util:rec(?wxGrid_GetCellRenderer). -%% @doc See external documentation. -doc "Returns the text colour for the grid cell at the specified location.". -spec getCellTextColour(This, Row, Col) -> wx:wx_colour4() when This::wxGrid(), Row::integer(), Col::integer(). @@ -1014,19 +967,17 @@ getCellTextColour(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellTextColour), wxe_util:rec(?wxGrid_GetCellTextColour). -%% @doc See external documentation. -doc """ Returns the string contained in the cell at the specified location. -For simple applications where a grid object automatically uses a default grid -table of string values you use this function together with `setCellValue/4` to -access cell values. For more complex applications where you have derived your -own grid table class that contains various data types (e.g. numeric, boolean or -user-defined custom types) then you only use this function for those cells that -contain string values. +For simple applications where a grid object automatically uses a default grid table of +string values you use this function together with `setCellValue/4` to access cell values. For more complex +applications where you have derived your own grid table class that contains various data +types (e.g. numeric, boolean or user-defined custom types) then you only use this function +for those cells that contain string values. -See `wxGridTableBase::CanGetValueAs()` (not implemented in wx) and the -overview_grid for more information. +See `wxGridTableBase::CanGetValueAs()` (not implemented in wx) and the overview_grid for +more information. """. -spec getCellValue(This, Coords) -> unicode:charlist() when This::wxGrid(), Coords::{R::integer(), C::integer()}. @@ -1036,19 +987,17 @@ getCellValue(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords) wxe_util:queue_cmd(This,Coords,?get_env(),?wxGrid_GetCellValue_1), wxe_util:rec(?wxGrid_GetCellValue_1). -%% @doc See external documentation. -doc """ Returns the string contained in the cell at the specified location. -For simple applications where a grid object automatically uses a default grid -table of string values you use this function together with `setCellValue/4` to -access cell values. For more complex applications where you have derived your -own grid table class that contains various data types (e.g. numeric, boolean or -user-defined custom types) then you only use this function for those cells that -contain string values. +For simple applications where a grid object automatically uses a default grid table of +string values you use this function together with `setCellValue/4` to access cell values. For more complex +applications where you have derived your own grid table class that contains various data +types (e.g. numeric, boolean or user-defined custom types) then you only use this function +for those cells that contain string values. -See `wxGridTableBase::CanGetValueAs()` (not implemented in wx) and the -overview_grid for more information. +See `wxGridTableBase::CanGetValueAs()` (not implemented in wx) and the overview_grid for +more information. """. -spec getCellValue(This, Row, Col) -> unicode:charlist() when This::wxGrid(), Row::integer(), Col::integer(). @@ -1058,15 +1007,12 @@ getCellValue(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetCellValue_2), wxe_util:rec(?wxGrid_GetCellValue_2). -%% @doc See external documentation. -doc """ Sets the arguments to the current column label alignment values. -Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. +Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. -Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or -`wxALIGN_BOTTOM`. +Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec getColLabelAlignment(This) -> {Horiz::integer(), Vert::integer()} when This::wxGrid(). @@ -1075,7 +1021,6 @@ getColLabelAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetColLabelAlignment), wxe_util:rec(?wxGrid_GetColLabelAlignment). -%% @doc See external documentation. -doc "Returns the current height of the column labels.". -spec getColLabelSize(This) -> integer() when This::wxGrid(). @@ -1084,14 +1029,12 @@ getColLabelSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetColLabelSize), wxe_util:rec(?wxGrid_GetColLabelSize). -%% @doc See external documentation. -doc """ Returns the specified column label. -The default grid table class provides column labels of the form -A,B...Z,AA,AB...ZZ,AAA... If you are using a custom grid table you can override -`wxGridTableBase::GetColLabelValue()` (not implemented in wx) to provide your -own labels. +The default grid table class provides column labels of the form A,B...Z,AA,AB...ZZ,AAA... +If you are using a custom grid table you can override `wxGridTableBase::GetColLabelValue()` +(not implemented in wx) to provide your own labels. """. -spec getColLabelValue(This, Col) -> unicode:charlist() when This::wxGrid(), Col::integer(). @@ -1101,12 +1044,10 @@ getColLabelValue(#wx_ref{type=ThisT}=This,Col) wxe_util:queue_cmd(This,Col,?get_env(),?wxGrid_GetColLabelValue), wxe_util:rec(?wxGrid_GetColLabelValue). -%% @doc See external documentation. -doc """ Returns the minimal width to which a column may be resized. -Use `setColMinimalAcceptableWidth/2` to change this value globally or -`setColMinimalWidth/3` to do it for individual columns. +Use `setColMinimalAcceptableWidth/2` to change this value globally or `setColMinimalWidth/3` to do it for individual columns. See: `getRowMinimalAcceptableHeight/1` """. @@ -1117,15 +1058,12 @@ getColMinimalAcceptableWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetColMinimalAcceptableWidth), wxe_util:rec(?wxGrid_GetColMinimalAcceptableWidth). -%% @doc See external documentation. -doc """ Returns the default cell alignment. -Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. +Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. -Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or -`wxALIGN_BOTTOM`. +Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. See: `setDefaultCellAlignment/3` """. @@ -1136,7 +1074,6 @@ getDefaultCellAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultCellAlignment), wxe_util:rec(?wxGrid_GetDefaultCellAlignment). -%% @doc See external documentation. -doc "Returns the current default background colour for grid cells.". -spec getDefaultCellBackgroundColour(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1145,7 +1082,6 @@ getDefaultCellBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultCellBackgroundColour), wxe_util:rec(?wxGrid_GetDefaultCellBackgroundColour). -%% @doc See external documentation. -doc "Returns the current default font for grid cell text.". -spec getDefaultCellFont(This) -> wxFont:wxFont() when This::wxGrid(). @@ -1154,7 +1090,6 @@ getDefaultCellFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultCellFont), wxe_util:rec(?wxGrid_GetDefaultCellFont). -%% @doc See external documentation. -doc "Returns the current default colour for grid cell text.". -spec getDefaultCellTextColour(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1163,7 +1098,6 @@ getDefaultCellTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultCellTextColour), wxe_util:rec(?wxGrid_GetDefaultCellTextColour). -%% @doc See external documentation. -doc "Returns the default height for column labels.". -spec getDefaultColLabelSize(This) -> integer() when This::wxGrid(). @@ -1172,7 +1106,6 @@ getDefaultColLabelSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultColLabelSize), wxe_util:rec(?wxGrid_GetDefaultColLabelSize). -%% @doc See external documentation. -doc "Returns the current default width for grid columns.". -spec getDefaultColSize(This) -> integer() when This::wxGrid(). @@ -1181,12 +1114,11 @@ getDefaultColSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultColSize), wxe_util:rec(?wxGrid_GetDefaultColSize). -%% @doc See external documentation. -doc """ Returns a pointer to the current default grid cell editor. -See `m:wxGridCellEditor` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellEditor` and the overview_grid for more information about cell editors +and renderers. """. -spec getDefaultEditor(This) -> wxGridCellEditor:wxGridCellEditor() when This::wxGrid(). @@ -1195,16 +1127,14 @@ getDefaultEditor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultEditor), wxe_util:rec(?wxGrid_GetDefaultEditor). -%% @doc See external documentation. -doc """ Returns the default editor for the specified cell. -The base class version returns the editor appropriate for the current cell type -but this method may be overridden in the derived classes to use custom editors -for some cells by default. +The base class version returns the editor appropriate for the current cell type but this +method may be overridden in the derived classes to use custom editors for some cells by default. -Notice that the same may be achieved in a usually simpler way by associating a -custom editor with the given cell or cells. +Notice that the same may be achieved in a usually simpler way by associating a custom +editor with the given cell or cells. The caller must call DecRef() on the returned pointer. """. @@ -1216,16 +1146,14 @@ getDefaultEditorForCell(#wx_ref{type=ThisT}=This,{CR,CC} = C) wxe_util:queue_cmd(This,C,?get_env(),?wxGrid_GetDefaultEditorForCell_1), wxe_util:rec(?wxGrid_GetDefaultEditorForCell_1). -%% @doc See external documentation. -doc """ Returns the default editor for the specified cell. -The base class version returns the editor appropriate for the current cell type -but this method may be overridden in the derived classes to use custom editors -for some cells by default. +The base class version returns the editor appropriate for the current cell type but this +method may be overridden in the derived classes to use custom editors for some cells by default. -Notice that the same may be achieved in a usually simpler way by associating a -custom editor with the given cell or cells. +Notice that the same may be achieved in a usually simpler way by associating a custom +editor with the given cell or cells. The caller must call DecRef() on the returned pointer. """. @@ -1237,14 +1165,12 @@ getDefaultEditorForCell(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetDefaultEditorForCell_2), wxe_util:rec(?wxGrid_GetDefaultEditorForCell_2). -%% @doc See external documentation. -doc """ Returns the default editor for the cells containing values of the given type. -The base class version returns the editor which was associated with the -specified `typeName` when it was registered `registerDataType/4` but this -function may be overridden to return something different. This allows overriding -an editor used for one of the standard types. +The base class version returns the editor which was associated with the specified `typeName` +when it was registered `registerDataType/4` but this function may be overridden to return something +different. This allows overriding an editor used for one of the standard types. The caller must call DecRef() on the returned pointer. """. @@ -1257,12 +1183,11 @@ getDefaultEditorForType(#wx_ref{type=ThisT}=This,TypeName) wxe_util:queue_cmd(This,TypeName_UC,?get_env(),?wxGrid_GetDefaultEditorForType), wxe_util:rec(?wxGrid_GetDefaultEditorForType). -%% @doc See external documentation. -doc """ Returns a pointer to the current default grid cell renderer. -See `m:wxGridCellRenderer` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellRenderer` and the overview_grid for more information about cell editors +and renderers. The caller must call DecRef() on the returned pointer. """. @@ -1273,13 +1198,12 @@ getDefaultRenderer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultRenderer), wxe_util:rec(?wxGrid_GetDefaultRenderer). -%% @doc See external documentation. -doc """ Returns the default renderer for the given cell. -The base class version returns the renderer appropriate for the current cell -type but this method may be overridden in the derived classes to use custom -renderers for some cells by default. +The base class version returns the renderer appropriate for the current cell type but +this method may be overridden in the derived classes to use custom renderers for some +cells by default. The caller must call DecRef() on the returned pointer. """. @@ -1291,7 +1215,6 @@ getDefaultRendererForCell(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetDefaultRendererForCell), wxe_util:rec(?wxGrid_GetDefaultRendererForCell). -%% @doc See external documentation. -doc """ Returns the default renderer for the cell containing values of the given type. @@ -1306,7 +1229,6 @@ getDefaultRendererForType(#wx_ref{type=ThisT}=This,TypeName) wxe_util:queue_cmd(This,TypeName_UC,?get_env(),?wxGrid_GetDefaultRendererForType), wxe_util:rec(?wxGrid_GetDefaultRendererForType). -%% @doc See external documentation. -doc "Returns the default width for the row labels.". -spec getDefaultRowLabelSize(This) -> integer() when This::wxGrid(). @@ -1315,7 +1237,6 @@ getDefaultRowLabelSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultRowLabelSize), wxe_util:rec(?wxGrid_GetDefaultRowLabelSize). -%% @doc See external documentation. -doc "Returns the current default height for grid rows.". -spec getDefaultRowSize(This) -> integer() when This::wxGrid(). @@ -1324,12 +1245,7 @@ getDefaultRowSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetDefaultRowSize), wxe_util:rec(?wxGrid_GetDefaultRowSize). -%% @doc See external documentation. --doc """ -Returns the current grid cell column position. - -See: `GetGridCursorCoords()` (not implemented in wx) -""". +-doc "Returns the current grid cell column position.". -spec getGridCursorCol(This) -> integer() when This::wxGrid(). getGridCursorCol(#wx_ref{type=ThisT}=This) -> @@ -1337,12 +1253,7 @@ getGridCursorCol(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridCursorCol), wxe_util:rec(?wxGrid_GetGridCursorCol). -%% @doc See external documentation. --doc """ -Returns the current grid cell row position. - -See: `GetGridCursorCoords()` (not implemented in wx) -""". +-doc "Returns the current grid cell row position.". -spec getGridCursorRow(This) -> integer() when This::wxGrid(). getGridCursorRow(#wx_ref{type=ThisT}=This) -> @@ -1350,12 +1261,7 @@ getGridCursorRow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridCursorRow), wxe_util:rec(?wxGrid_GetGridCursorRow). -%% @doc See external documentation. --doc """ -Returns the colour used for grid lines. - -See: `GetDefaultGridLinePen()` (not implemented in wx) -""". +-doc "Returns the colour used for grid lines.". -spec getGridLineColour(This) -> wx:wx_colour4() when This::wxGrid(). getGridLineColour(#wx_ref{type=ThisT}=This) -> @@ -1363,7 +1269,6 @@ getGridLineColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridLineColour), wxe_util:rec(?wxGrid_GetGridLineColour). -%% @doc See external documentation. -doc "Returns true if drawing of grid lines is turned on, false otherwise.". -spec gridLinesEnabled(This) -> boolean() when This::wxGrid(). @@ -1372,7 +1277,6 @@ gridLinesEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GridLinesEnabled), wxe_util:rec(?wxGrid_GridLinesEnabled). -%% @doc See external documentation. -doc "Returns the colour used for the background of row and column labels.". -spec getLabelBackgroundColour(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1381,7 +1285,6 @@ getLabelBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetLabelBackgroundColour), wxe_util:rec(?wxGrid_GetLabelBackgroundColour). -%% @doc See external documentation. -doc "Returns the font used for row and column labels.". -spec getLabelFont(This) -> wxFont:wxFont() when This::wxGrid(). @@ -1390,7 +1293,6 @@ getLabelFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetLabelFont), wxe_util:rec(?wxGrid_GetLabelFont). -%% @doc See external documentation. -doc "Returns the colour used for row and column label text.". -spec getLabelTextColour(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1399,7 +1301,6 @@ getLabelTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetLabelTextColour), wxe_util:rec(?wxGrid_GetLabelTextColour). -%% @doc See external documentation. -doc """ Returns the total number of grid columns. @@ -1412,7 +1313,6 @@ getNumberCols(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetNumberCols), wxe_util:rec(?wxGrid_GetNumberCols). -%% @doc See external documentation. -doc """ Returns the total number of grid rows. @@ -1425,19 +1325,18 @@ getNumberRows(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetNumberRows), wxe_util:rec(?wxGrid_GetNumberRows). -%% @doc See external documentation. -doc """ Returns the attribute for the given cell creating one if necessary. -If the cell already has an attribute, it is returned. Otherwise a new attribute -is created, associated with the cell and returned. In any case the caller must -call DecRef() on the returned pointer. +If the cell already has an attribute, it is returned. Otherwise a new attribute is +created, associated with the cell and returned. In any case the caller must call DecRef() +on the returned pointer. -Prefer to use `GetOrCreateCellAttrPtr()` (not implemented in wx) to avoid the -need to call DecRef() on the returned pointer. +Prefer to use `GetOrCreateCellAttrPtr()` (not implemented in wx) to avoid the need to +call DecRef() on the returned pointer. -This function may only be called if `CanHaveAttributes()` (not implemented in -wx) returns true. +This function may only be called if `CanHaveAttributes()` (not implemented in wx) returns +true. """. -spec getOrCreateCellAttr(This, Row, Col) -> wxGridCellAttr:wxGridCellAttr() when This::wxGrid(), Row::integer(), Col::integer(). @@ -1447,12 +1346,10 @@ getOrCreateCellAttr(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_GetOrCreateCellAttr), wxe_util:rec(?wxGrid_GetOrCreateCellAttr). -%% @doc See external documentation. -doc """ Returns the minimal size to which rows can be resized. -Use `setRowMinimalAcceptableHeight/2` to change this value globally or -`setRowMinimalHeight/3` to do it for individual cells. +Use `setRowMinimalAcceptableHeight/2` to change this value globally or `setRowMinimalHeight/3` to do it for individual cells. See: `getColMinimalAcceptableWidth/1` """. @@ -1463,15 +1360,12 @@ getRowMinimalAcceptableHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetRowMinimalAcceptableHeight), wxe_util:rec(?wxGrid_GetRowMinimalAcceptableHeight). -%% @doc See external documentation. -doc """ Returns the alignment used for row labels. -Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. +Horizontal alignment will be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. -Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or -`wxALIGN_BOTTOM`. +Vertical alignment will be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec getRowLabelAlignment(This) -> {Horiz::integer(), Vert::integer()} when This::wxGrid(). @@ -1480,7 +1374,6 @@ getRowLabelAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetRowLabelAlignment), wxe_util:rec(?wxGrid_GetRowLabelAlignment). -%% @doc See external documentation. -doc "Returns the current width of the row labels.". -spec getRowLabelSize(This) -> integer() when This::wxGrid(). @@ -1489,13 +1382,12 @@ getRowLabelSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetRowLabelSize), wxe_util:rec(?wxGrid_GetRowLabelSize). -%% @doc See external documentation. -doc """ Returns the specified row label. -The default grid table class provides numeric row labels. If you are using a -custom grid table you can override `wxGridTableBase::GetRowLabelValue()` (not -implemented in wx) to provide your own labels. +The default grid table class provides numeric row labels. If you are using a custom grid +table you can override `wxGridTableBase::GetRowLabelValue()` (not implemented in wx) to +provide your own labels. """. -spec getRowLabelValue(This, Row) -> unicode:charlist() when This::wxGrid(), Row::integer(). @@ -1505,7 +1397,6 @@ getRowLabelValue(#wx_ref{type=ThisT}=This,Row) wxe_util:queue_cmd(This,Row,?get_env(),?wxGrid_GetRowLabelValue), wxe_util:rec(?wxGrid_GetRowLabelValue). -%% @doc See external documentation. -doc "Returns the height of the specified row.". -spec getRowSize(This, Row) -> integer() when This::wxGrid(), Row::integer(). @@ -1515,13 +1406,17 @@ getRowSize(#wx_ref{type=ThisT}=This,Row) wxe_util:queue_cmd(This,Row,?get_env(),?wxGrid_GetRowSize), wxe_util:rec(?wxGrid_GetRowSize). -%% @doc See external documentation. -doc """ Returns the number of pixels per horizontal scroll increment. The default is 15. -See: `getScrollLineY/1`, `setScrollLineX/2`, `setScrollLineY/2` +See: +* `getScrollLineY/1` + +* `setScrollLineX/2` + +* `setScrollLineY/2` """. -spec getScrollLineX(This) -> integer() when This::wxGrid(). @@ -1530,13 +1425,17 @@ getScrollLineX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetScrollLineX), wxe_util:rec(?wxGrid_GetScrollLineX). -%% @doc See external documentation. -doc """ Returns the number of pixels per vertical scroll increment. The default is 15. -See: `getScrollLineX/1`, `setScrollLineX/2`, `setScrollLineY/2` +See: +* `getScrollLineX/1` + +* `setScrollLineX/2` + +* `setScrollLineY/2` """. -spec getScrollLineY(This) -> integer() when This::wxGrid(). @@ -1545,24 +1444,20 @@ getScrollLineY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetScrollLineY), wxe_util:rec(?wxGrid_GetScrollLineY). -%% @doc See external documentation. -doc """ Returns an array of individually selected cells. -Notice that this array does `not` contain all the selected cells in general as -it doesn't include the cells selected as part of column, row or block selection. -You must use this method, `getSelectedCols/1`, `getSelectedRows/1` and -`getSelectionBlockTopLeft/1` and `getSelectionBlockBottomRight/1` methods to -obtain the entire selection in general. +Notice that this array does `not` contain all the selected cells in general as it doesn't +include the cells selected as part of column, row or block selection. You must use this +method, `getSelectedCols/1`, `getSelectedRows/1` and `getSelectionBlockTopLeft/1` and `getSelectionBlockBottomRight/1` methods to obtain the entire selection in general. -Please notice this behaviour is by design and is needed in order to support -grids of arbitrary size (when an entire column is selected in a grid with a -million of columns, we don't want to create an array with a million of entries -in this function, instead it returns an empty array and `getSelectedCols/1` -returns an array containing one element). +Please notice this behaviour is by design and is needed in order to support grids of +arbitrary size (when an entire column is selected in a grid with a million of columns, we +don't want to create an array with a million of entries in this function, instead it +returns an empty array and `getSelectedCols/1` returns an array containing one element). -The function can be slow for the big grids, use `GetSelectedBlocks()` (not -implemented in wx) in the new code. +The function can be slow for the big grids, use `GetSelectedBlocks()` (not implemented in +wx) in the new code. """. -spec getSelectedCells(This) -> [{R::integer(), C::integer()}] when This::wxGrid(). @@ -1571,18 +1466,16 @@ getSelectedCells(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectedCells), wxe_util:rec(?wxGrid_GetSelectedCells). -%% @doc See external documentation. -doc """ Returns an array of selected columns. -Please notice that this method alone is not sufficient to find all the selected -columns as it contains only the columns which were individually selected but not -those being part of the block selection or being selected in virtue of all of -their cells being selected individually, please see `getSelectedCells/1` for -more details. +Please notice that this method alone is not sufficient to find all the selected columns +as it contains only the columns which were individually selected but not those being part +of the block selection or being selected in virtue of all of their cells being selected +individually, please see `getSelectedCells/1` for more details. -The function can be slow for the big grids, use `GetSelectedBlocks()` (not -implemented in wx) in the new code. +The function can be slow for the big grids, use `GetSelectedBlocks()` (not implemented in +wx) in the new code. """. -spec getSelectedCols(This) -> [integer()] when This::wxGrid(). @@ -1591,18 +1484,16 @@ getSelectedCols(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectedCols), wxe_util:rec(?wxGrid_GetSelectedCols). -%% @doc See external documentation. -doc """ Returns an array of selected rows. -Please notice that this method alone is not sufficient to find all the selected -rows as it contains only the rows which were individually selected but not those -being part of the block selection or being selected in virtue of all of their -cells being selected individually, please see `getSelectedCells/1` for more -details. +Please notice that this method alone is not sufficient to find all the selected rows as +it contains only the rows which were individually selected but not those being part of the +block selection or being selected in virtue of all of their cells being selected +individually, please see `getSelectedCells/1` for more details. -The function can be slow for the big grids, use `GetSelectedBlocks()` (not -implemented in wx) in the new code. +The function can be slow for the big grids, use `GetSelectedBlocks()` (not implemented in +wx) in the new code. """. -spec getSelectedRows(This) -> [integer()] when This::wxGrid(). @@ -1611,7 +1502,6 @@ getSelectedRows(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectedRows), wxe_util:rec(?wxGrid_GetSelectedRows). -%% @doc See external documentation. -doc "Returns the colour used for drawing the selection background.". -spec getSelectionBackground(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1620,15 +1510,13 @@ getSelectionBackground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectionBackground), wxe_util:rec(?wxGrid_GetSelectionBackground). -%% @doc See external documentation. -doc """ Returns an array of the top left corners of blocks of selected cells. -Please see `getSelectedCells/1` for more information about the selection -representation in `m:wxGrid`. +Please see `getSelectedCells/1` for more information about the selection representation in `m:wxGrid`. -The function can be slow for the big grids, use `GetSelectedBlocks()` (not -implemented in wx) in the new code. +The function can be slow for the big grids, use `GetSelectedBlocks()` (not implemented in +wx) in the new code. See: `getSelectionBlockBottomRight/1` """. @@ -1639,15 +1527,13 @@ getSelectionBlockTopLeft(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectionBlockTopLeft), wxe_util:rec(?wxGrid_GetSelectionBlockTopLeft). -%% @doc See external documentation. -doc """ Returns an array of the bottom right corners of blocks of selected cells. -Please see `getSelectedCells/1` for more information about the selection -representation in `m:wxGrid`. +Please see `getSelectedCells/1` for more information about the selection representation in `m:wxGrid`. -The function can be slow for the big grids, use `GetSelectedBlocks()` (not -implemented in wx) in the new code. +The function can be slow for the big grids, use `GetSelectedBlocks()` (not implemented in +wx) in the new code. See: `getSelectionBlockTopLeft/1` """. @@ -1658,7 +1544,6 @@ getSelectionBlockBottomRight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectionBlockBottomRight), wxe_util:rec(?wxGrid_GetSelectionBlockBottomRight). -%% @doc See external documentation. -doc "Returns the colour used for drawing the selection foreground.". -spec getSelectionForeground(This) -> wx:wx_colour4() when This::wxGrid(). @@ -1667,7 +1552,6 @@ getSelectionForeground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetSelectionForeground), wxe_util:rec(?wxGrid_GetSelectionForeground). -%% @doc See external documentation. -doc """ Return the main grid window containing the grid cells. @@ -1680,12 +1564,11 @@ getGridWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridWindow), wxe_util:rec(?wxGrid_GetGridWindow). -%% @doc See external documentation. -doc """ Return the row labels window. -This window is not shown if the row labels were hidden using `HideRowLabels()` -(not implemented in wx). +This window is not shown if the row labels were hidden using `HideRowLabels()` (not +implemented in wx). """. -spec getGridRowLabelWindow(This) -> wxWindow:wxWindow() when This::wxGrid(). @@ -1694,18 +1577,17 @@ getGridRowLabelWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridRowLabelWindow), wxe_util:rec(?wxGrid_GetGridRowLabelWindow). -%% @doc See external documentation. -doc """ Return the column labels window. -This window is not shown if the columns labels were hidden using -`HideColLabels()` (not implemented in wx). +This window is not shown if the columns labels were hidden using `HideColLabels()` (not +implemented in wx). -Depending on whether `UseNativeColHeader()` (not implemented in wx) was called -or not this can be either a `wxHeaderCtrl` (not implemented in wx) or a plain -`m:wxWindow`. This function returns a valid window pointer in either case but in -the former case you can also use `GetGridColHeader()` (not implemented in wx) to -access it if you need wxHeaderCtrl-specific functionality. +Depending on whether `UseNativeColHeader()` (not implemented in wx) was called or not +this can be either a `wxHeaderCtrl` (not implemented in wx) or a plain `m:wxWindow`. This +function returns a valid window pointer in either case but in the former case you can also +use `GetGridColHeader()` (not implemented in wx) to access it if you need +wxHeaderCtrl-specific functionality. """. -spec getGridColLabelWindow(This) -> wxWindow:wxWindow() when This::wxGrid(). @@ -1714,13 +1596,12 @@ getGridColLabelWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridColLabelWindow), wxe_util:rec(?wxGrid_GetGridColLabelWindow). -%% @doc See external documentation. -doc """ Return the window in the top left grid corner. -This window is shown only of both columns and row labels are shown and normally -doesn't contain anything. Clicking on it is handled by `m:wxGrid` however and -can be used to select the entire grid. +This window is shown only of both columns and row labels are shown and normally doesn't +contain anything. Clicking on it is handled by `m:wxGrid` however and can be used to +select the entire grid. """. -spec getGridCornerLabelWindow(This) -> wxWindow:wxWindow() when This::wxGrid(). @@ -1729,7 +1610,6 @@ getGridCornerLabelWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_GetGridCornerLabelWindow), wxe_util:rec(?wxGrid_GetGridCornerLabelWindow). -%% @doc See external documentation. -doc "Hides the in-place cell edit control.". -spec hideCellEditControl(This) -> 'ok' when This::wxGrid(). @@ -1737,7 +1617,7 @@ hideCellEditControl(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_HideCellEditControl). -%% @equiv insertCols(This, []) +-doc(#{equiv => insertCols(This, [])}). -spec insertCols(This) -> boolean() when This::wxGrid(). @@ -1745,22 +1625,20 @@ insertCols(This) when is_record(This, wx_ref) -> insertCols(This, []). -%% @doc See external documentation. -doc """ -Inserts one or more new columns into a grid with the first new column at the -specified position. +Inserts one or more new columns into a grid with the first new column at the specified +position. -Notice that inserting the columns in the grid requires grid table cooperation: -when this method is called, grid object begins by requesting the underlying grid -table to insert new columns. If this is successful the table notifies the grid -and the grid updates the display. For a default grid (one where you have called -`createGrid/4`) this process is automatic. If you are using a custom grid table -(specified with `SetTable()` (not implemented in wx) or `AssignTable()` (not -implemented in wx)) then you must override `wxGridTableBase::InsertCols()` (not +Notice that inserting the columns in the grid requires grid table cooperation: when this +method is called, grid object begins by requesting the underlying grid table to insert new +columns. If this is successful the table notifies the grid and the grid updates the +display. For a default grid (one where you have called `createGrid/4`) this process is automatic. If you +are using a custom grid table (specified with `SetTable()` (not implemented in wx) or `AssignTable()` +(not implemented in wx)) then you must override `wxGridTableBase::InsertCols()` (not implemented in wx) in your derived table class. -Return: true if the columns were successfully inserted, false if an error -occurred (most likely the table couldn't be updated). +Return: true if the columns were successfully inserted, false if an error occurred (most +likely the table couldn't be updated). """. -spec insertCols(This, [Option]) -> boolean() when This::wxGrid(), @@ -1778,7 +1656,7 @@ insertCols(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_InsertCols), wxe_util:rec(?wxGrid_InsertCols). -%% @equiv insertRows(This, []) +-doc(#{equiv => insertRows(This, [])}). -spec insertRows(This) -> boolean() when This::wxGrid(). @@ -1786,17 +1664,15 @@ insertRows(This) when is_record(This, wx_ref) -> insertRows(This, []). -%% @doc See external documentation. -doc """ Inserts one or more new rows into a grid with the first new row at the specified position. -Notice that you must implement `wxGridTableBase::InsertRows()` (not implemented -in wx) if you use a grid with a custom table, please see `insertCols/2` for more -information. +Notice that you must implement `wxGridTableBase::InsertRows()` (not implemented in wx) if +you use a grid with a custom table, please see `insertCols/2` for more information. -Return: true if the rows were successfully inserted, false if an error occurred -(most likely the table couldn't be updated). +Return: true if the rows were successfully inserted, false if an error occurred (most +likely the table couldn't be updated). """. -spec insertRows(This, [Option]) -> boolean() when This::wxGrid(), @@ -1814,7 +1690,6 @@ insertRows(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxGrid_InsertRows), wxe_util:rec(?wxGrid_InsertRows). -%% @doc See external documentation. -doc "Returns true if the in-place edit control is currently enabled.". -spec isCellEditControlEnabled(This) -> boolean() when This::wxGrid(). @@ -1823,11 +1698,13 @@ isCellEditControlEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_IsCellEditControlEnabled), wxe_util:rec(?wxGrid_IsCellEditControlEnabled). -%% @doc See external documentation. -doc """ Returns true if the current cell is read-only. -See: `setReadOnly/4`, `isReadOnly/3` +See: +* `setReadOnly/4` + +* `isReadOnly/3` """. -spec isCurrentCellReadOnly(This) -> boolean() when This::wxGrid(). @@ -1836,12 +1713,10 @@ isCurrentCellReadOnly(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_IsCurrentCellReadOnly), wxe_util:rec(?wxGrid_IsCurrentCellReadOnly). -%% @doc See external documentation. -doc """ Returns false if the whole grid has been set as read-only or true otherwise. -See `enableEditing/2` for more information about controlling the editing status -of grid cells. +See `enableEditing/2` for more information about controlling the editing status of grid cells. """. -spec isEditable(This) -> boolean() when This::wxGrid(). @@ -1850,7 +1725,6 @@ isEditable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_IsEditable), wxe_util:rec(?wxGrid_IsEditable). -%% @doc See external documentation. -doc "Returns true if the given cell is selected.". -spec isInSelection(This, Coords) -> boolean() when This::wxGrid(), Coords::{R::integer(), C::integer()}. @@ -1860,7 +1734,6 @@ isInSelection(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords) wxe_util:queue_cmd(This,Coords,?get_env(),?wxGrid_IsInSelection_1), wxe_util:rec(?wxGrid_IsInSelection_1). -%% @doc See external documentation. -doc "Returns true if the given cell is selected.". -spec isInSelection(This, Row, Col) -> boolean() when This::wxGrid(), Row::integer(), Col::integer(). @@ -1870,11 +1743,13 @@ isInSelection(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_IsInSelection_2), wxe_util:rec(?wxGrid_IsInSelection_2). -%% @doc See external documentation. -doc """ Returns true if the cell at the specified location can't be edited. -See: `setReadOnly/4`, `isCurrentCellReadOnly/1` +See: +* `setReadOnly/4` + +* `isCurrentCellReadOnly/1` """. -spec isReadOnly(This, Row, Col) -> boolean() when This::wxGrid(), Row::integer(), Col::integer(). @@ -1884,7 +1759,6 @@ isReadOnly(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_IsReadOnly), wxe_util:rec(?wxGrid_IsReadOnly). -%% @doc See external documentation. -doc "Returns true if there are currently any selected cells, rows, columns or blocks.". -spec isSelection(This) -> boolean() when This::wxGrid(). @@ -1893,7 +1767,7 @@ isSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_IsSelection), wxe_util:rec(?wxGrid_IsSelection). -%% @equiv isVisible(This,Coords, []) +-doc(#{equiv => isVisible(This,Coords, [])}). -spec isVisible(This, Coords) -> boolean() when This::wxGrid(), Coords::{R::integer(), C::integer()}. @@ -1901,19 +1775,12 @@ isVisible(This,{CoordsR,CoordsC} = Coords) when is_record(This, wx_ref),is_integer(CoordsR),is_integer(CoordsC) -> isVisible(This,Coords, []). -%% @doc See external documentation. -%%
Also:
-%% isVisible(This, Coords, [Option]) -> boolean() when
-%% This::wxGrid(), Coords::{R::integer(), C::integer()},
-%% Option :: {'wholeCellVisible', boolean()}.
-%% -doc """ -Returns true if a cell is either entirely or at least partially visible in the -grid window. +Returns true if a cell is either entirely or at least partially visible in the grid +window. -By default, the cell must be entirely visible for this function to return true -but if `wholeCellVisible` is false, the function returns true even if the cell -is only partially visible. +By default, the cell must be entirely visible for this function to return true but if `wholeCellVisible` +is false, the function returns true even if the cell is only partially visible. """. -spec isVisible(This, Row, Col) -> boolean() when This::wxGrid(), Row::integer(), Col::integer(); @@ -1933,14 +1800,12 @@ isVisible(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords, Options) wxe_util:queue_cmd(This,Coords, Opts,?get_env(),?wxGrid_IsVisible_2), wxe_util:rec(?wxGrid_IsVisible_2). -%% @doc See external documentation. -doc """ -Returns true if a cell is either entirely or at least partially visible in the -grid window. +Returns true if a cell is either entirely or at least partially visible in the grid +window. -By default, the cell must be entirely visible for this function to return true -but if `wholeCellVisible` is false, the function returns true even if the cell -is only partially visible. +By default, the cell must be entirely visible for this function to return true but if `wholeCellVisible` +is false, the function returns true even if the cell is only partially visible. """. -spec isVisible(This, Row, Col, [Option]) -> boolean() when This::wxGrid(), Row::integer(), Col::integer(), @@ -1954,10 +1819,8 @@ isVisible(#wx_ref{type=ThisT}=This,Row,Col, Options) wxe_util:queue_cmd(This,Row,Col, Opts,?get_env(),?wxGrid_IsVisible_3), wxe_util:rec(?wxGrid_IsVisible_3). -%% @doc See external documentation. -doc """ -Brings the specified cell into the visible grid cell area with minimal -scrolling. +Brings the specified cell into the visible grid cell area with minimal scrolling. Does nothing if the cell is already visible. """. @@ -1968,10 +1831,8 @@ makeCellVisible(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Coords,?get_env(),?wxGrid_MakeCellVisible_1). -%% @doc See external documentation. -doc """ -Brings the specified cell into the visible grid cell area with minimal -scrolling. +Brings the specified cell into the visible grid cell area with minimal scrolling. Does nothing if the cell is already visible. """. @@ -1982,12 +1843,11 @@ makeCellVisible(#wx_ref{type=ThisT}=This,Row,Col) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_MakeCellVisible_2). -%% @doc See external documentation. -doc """ Moves the grid cursor down by one row. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorDown(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -1997,12 +1857,11 @@ moveCursorDown(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorDown), wxe_util:rec(?wxGrid_MoveCursorDown). -%% @doc See external documentation. -doc """ Moves the grid cursor left by one column. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorLeft(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2012,12 +1871,11 @@ moveCursorLeft(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorLeft), wxe_util:rec(?wxGrid_MoveCursorLeft). -%% @doc See external documentation. -doc """ Moves the grid cursor right by one column. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorRight(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2027,12 +1885,11 @@ moveCursorRight(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorRight), wxe_util:rec(?wxGrid_MoveCursorRight). -%% @doc See external documentation. -doc """ Moves the grid cursor up by one row. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorUp(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2042,13 +1899,12 @@ moveCursorUp(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorUp), wxe_util:rec(?wxGrid_MoveCursorUp). -%% @doc See external documentation. -doc """ -Moves the grid cursor down in the current column such that it skips to the -beginning or end of a block of non-empty cells. +Moves the grid cursor down in the current column such that it skips to the beginning or +end of a block of non-empty cells. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorDownBlock(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2058,13 +1914,12 @@ moveCursorDownBlock(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorDownBlock), wxe_util:rec(?wxGrid_MoveCursorDownBlock). -%% @doc See external documentation. -doc """ -Moves the grid cursor left in the current row such that it skips to the -beginning or end of a block of non-empty cells. +Moves the grid cursor left in the current row such that it skips to the beginning or end +of a block of non-empty cells. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorLeftBlock(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2074,13 +1929,12 @@ moveCursorLeftBlock(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorLeftBlock), wxe_util:rec(?wxGrid_MoveCursorLeftBlock). -%% @doc See external documentation. -doc """ -Moves the grid cursor right in the current row such that it skips to the -beginning or end of a block of non-empty cells. +Moves the grid cursor right in the current row such that it skips to the beginning or end +of a block of non-empty cells. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorRightBlock(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2090,13 +1944,12 @@ moveCursorRightBlock(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorRightBlock), wxe_util:rec(?wxGrid_MoveCursorRightBlock). -%% @doc See external documentation. -doc """ -Moves the grid cursor up in the current column such that it skips to the -beginning or end of a block of non-empty cells. +Moves the grid cursor up in the current column such that it skips to the beginning or end +of a block of non-empty cells. -If a block of cells was previously selected it will expand if the argument is -true or be cleared if the argument is false. +If a block of cells was previously selected it will expand if the argument is true or be +cleared if the argument is false. """. -spec moveCursorUpBlock(This, ExpandSelection) -> boolean() when This::wxGrid(), ExpandSelection::boolean(). @@ -2106,10 +1959,9 @@ moveCursorUpBlock(#wx_ref{type=ThisT}=This,ExpandSelection) wxe_util:queue_cmd(This,ExpandSelection,?get_env(),?wxGrid_MoveCursorUpBlock), wxe_util:rec(?wxGrid_MoveCursorUpBlock). -%% @doc See external documentation. -doc """ -Moves the grid cursor down by some number of rows so that the previous bottom -visible row becomes the top visible row. +Moves the grid cursor down by some number of rows so that the previous bottom visible row +becomes the top visible row. """. -spec movePageDown(This) -> boolean() when This::wxGrid(). @@ -2118,10 +1970,9 @@ movePageDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_MovePageDown), wxe_util:rec(?wxGrid_MovePageDown). -%% @doc See external documentation. -doc """ -Moves the grid cursor up by some number of rows so that the previous top visible -row becomes the bottom visible row. +Moves the grid cursor up by some number of rows so that the previous top visible row +becomes the bottom visible row. """. -spec movePageUp(This) -> boolean() when This::wxGrid(). @@ -2130,27 +1981,23 @@ movePageUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGrid_MovePageUp), wxe_util:rec(?wxGrid_MovePageUp). -%% @doc See external documentation. -doc """ Register a new data type. -The data types allow to naturally associate specific renderers and editors to -the cells containing values of the given type. For example, the grid -automatically registers a data type with the name `wxGRID_VALUE_STRING` which -uses `m:wxGridCellStringRenderer` and `m:wxGridCellTextEditor` as its renderer -and editor respectively - this is the data type used by all the cells of the -default `wxGridStringTable` (not implemented in wx), so this renderer and editor -are used by default for all grid cells. +The data types allow to naturally associate specific renderers and editors to the cells +containing values of the given type. For example, the grid automatically registers a data +type with the name `wxGRID_VALUE_STRING` which uses `m:wxGridCellStringRenderer` and `m:wxGridCellTextEditor` +as its renderer and editor respectively - this is the data type used by all the cells of +the default `wxGridStringTable` (not implemented in wx), so this renderer and editor are +used by default for all grid cells. -However if a custom table returns `wxGRID_VALUE_BOOL` from its -`wxGridTableBase::GetTypeName()` (not implemented in wx) method, then -`m:wxGridCellBoolRenderer` and `m:wxGridCellBoolEditor` are used for it because -the grid also registers a boolean data type with this name. +However if a custom table returns `wxGRID_VALUE_BOOL` from its `wxGridTableBase::GetTypeName()` +(not implemented in wx) method, then `m:wxGridCellBoolRenderer` and `m:wxGridCellBoolEditor` +are used for it because the grid also registers a boolean data type with this name. -And as this mechanism is completely generic, you may register your own data -types using your own custom renderers and editors. Just remember that the table -must identify a cell as being of the given type for them to be used for this -cell. +And as this mechanism is completely generic, you may register your own data types using +your own custom renderers and editors. Just remember that the table must identify a cell +as being of the given type for them to be used for this cell. """. -spec registerDataType(This, TypeName, Renderer, Editor) -> 'ok' when This::wxGrid(), TypeName::unicode:chardata(), Renderer::wxGridCellRenderer:wxGridCellRenderer(), Editor::wxGridCellEditor:wxGridCellEditor(). @@ -2162,14 +2009,12 @@ registerDataType(#wx_ref{type=ThisT}=This,TypeName,#wx_ref{type=RendererT}=Rende ?CLASS(EditorT,wxGridCellEditor), wxe_util:queue_cmd(This,TypeName_UC,Renderer,Editor,?get_env(),?wxGrid_RegisterDataType). -%% @doc See external documentation. -doc """ -Sets the value of the current grid cell to the current in-place edit control -value. +Sets the value of the current grid cell to the current in-place edit control value. -This is called automatically when the grid cursor moves from the current cell to -a new cell. It is also a good idea to call this function when closing a grid -since any edits to the final cell location will not be saved otherwise. +This is called automatically when the grid cursor moves from the current cell to a new +cell. It is also a good idea to call this function when closing a grid since any edits to +the final cell location will not be saved otherwise. """. -spec saveEditControlValue(This) -> 'ok' when This::wxGrid(). @@ -2177,7 +2022,6 @@ saveEditControlValue(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_SaveEditControlValue). -%% @doc See external documentation. -doc "Selects all cells in the grid.". -spec selectAll(This) -> 'ok' when This::wxGrid(). @@ -2185,7 +2029,7 @@ selectAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_SelectAll). -%% @equiv selectBlock(This,TopLeft,BottomRight, []) +-doc(#{equiv => selectBlock(This,TopLeft,BottomRight, [])}). -spec selectBlock(This, TopLeft, BottomRight) -> 'ok' when This::wxGrid(), TopLeft::{R::integer(), C::integer()}, BottomRight::{R::integer(), C::integer()}. @@ -2193,12 +2037,11 @@ selectBlock(This,{TopLeftR,TopLeftC} = TopLeft,{BottomRightR,BottomRightC} = Bot when is_record(This, wx_ref),is_integer(TopLeftR),is_integer(TopLeftC),is_integer(BottomRightR),is_integer(BottomRightC) -> selectBlock(This,TopLeft,BottomRight, []). -%% @doc See external documentation. -doc """ Selects a rectangular block of cells. -If `addToSelected` is false then any existing selection will be deselected; if -true the column will be added to the existing selection. +If `addToSelected` is false then any existing selection will be deselected; if true the +column will be added to the existing selection. """. -spec selectBlock(This, TopLeft, BottomRight, [Option]) -> 'ok' when This::wxGrid(), TopLeft::{R::integer(), C::integer()}, BottomRight::{R::integer(), C::integer()}, @@ -2211,7 +2054,7 @@ selectBlock(#wx_ref{type=ThisT}=This,{TopLeftR,TopLeftC} = TopLeft,{BottomRightR Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,TopLeft,BottomRight, Opts,?get_env(),?wxGrid_SelectBlock_3). -%% @equiv selectBlock(This,TopRow,LeftCol,BottomRow,RightCol, []) +-doc(#{equiv => selectBlock(This,TopRow,LeftCol,BottomRow,RightCol, [])}). -spec selectBlock(This, TopRow, LeftCol, BottomRow, RightCol) -> 'ok' when This::wxGrid(), TopRow::integer(), LeftCol::integer(), BottomRow::integer(), RightCol::integer(). @@ -2219,12 +2062,11 @@ selectBlock(This,TopRow,LeftCol,BottomRow,RightCol) when is_record(This, wx_ref),is_integer(TopRow),is_integer(LeftCol),is_integer(BottomRow),is_integer(RightCol) -> selectBlock(This,TopRow,LeftCol,BottomRow,RightCol, []). -%% @doc See external documentation. -doc """ Selects a rectangular block of cells. -If `addToSelected` is false then any existing selection will be deselected; if -true the column will be added to the existing selection. +If `addToSelected` is false then any existing selection will be deselected; if true the +column will be added to the existing selection. """. -spec selectBlock(This, TopRow, LeftCol, BottomRow, RightCol, [Option]) -> 'ok' when This::wxGrid(), TopRow::integer(), LeftCol::integer(), BottomRow::integer(), RightCol::integer(), @@ -2237,7 +2079,7 @@ selectBlock(#wx_ref{type=ThisT}=This,TopRow,LeftCol,BottomRow,RightCol, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,TopRow,LeftCol,BottomRow,RightCol, Opts,?get_env(),?wxGrid_SelectBlock_5). -%% @equiv selectCol(This,Col, []) +-doc(#{equiv => selectCol(This,Col, [])}). -spec selectCol(This, Col) -> 'ok' when This::wxGrid(), Col::integer(). @@ -2245,15 +2087,13 @@ selectCol(This,Col) when is_record(This, wx_ref),is_integer(Col) -> selectCol(This,Col, []). -%% @doc See external documentation. -doc """ Selects the specified column. -If `addToSelected` is false then any existing selection will be deselected; if -true the column will be added to the existing selection. +If `addToSelected` is false then any existing selection will be deselected; if true the +column will be added to the existing selection. -This method won't select anything if the current selection mode is -wxGridSelectRows. +This method won't select anything if the current selection mode is wxGridSelectRows. """. -spec selectCol(This, Col, [Option]) -> 'ok' when This::wxGrid(), Col::integer(), @@ -2266,7 +2106,7 @@ selectCol(#wx_ref{type=ThisT}=This,Col, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Col, Opts,?get_env(),?wxGrid_SelectCol). -%% @equiv selectRow(This,Row, []) +-doc(#{equiv => selectRow(This,Row, [])}). -spec selectRow(This, Row) -> 'ok' when This::wxGrid(), Row::integer(). @@ -2274,15 +2114,13 @@ selectRow(This,Row) when is_record(This, wx_ref),is_integer(Row) -> selectRow(This,Row, []). -%% @doc See external documentation. -doc """ Selects the specified row. -If `addToSelected` is false then any existing selection will be deselected; if -true the row will be added to the existing selection. +If `addToSelected` is false then any existing selection will be deselected; if true the +row will be added to the existing selection. -This method won't select anything if the current selection mode is -wxGridSelectColumns. +This method won't select anything if the current selection mode is wxGridSelectColumns. """. -spec selectRow(This, Row, [Option]) -> 'ok' when This::wxGrid(), Row::integer(), @@ -2295,16 +2133,12 @@ selectRow(#wx_ref{type=ThisT}=This,Row, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Row, Opts,?get_env(),?wxGrid_SelectRow). -%% @doc See external documentation. -doc """ -Sets the horizontal and vertical alignment for grid cell text at the specified -location. +Sets the horizontal and vertical alignment for grid cell text at the specified location. -Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. +Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. -Vertical alignment should be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or -`wxALIGN_BOTTOM`. +Vertical alignment should be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec setCellAlignment(This, Row, Col, Horiz, Vert) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Horiz::integer(), Vert::integer(). @@ -2313,7 +2147,6 @@ setCellAlignment(#wx_ref{type=ThisT}=This,Row,Col,Horiz,Vert) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Col,Horiz,Vert,?get_env(),?wxGrid_SetCellAlignment). -%% @doc See external documentation. -doc "Set the background colour for the given cell or all cells by default.". -spec setCellBackgroundColour(This, Row, Col, Colour) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Colour::wx:wx_colour(). @@ -2322,14 +2155,13 @@ setCellBackgroundColour(#wx_ref{type=ThisT}=This,Row,Col,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Col,wxe_util:color(Colour),?get_env(),?wxGrid_SetCellBackgroundColour). -%% @doc See external documentation. -doc """ Sets the editor for the grid cell at the specified location. The grid will take ownership of the pointer. -See `m:wxGridCellEditor` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellEditor` and the overview_grid for more information about cell editors +and renderers. """. -spec setCellEditor(This, Row, Col, Editor) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Editor::wxGridCellEditor:wxGridCellEditor(). @@ -2339,7 +2171,6 @@ setCellEditor(#wx_ref{type=ThisT}=This,Row,Col,#wx_ref{type=EditorT}=Editor) ?CLASS(EditorT,wxGridCellEditor), wxe_util:queue_cmd(This,Row,Col,Editor,?get_env(),?wxGrid_SetCellEditor). -%% @doc See external documentation. -doc "Sets the font for text in the grid cell at the specified location.". -spec setCellFont(This, Row, Col, Font) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Font::wxFont:wxFont(). @@ -2349,14 +2180,13 @@ setCellFont(#wx_ref{type=ThisT}=This,Row,Col,#wx_ref{type=FontT}=Font) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Row,Col,Font,?get_env(),?wxGrid_SetCellFont). -%% @doc See external documentation. -doc """ Sets the renderer for the grid cell at the specified location. The grid will take ownership of the pointer. -See `m:wxGridCellRenderer` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellRenderer` and the overview_grid for more information about cell editors +and renderers. """. -spec setCellRenderer(This, Row, Col, Renderer) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Renderer::wxGridCellRenderer:wxGridCellRenderer(). @@ -2366,7 +2196,6 @@ setCellRenderer(#wx_ref{type=ThisT}=This,Row,Col,#wx_ref{type=RendererT}=Rendere ?CLASS(RendererT,wxGridCellRenderer), wxe_util:queue_cmd(This,Row,Col,Renderer,?get_env(),?wxGrid_SetCellRenderer). -%% @doc See external documentation. -doc "Sets the text colour for the given cell.". -spec setCellTextColour(This, Row, Col, Colour) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), Colour::wx:wx_colour(). @@ -2375,19 +2204,17 @@ setCellTextColour(#wx_ref{type=ThisT}=This,Row,Col,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Col,wxe_util:color(Colour),?get_env(),?wxGrid_SetCellTextColour). -%% @doc See external documentation. -doc """ Sets the string value for the cell at the specified location. -For simple applications where a grid object automatically uses a default grid -table of string values you use this function together with `getCellValue/3` to -access cell values. For more complex applications where you have derived your -own grid table class that contains various data types (e.g. numeric, boolean or -user-defined custom types) then you only use this function for those cells that -contain string values. +For simple applications where a grid object automatically uses a default grid table of +string values you use this function together with `getCellValue/3` to access cell values. For more complex +applications where you have derived your own grid table class that contains various data +types (e.g. numeric, boolean or user-defined custom types) then you only use this function +for those cells that contain string values. -See `wxGridTableBase::CanSetValueAs()` (not implemented in wx) and the -overview_grid for more information. +See `wxGridTableBase::CanSetValueAs()` (not implemented in wx) and the overview_grid for +more information. """. -spec setCellValue(This, Coords, S) -> 'ok' when This::wxGrid(), Coords::{R::integer(), C::integer()}, S::unicode:chardata(). @@ -2397,19 +2224,17 @@ setCellValue(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords,S) S_UC = unicode:characters_to_binary(S), wxe_util:queue_cmd(This,Coords,S_UC,?get_env(),?wxGrid_SetCellValue_2). -%% @doc See external documentation. -doc """ Sets the string value for the cell at the specified location. -For simple applications where a grid object automatically uses a default grid -table of string values you use this function together with `getCellValue/3` to -access cell values. For more complex applications where you have derived your -own grid table class that contains various data types (e.g. numeric, boolean or -user-defined custom types) then you only use this function for those cells that -contain string values. +For simple applications where a grid object automatically uses a default grid table of +string values you use this function together with `getCellValue/3` to access cell values. For more complex +applications where you have derived your own grid table class that contains various data +types (e.g. numeric, boolean or user-defined custom types) then you only use this function +for those cells that contain string values. -See `wxGridTableBase::CanSetValueAs()` (not implemented in wx) and the -overview_grid for more information. +See `wxGridTableBase::CanSetValueAs()` (not implemented in wx) and the overview_grid for +more information. """. -spec setCellValue(This, Row, Col, S) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(), S::unicode:chardata(). @@ -2419,12 +2244,11 @@ setCellValue(#wx_ref{type=ThisT}=This,Row,Col,S) S_UC = unicode:characters_to_binary(S), wxe_util:queue_cmd(This,Row,Col,S_UC,?get_env(),?wxGrid_SetCellValue_3). -%% @doc See external documentation. -doc """ Sets the cell attributes for all cells in the specified column. -For more information about controlling grid cell attributes see the -`m:wxGridCellAttr` cell attribute class and the overview_grid. +For more information about controlling grid cell attributes see the `m:wxGridCellAttr` +cell attribute class and the overview_grid. """. -spec setColAttr(This, Col, Attr) -> 'ok' when This::wxGrid(), Col::integer(), Attr::wxGridCellAttr:wxGridCellAttr(). @@ -2434,7 +2258,6 @@ setColAttr(#wx_ref{type=ThisT}=This,Col,#wx_ref{type=AttrT}=Attr) ?CLASS(AttrT,wxGridCellAttr), wxe_util:queue_cmd(This,Col,Attr,?get_env(),?wxGrid_SetColAttr). -%% @doc See external documentation. -doc """ Sets the specified column to display boolean values. @@ -2447,7 +2270,6 @@ setColFormatBool(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Col,?get_env(),?wxGrid_SetColFormatBool). -%% @doc See external documentation. -doc """ Sets the specified column to display integer values. @@ -2460,7 +2282,7 @@ setColFormatNumber(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Col,?get_env(),?wxGrid_SetColFormatNumber). -%% @equiv setColFormatFloat(This,Col, []) +-doc(#{equiv => setColFormatFloat(This,Col, [])}). -spec setColFormatFloat(This, Col) -> 'ok' when This::wxGrid(), Col::integer(). @@ -2468,10 +2290,9 @@ setColFormatFloat(This,Col) when is_record(This, wx_ref),is_integer(Col) -> setColFormatFloat(This,Col, []). -%% @doc See external documentation. -doc """ -Sets the specified column to display floating point values with the given width -and precision. +Sets the specified column to display floating point values with the given width and +precision. See: `setColFormatCustom/3` """. @@ -2488,15 +2309,13 @@ setColFormatFloat(#wx_ref{type=ThisT}=This,Col, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Col, Opts,?get_env(),?wxGrid_SetColFormatFloat). -%% @doc See external documentation. -doc """ Sets the specified column to display data in a custom format. -This method provides an alternative to defining a custom grid table which would -return `typeName` from its GetTypeName() method for the cells in this column: -while it doesn't really change the type of the cells in this column, it does -associate the renderer and editor used for the cells of the specified type with -them. +This method provides an alternative to defining a custom grid table which would return `typeName` +from its GetTypeName() method for the cells in this column: while it doesn't really +change the type of the cells in this column, it does associate the renderer and editor +used for the cells of the specified type with them. See the overview_grid for more information on working with custom data types. """. @@ -2508,13 +2327,11 @@ setColFormatCustom(#wx_ref{type=ThisT}=This,Col,TypeName) TypeName_UC = unicode:characters_to_binary(TypeName), wxe_util:queue_cmd(This,Col,TypeName_UC,?get_env(),?wxGrid_SetColFormatCustom). -%% @doc See external documentation. -doc """ Sets the horizontal and vertical alignment of column label text. -Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. Vertical alignment should be one of `wxALIGN_TOP`, -`wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. +Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. +Vertical alignment should be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec setColLabelAlignment(This, Horiz, Vert) -> 'ok' when This::wxGrid(), Horiz::integer(), Vert::integer(). @@ -2523,12 +2340,11 @@ setColLabelAlignment(#wx_ref{type=ThisT}=This,Horiz,Vert) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Horiz,Vert,?get_env(),?wxGrid_SetColLabelAlignment). -%% @doc See external documentation. -doc """ Sets the height of the column labels. -If `height` equals to `wxGRID_AUTOSIZE` then height is calculated automatically -so that no label is truncated. Note that this could be slow for a large table. +If `height` equals to `wxGRID_AUTOSIZE` then height is calculated automatically so that +no label is truncated. Note that this could be slow for a large table. """. -spec setColLabelSize(This, Height) -> 'ok' when This::wxGrid(), Height::integer(). @@ -2537,13 +2353,11 @@ setColLabelSize(#wx_ref{type=ThisT}=This,Height) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Height,?get_env(),?wxGrid_SetColLabelSize). -%% @doc See external documentation. -doc """ Set the value for the given column label. -If you are using a custom grid table you must override -`wxGridTableBase::SetColLabelValue()` (not implemented in wx) for this to have -any effect. +If you are using a custom grid table you must override `wxGridTableBase::SetColLabelValue()` +(not implemented in wx) for this to have any effect. """. -spec setColLabelValue(This, Col, Value) -> 'ok' when This::wxGrid(), Col::integer(), Value::unicode:chardata(). @@ -2553,16 +2367,13 @@ setColLabelValue(#wx_ref{type=ThisT}=This,Col,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Col,Value_UC,?get_env(),?wxGrid_SetColLabelValue). -%% @doc See external documentation. -doc """ Sets the minimal `width` for the specified column `col`. -It is usually best to call this method during grid creation as calling it later -will not resize the column to the given minimal width even if it is currently -narrower than it. +It is usually best to call this method during grid creation as calling it later will not +resize the column to the given minimal width even if it is currently narrower than it. -`width` must be greater than the minimal acceptable column width as returned by -`getColMinimalAcceptableWidth/1`. +`width` must be greater than the minimal acceptable column width as returned by `getColMinimalAcceptableWidth/1`. """. -spec setColMinimalWidth(This, Col, Width) -> 'ok' when This::wxGrid(), Col::integer(), Width::integer(). @@ -2571,7 +2382,6 @@ setColMinimalWidth(#wx_ref{type=ThisT}=This,Col,Width) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Col,Width,?get_env(),?wxGrid_SetColMinimalWidth). -%% @doc See external documentation. -doc """ Sets the minimal `width` to which the user can resize columns. @@ -2584,7 +2394,6 @@ setColMinimalAcceptableWidth(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Width,?get_env(),?wxGrid_SetColMinimalAcceptableWidth). -%% @doc See external documentation. -doc "Sets the width of the specified column.". -spec setColSize(This, Col, Width) -> 'ok' when This::wxGrid(), Col::integer(), Width::integer(). @@ -2593,13 +2402,11 @@ setColSize(#wx_ref{type=ThisT}=This,Col,Width) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Col,Width,?get_env(),?wxGrid_SetColSize). -%% @doc See external documentation. -doc """ Sets the default horizontal and vertical alignment for grid cell text. -Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. Vertical alignment should be one of `wxALIGN_TOP`, -`wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. +Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. +Vertical alignment should be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec setDefaultCellAlignment(This, Horiz, Vert) -> 'ok' when This::wxGrid(), Horiz::integer(), Vert::integer(). @@ -2608,7 +2415,6 @@ setDefaultCellAlignment(#wx_ref{type=ThisT}=This,Horiz,Vert) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Horiz,Vert,?get_env(),?wxGrid_SetDefaultCellAlignment). -%% @doc See external documentation. -doc "Sets the default background colour for grid cells.". -spec setDefaultCellBackgroundColour(This, Colour) -> 'ok' when This::wxGrid(), Colour::wx:wx_colour(). @@ -2617,7 +2423,6 @@ setDefaultCellBackgroundColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxGrid_SetDefaultCellBackgroundColour). -%% @doc See external documentation. -doc "Sets the default font to be used for grid cell text.". -spec setDefaultCellFont(This, Font) -> 'ok' when This::wxGrid(), Font::wxFont:wxFont(). @@ -2626,7 +2431,6 @@ setDefaultCellFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxGrid_SetDefaultCellFont). -%% @doc See external documentation. -doc "Sets the current default colour for grid cell text.". -spec setDefaultCellTextColour(This, Colour) -> 'ok' when This::wxGrid(), Colour::wx:wx_colour(). @@ -2635,14 +2439,13 @@ setDefaultCellTextColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxGrid_SetDefaultCellTextColour). -%% @doc See external documentation. -doc """ Sets the default editor for grid cells. The grid will take ownership of the pointer. -See `m:wxGridCellEditor` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellEditor` and the overview_grid for more information about cell editors +and renderers. """. -spec setDefaultEditor(This, Editor) -> 'ok' when This::wxGrid(), Editor::wxGridCellEditor:wxGridCellEditor(). @@ -2651,14 +2454,13 @@ setDefaultEditor(#wx_ref{type=ThisT}=This,#wx_ref{type=EditorT}=Editor) -> ?CLASS(EditorT,wxGridCellEditor), wxe_util:queue_cmd(This,Editor,?get_env(),?wxGrid_SetDefaultEditor). -%% @doc See external documentation. -doc """ Sets the default renderer for grid cells. The grid will take ownership of the pointer. -See `m:wxGridCellRenderer` and the overview_grid for more information about cell -editors and renderers. +See `m:wxGridCellRenderer` and the overview_grid for more information about cell editors +and renderers. """. -spec setDefaultRenderer(This, Renderer) -> 'ok' when This::wxGrid(), Renderer::wxGridCellRenderer:wxGridCellRenderer(). @@ -2667,7 +2469,7 @@ setDefaultRenderer(#wx_ref{type=ThisT}=This,#wx_ref{type=RendererT}=Renderer) -> ?CLASS(RendererT,wxGridCellRenderer), wxe_util:queue_cmd(This,Renderer,?get_env(),?wxGrid_SetDefaultRenderer). -%% @equiv setDefaultColSize(This,Width, []) +-doc(#{equiv => setDefaultColSize(This,Width, [])}). -spec setDefaultColSize(This, Width) -> 'ok' when This::wxGrid(), Width::integer(). @@ -2675,15 +2477,13 @@ setDefaultColSize(This,Width) when is_record(This, wx_ref),is_integer(Width) -> setDefaultColSize(This,Width, []). -%% @doc See external documentation. -doc """ Sets the default width for columns in the grid. -This will only affect columns subsequently added to the grid unless -`resizeExistingCols` is true. +This will only affect columns subsequently added to the grid unless `resizeExistingCols` +is true. -If `width` is less than `getColMinimalAcceptableWidth/1`, then the minimal -acceptable width is used instead of it. +If `width` is less than `getColMinimalAcceptableWidth/1`, then the minimal acceptable width is used instead of it. """. -spec setDefaultColSize(This, Width, [Option]) -> 'ok' when This::wxGrid(), Width::integer(), @@ -2696,7 +2496,7 @@ setDefaultColSize(#wx_ref{type=ThisT}=This,Width, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Width, Opts,?get_env(),?wxGrid_SetDefaultColSize). -%% @equiv setDefaultRowSize(This,Height, []) +-doc(#{equiv => setDefaultRowSize(This,Height, [])}). -spec setDefaultRowSize(This, Height) -> 'ok' when This::wxGrid(), Height::integer(). @@ -2704,15 +2504,12 @@ setDefaultRowSize(This,Height) when is_record(This, wx_ref),is_integer(Height) -> setDefaultRowSize(This,Height, []). -%% @doc See external documentation. -doc """ Sets the default height for rows in the grid. -This will only affect rows subsequently added to the grid unless -`resizeExistingRows` is true. +This will only affect rows subsequently added to the grid unless `resizeExistingRows` is true. -If `height` is less than `getRowMinimalAcceptableHeight/1`, then the minimal -acceptable height is used instead of it. +If `height` is less than `getRowMinimalAcceptableHeight/1`, then the minimal acceptable height is used instead of it. """. -spec setDefaultRowSize(This, Height, [Option]) -> 'ok' when This::wxGrid(), Height::integer(), @@ -2725,18 +2522,17 @@ setDefaultRowSize(#wx_ref{type=ThisT}=This,Height, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Height, Opts,?get_env(),?wxGrid_SetDefaultRowSize). -%% @doc See external documentation. -doc """ Set the grid cursor to the specified cell. -The grid cursor indicates the current cell and can be moved by the user using -the arrow keys or the mouse. +The grid cursor indicates the current cell and can be moved by the user using the arrow +keys or the mouse. -Calling this function generates a `wxEVT_GRID_SELECT_CELL` event and if the -event handler vetoes this event, the cursor is not moved. +Calling this function generates a `wxEVT_GRID_SELECT_CELL` event and if the event handler +vetoes this event, the cursor is not moved. -This function doesn't make the target call visible, use `GoToCell()` (not -implemented in wx) to do this. +This function doesn't make the target call visible, use `GoToCell()` (not implemented in +wx) to do this. """. -spec setGridCursor(This, Coords) -> 'ok' when This::wxGrid(), Coords::{R::integer(), C::integer()}. @@ -2745,18 +2541,17 @@ setGridCursor(#wx_ref{type=ThisT}=This,{CoordsR,CoordsC} = Coords) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Coords,?get_env(),?wxGrid_SetGridCursor_1). -%% @doc See external documentation. -doc """ Set the grid cursor to the specified cell. -The grid cursor indicates the current cell and can be moved by the user using -the arrow keys or the mouse. +The grid cursor indicates the current cell and can be moved by the user using the arrow +keys or the mouse. -Calling this function generates a `wxEVT_GRID_SELECT_CELL` event and if the -event handler vetoes this event, the cursor is not moved. +Calling this function generates a `wxEVT_GRID_SELECT_CELL` event and if the event handler +vetoes this event, the cursor is not moved. -This function doesn't make the target call visible, use `GoToCell()` (not -implemented in wx) to do this. +This function doesn't make the target call visible, use `GoToCell()` (not implemented in +wx) to do this. """. -spec setGridCursor(This, Row, Col) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(). @@ -2765,7 +2560,6 @@ setGridCursor(#wx_ref{type=ThisT}=This,Row,Col) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGrid_SetGridCursor_2). -%% @doc See external documentation. -doc "Sets the colour used to draw grid lines.". -spec setGridLineColour(This, Colour) -> 'ok' when This::wxGrid(), Colour::wx:wx_colour(). @@ -2774,7 +2568,6 @@ setGridLineColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxGrid_SetGridLineColour). -%% @doc See external documentation. -doc "Sets the background colour for row and column labels.". -spec setLabelBackgroundColour(This, Colour) -> 'ok' when This::wxGrid(), Colour::wx:wx_colour(). @@ -2783,7 +2576,6 @@ setLabelBackgroundColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxGrid_SetLabelBackgroundColour). -%% @doc See external documentation. -doc "Sets the font for row and column labels.". -spec setLabelFont(This, Font) -> 'ok' when This::wxGrid(), Font::wxFont:wxFont(). @@ -2792,7 +2584,6 @@ setLabelFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxGrid_SetLabelFont). -%% @doc See external documentation. -doc "Sets the colour for row and column label text.". -spec setLabelTextColour(This, Colour) -> 'ok' when This::wxGrid(), Colour::wx:wx_colour(). @@ -2801,12 +2592,11 @@ setLabelTextColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxGrid_SetLabelTextColour). -%% @doc See external documentation. -doc """ Sets the extra margins used around the grid area. -A grid may occupy more space than needed for its data display and this function -allows setting how big this extra space is +A grid may occupy more space than needed for its data display and this function allows +setting how big this extra space is """. -spec setMargins(This, ExtraWidth, ExtraHeight) -> 'ok' when This::wxGrid(), ExtraWidth::integer(), ExtraHeight::integer(). @@ -2815,7 +2605,7 @@ setMargins(#wx_ref{type=ThisT}=This,ExtraWidth,ExtraHeight) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,ExtraWidth,ExtraHeight,?get_env(),?wxGrid_SetMargins). -%% @equiv setReadOnly(This,Row,Col, []) +-doc(#{equiv => setReadOnly(This,Row,Col, [])}). -spec setReadOnly(This, Row, Col) -> 'ok' when This::wxGrid(), Row::integer(), Col::integer(). @@ -2823,7 +2613,6 @@ setReadOnly(This,Row,Col) when is_record(This, wx_ref),is_integer(Row),is_integer(Col) -> setReadOnly(This,Row,Col, []). -%% @doc See external documentation. -doc """ Makes the cell at the specified location read-only or editable. @@ -2840,14 +2629,12 @@ setReadOnly(#wx_ref{type=ThisT}=This,Row,Col, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Row,Col, Opts,?get_env(),?wxGrid_SetReadOnly). -%% @doc See external documentation. -doc """ Sets the cell attributes for all cells in the specified row. The grid takes ownership of the attribute pointer. -See the `m:wxGridCellAttr` class for more information about controlling cell -attributes. +See the `m:wxGridCellAttr` class for more information about controlling cell attributes. """. -spec setRowAttr(This, Row, Attr) -> 'ok' when This::wxGrid(), Row::integer(), Attr::wxGridCellAttr:wxGridCellAttr(). @@ -2857,13 +2644,11 @@ setRowAttr(#wx_ref{type=ThisT}=This,Row,#wx_ref{type=AttrT}=Attr) ?CLASS(AttrT,wxGridCellAttr), wxe_util:queue_cmd(This,Row,Attr,?get_env(),?wxGrid_SetRowAttr). -%% @doc See external documentation. -doc """ Sets the horizontal and vertical alignment of row label text. -Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or -`wxALIGN_RIGHT`. Vertical alignment should be one of `wxALIGN_TOP`, -`wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. +Horizontal alignment should be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT`. +Vertical alignment should be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec setRowLabelAlignment(This, Horiz, Vert) -> 'ok' when This::wxGrid(), Horiz::integer(), Vert::integer(). @@ -2872,12 +2657,11 @@ setRowLabelAlignment(#wx_ref{type=ThisT}=This,Horiz,Vert) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Horiz,Vert,?get_env(),?wxGrid_SetRowLabelAlignment). -%% @doc See external documentation. -doc """ Sets the width of the row labels. -If `width` equals `wxGRID_AUTOSIZE` then width is calculated automatically so -that no label is truncated. Note that this could be slow for a large table. +If `width` equals `wxGRID_AUTOSIZE` then width is calculated automatically so that no +label is truncated. Note that this could be slow for a large table. """. -spec setRowLabelSize(This, Width) -> 'ok' when This::wxGrid(), Width::integer(). @@ -2886,13 +2670,11 @@ setRowLabelSize(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Width,?get_env(),?wxGrid_SetRowLabelSize). -%% @doc See external documentation. -doc """ Sets the value for the given row label. -If you are using a derived grid table you must override -`wxGridTableBase::SetRowLabelValue()` (not implemented in wx) for this to have -any effect. +If you are using a derived grid table you must override `wxGridTableBase::SetRowLabelValue()` +(not implemented in wx) for this to have any effect. """. -spec setRowLabelValue(This, Row, Value) -> 'ok' when This::wxGrid(), Row::integer(), Value::unicode:chardata(). @@ -2902,7 +2684,6 @@ setRowLabelValue(#wx_ref{type=ThisT}=This,Row,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Row,Value_UC,?get_env(),?wxGrid_SetRowLabelValue). -%% @doc See external documentation. -doc """ Sets the minimal `height` for the specified `row`. @@ -2915,7 +2696,6 @@ setRowMinimalHeight(#wx_ref{type=ThisT}=This,Row,Height) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Height,?get_env(),?wxGrid_SetRowMinimalHeight). -%% @doc See external documentation. -doc """ Sets the minimal row `height` used by default. @@ -2928,7 +2708,6 @@ setRowMinimalAcceptableHeight(#wx_ref{type=ThisT}=This,Height) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Height,?get_env(),?wxGrid_SetRowMinimalAcceptableHeight). -%% @doc See external documentation. -doc """ Sets the height of the specified row. @@ -2941,13 +2720,17 @@ setRowSize(#wx_ref{type=ThisT}=This,Row,Height) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Row,Height,?get_env(),?wxGrid_SetRowSize). -%% @doc See external documentation. -doc """ Sets the number of pixels per horizontal scroll increment. The default is 15. -See: `getScrollLineX/1`, `getScrollLineY/1`, `setScrollLineY/2` +See: +* `getScrollLineX/1` + +* `getScrollLineY/1` + +* `setScrollLineY/2` """. -spec setScrollLineX(This, X) -> 'ok' when This::wxGrid(), X::integer(). @@ -2956,13 +2739,17 @@ setScrollLineX(#wx_ref{type=ThisT}=This,X) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,X,?get_env(),?wxGrid_SetScrollLineX). -%% @doc See external documentation. -doc """ Sets the number of pixels per vertical scroll increment. The default is 15. -See: `getScrollLineX/1`, `getScrollLineY/1`, `setScrollLineX/2` +See: +* `getScrollLineX/1` + +* `getScrollLineY/1` + +* `setScrollLineX/2` """. -spec setScrollLineY(This, Y) -> 'ok' when This::wxGrid(), Y::integer(). @@ -2971,7 +2758,6 @@ setScrollLineY(#wx_ref{type=ThisT}=This,Y) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Y,?get_env(),?wxGrid_SetScrollLineY). -%% @doc See external documentation. -doc "Set the colour to be used for drawing the selection background.". -spec setSelectionBackground(This, C) -> 'ok' when This::wxGrid(), C::wx:wx_colour(). @@ -2980,7 +2766,6 @@ setSelectionBackground(#wx_ref{type=ThisT}=This,C) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(C),?get_env(),?wxGrid_SetSelectionBackground). -%% @doc See external documentation. -doc "Set the colour to be used for drawing the selection foreground.". -spec setSelectionForeground(This, C) -> 'ok' when This::wxGrid(), C::wx:wx_colour(). @@ -2989,15 +2774,14 @@ setSelectionForeground(#wx_ref{type=ThisT}=This,C) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,wxe_util:color(C),?get_env(),?wxGrid_SetSelectionForeground). -%% @doc See external documentation. -%%
Selmode = ?wxGrid_wxGridSelectCells | ?wxGrid_wxGridSelectRows | ?wxGrid_wxGridSelectColumns | ?wxGrid_wxGridSelectRowsOrColumns -doc """ Set the selection behaviour of the grid. -The existing selection is converted to conform to the new mode if possible and -discarded otherwise (e.g. any individual selected cells are deselected if the -new mode allows only the selection of the entire rows or columns). +The existing selection is converted to conform to the new mode if possible and discarded +otherwise (e.g. any individual selected cells are deselected if the new mode allows only +the selection of the entire rows or columns). """. +%% Selmode = ?wxGrid_wxGridSelectCells | ?wxGrid_wxGridSelectRows | ?wxGrid_wxGridSelectColumns | ?wxGrid_wxGridSelectRowsOrColumns -spec setSelectionMode(This, Selmode) -> 'ok' when This::wxGrid(), Selmode::wx:wx_enum(). setSelectionMode(#wx_ref{type=ThisT}=This,Selmode) @@ -3005,13 +2789,11 @@ setSelectionMode(#wx_ref{type=ThisT}=This,Selmode) ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,Selmode,?get_env(),?wxGrid_SetSelectionMode). -%% @doc See external documentation. -doc """ -Displays the active in-place cell edit control for the current cell after it was -hidden. +Displays the active in-place cell edit control for the current cell after it was hidden. -This method should only be called after calling `hideCellEditControl/1`, to -start editing the current grid cell use `enableCellEditControl/2` instead. +This method should only be called after calling `hideCellEditControl/1`, to start editing the current grid cell +use `enableCellEditControl/2` instead. """. -spec showCellEditControl(This) -> 'ok' when This::wxGrid(). @@ -3019,7 +2801,7 @@ showCellEditControl(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGrid), wxe_util:queue_cmd(This,?get_env(),?wxGrid_ShowCellEditControl). -%% @equiv xToCol(This,X, []) +-doc(#{equiv => xToCol(This,X, [])}). -spec xToCol(This, X) -> integer() when This::wxGrid(), X::integer(). @@ -3027,7 +2809,6 @@ xToCol(This,X) when is_record(This, wx_ref),is_integer(X) -> xToCol(This,X, []). -%% @doc See external documentation. -doc """ Returns the column at the given pixel position depending on the window. @@ -3045,10 +2826,8 @@ xToCol(#wx_ref{type=ThisT}=This,X, Options) wxe_util:queue_cmd(This,X, Opts,?get_env(),?wxGrid_XToCol), wxe_util:rec(?wxGrid_XToCol). -%% @doc See external documentation. -doc """ -Returns the column whose right hand edge is close to the given logical `x` -position. +Returns the column whose right hand edge is close to the given logical `x` position. If no column edge is near to this position `wxNOT_FOUND` is returned. """. @@ -3060,7 +2839,6 @@ xToEdgeOfCol(#wx_ref{type=ThisT}=This,X) wxe_util:queue_cmd(This,X,?get_env(),?wxGrid_XToEdgeOfCol), wxe_util:rec(?wxGrid_XToEdgeOfCol). -%% @doc See external documentation. -doc """ Returns the row whose bottom edge is close to the given logical `y` position. @@ -3074,7 +2852,7 @@ yToEdgeOfRow(#wx_ref{type=ThisT}=This,Y) wxe_util:queue_cmd(This,Y,?get_env(),?wxGrid_YToEdgeOfRow), wxe_util:rec(?wxGrid_YToEdgeOfRow). -%% @equiv yToRow(This,Y, []) +-doc(#{equiv => yToRow(This,Y, [])}). -spec yToRow(This, Y) -> integer() when This::wxGrid(), Y::integer(). @@ -3082,16 +2860,15 @@ yToRow(This,Y) when is_record(This, wx_ref),is_integer(Y) -> yToRow(This,Y, []). -%% @doc See external documentation. -doc """ Returns the grid row that corresponds to the logical `y` coordinate. -The parameter `gridWindow` is new since wxWidgets 3.1.3. If it is specified, -i.e. non-NULL, only the cells of this window are considered, i.e. the function -returns `wxNOT_FOUND` if `y` is out of bounds. +The parameter `gridWindow` is new since wxWidgets 3.1.3. If it is specified, i.e. +non-NULL, only the cells of this window are considered, i.e. the function returns `wxNOT_FOUND` +if `y` is out of bounds. -If `gridWindow` is NULL, the function returns `wxNOT_FOUND` only if there is no -row at all at the `y` position. +If `gridWindow` is NULL, the function returns `wxNOT_FOUND` only if there is no row at +all at the `y` position. """. -spec yToRow(This, Y, [Option]) -> integer() when This::wxGrid(), Y::integer(), @@ -3105,614 +2882,409 @@ yToRow(#wx_ref{type=ThisT}=This,Y, Options) wxe_util:queue_cmd(This,Y, Opts,?get_env(),?wxGrid_YToRow), wxe_util:rec(?wxGrid_YToRow). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -This will also destroy the associated grid table unless you passed a table -object to the grid and specified that the grid should not take ownership of the -table (see `SetTable()` (not implemented in wx)). -""". +-doc "Destroys the object". -spec destroy(This::wxGrid()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGrid), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxScrolledWindow -%% @hidden -doc false. setTargetWindow(This,Window) -> wxScrolledWindow:setTargetWindow(This,Window). -%% @hidden -doc false. setScrollRate(This,Xstep,Ystep) -> wxScrolledWindow:setScrollRate(This,Xstep,Ystep). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY). -%% @hidden -doc false. scroll(This,X,Y) -> wxScrolledWindow:scroll(This,X,Y). -%% @hidden -doc false. scroll(This,Pt) -> wxScrolledWindow:scroll(This,Pt). -%% @hidden -doc false. prepareDC(This,Dc) -> wxScrolledWindow:prepareDC(This,Dc). -%% @hidden -doc false. doPrepareDC(This,Dc) -> wxScrolledWindow:doPrepareDC(This,Dc). -%% @hidden -doc false. getViewStart(This) -> wxScrolledWindow:getViewStart(This). -%% @hidden -doc false. getScrollPixelsPerUnit(This) -> wxScrolledWindow:getScrollPixelsPerUnit(This). -%% @hidden -doc false. enableScrolling(This,XScrolling,YScrolling) -> wxScrolledWindow:enableScrolling(This,XScrolling,YScrolling). -%% @hidden -doc false. calcUnscrolledPosition(This,X,Y) -> wxScrolledWindow:calcUnscrolledPosition(This,X,Y). -%% @hidden -doc false. calcUnscrolledPosition(This,Pt) -> wxScrolledWindow:calcUnscrolledPosition(This,Pt). -%% @hidden -doc false. calcScrolledPosition(This,X,Y) -> wxScrolledWindow:calcScrolledPosition(This,X,Y). -%% @hidden -doc false. calcScrolledPosition(This,Pt) -> wxScrolledWindow:calcScrolledPosition(This,Pt). %% From wxPanel -%% @hidden -doc false. setFocusIgnoringChildren(This) -> wxPanel:setFocusIgnoringChildren(This). -%% @hidden -doc false. initDialog(This) -> wxPanel:initDialog(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxGridBagSizer.erl b/lib/wx/src/gen/wxGridBagSizer.erl index 114ba98de3c6..3eb0314cbcd4 100644 --- a/lib/wx/src/gen/wxGridBagSizer.erl +++ b/lib/wx/src/gen/wxGridBagSizer.erl @@ -20,18 +20,20 @@ -module(wxGridBagSizer). -moduledoc """ -Functions for wxGridBagSizer class +A `m:wxSizer` that can lay out items in a virtual grid like a `m:wxFlexGridSizer` but in +this case explicit positioning of the items is allowed using `wxGBPosition` (not +implemented in wx), and items can optionally span more than one row and/or column using `wxGBSpan` +(not implemented in wx). -A `m:wxSizer` that can lay out items in a virtual grid like a -`m:wxFlexGridSizer` but in this case explicit positioning of the items is -allowed using `wxGBPosition` (not implemented in wx), and items can optionally -span more than one row and/or column using `wxGBSpan` (not implemented in wx). +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxFlexGridSizer` -`m:wxGridSizer` `m:wxSizer` +* `m:wxFlexGridSizer` -wxWidgets docs: -[wxGridBagSizer](https://docs.wxwidgets.org/3.1/classwx_grid_bag_sizer.html) +* `m:wxGridSizer` + +* `m:wxSizer` + +wxWidgets docs: [wxGridBagSizer](https://docs.wxwidgets.org/3.2/classwx_grid_bag_sizer.html) """. -include("wxe.hrl"). -export([add/2,add/3,add/4,add/5,calcMin/1,checkForIntersection/2,checkForIntersection/3, @@ -56,24 +58,19 @@ wxWidgets docs: -type wxGridBagSizer() :: wx:wx_object(). -export_type([wxGridBagSizer/0]). -%% @hidden -doc false. parent_class(wxFlexGridSizer) -> true; parent_class(wxGridSizer) -> true; parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGridBagSizer(). new() -> new([]). -%% @doc See external documentation. --doc """ -Constructor, with optional parameters to specify the gap between the rows and -columns. -""". +-doc "Constructor, with optional parameters to specify the gap between the rows and columns.". -spec new([Option]) -> wxGridBagSizer() when Option :: {'vgap', integer()} | {'hgap', integer()}. @@ -86,7 +83,7 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGridBagSizer_new), wxe_util:rec(?wxGridBagSizer_new). -%% @doc See external documentation. +-doc "". -spec add(This, Item) -> wxSizerItem:wxSizerItem() when This::wxGridBagSizer(), Item::wxGBSizerItem:wxGBSizerItem(). add(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> @@ -95,7 +92,7 @@ add(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(This,Item,?get_env(),?wxGridBagSizer_Add_1), wxe_util:rec(?wxGridBagSizer_Add_1). -%% @equiv add(This,Window,Pos, []) +-doc(#{equiv => add(This,Window,Pos, [])}). -spec add(This, Window, Pos) -> wxSizerItem:wxSizerItem() when This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Pos::{R::integer(), C::integer()}. @@ -103,20 +100,11 @@ add(This,Window,{PosR,PosC} = Pos) when is_record(This, wx_ref),is_record(Window, wx_ref),is_integer(PosR),is_integer(PosC) -> add(This,Window,Pos, []). -%% @doc See external documentation. -%%
Also:
-%% add(This, Window, Pos, [Option]) -> wxSizerItem:wxSizerItem() when
-%% This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Pos::{R::integer(), C::integer()},
-%% Option :: {'span', {RS::integer(), CS::integer()}}
-%% | {'flag', integer()}
-%% | {'border', integer()}
-%% | {'userData', wx:wx_object()}.
-%% -doc """ Adds the given item to the given position. -Return: A valid pointer if the item was successfully placed at the given -position, or NULL if something was already there. +Return: A valid pointer if the item was successfully placed at the given position, or +NULL if something was already there. """. -spec add(This, Width, Height, Pos) -> wxSizerItem:wxSizerItem() when This::wxGridBagSizer(), Width::integer(), Height::integer(), Pos::{R::integer(), C::integer()}; @@ -149,14 +137,13 @@ add(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window,{PosR,PosC} = Pos, Opt wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType),Pos, Opts,?get_env(),?wxGridBagSizer_Add_3), wxe_util:rec(?wxGridBagSizer_Add_3). -%% @doc See external documentation. -doc """ Adds a spacer to the given position. `width` and `height` specify the dimension of the spacer to be added. -Return: A valid pointer if the spacer was successfully placed at the given -position, or NULL if something was already there. +Return: A valid pointer if the spacer was successfully placed at the given position, or +NULL if something was already there. """. -spec add(This, Width, Height, Pos, [Option]) -> wxSizerItem:wxSizerItem() when This::wxGridBagSizer(), Width::integer(), Height::integer(), Pos::{R::integer(), C::integer()}, @@ -176,7 +163,6 @@ add(#wx_ref{type=ThisT}=This,Width,Height,{PosR,PosC} = Pos, Options) wxe_util:queue_cmd(This,Width,Height,Pos, Opts,?get_env(),?wxGridBagSizer_Add_4), wxe_util:rec(?wxGridBagSizer_Add_4). -%% @doc See external documentation. -doc "Called when the managed size of the sizer is needed or when layout needs done.". -spec calcMin(This) -> {W::integer(), H::integer()} when This::wxGridBagSizer(). @@ -185,7 +171,7 @@ calcMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridBagSizer_CalcMin), wxe_util:rec(?wxGridBagSizer_CalcMin). -%% @equiv checkForIntersection(This,Item, []) +-doc(#{equiv => checkForIntersection(This,Item, [])}). -spec checkForIntersection(This, Item) -> boolean() when This::wxGridBagSizer(), Item::wxGBSizerItem:wxGBSizerItem(). @@ -193,18 +179,12 @@ checkForIntersection(This,Item) when is_record(This, wx_ref),is_record(Item, wx_ref) -> checkForIntersection(This,Item, []). -%% @doc See external documentation. -%%
Also:
-%% checkForIntersection(This, Item, [Option]) -> boolean() when
-%% This::wxGridBagSizer(), Item::wxGBSizerItem:wxGBSizerItem(),
-%% Option :: {'excludeItem', wxGBSizerItem:wxGBSizerItem()}.
-%% -doc """ Look at all items and see if any intersect (or would overlap) the given item. -Returns true if so, false if there would be no overlap. If an `excludeItem` is -given then it will not be checked for intersection, for example it may be the -item we are checking the position of. +Returns true if so, false if there would be no overlap. If an `excludeItem` is given then +it will not be checked for intersection, for example it may be the item we are checking +the position of. """. -spec checkForIntersection(This, Pos, Span) -> boolean() when This::wxGridBagSizer(), Pos::{R::integer(), C::integer()}, Span::{RS::integer(), CS::integer()}; @@ -225,7 +205,7 @@ checkForIntersection(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxGridBagSizer_CheckForIntersection_2), wxe_util:rec(?wxGridBagSizer_CheckForIntersection_2). -%% @doc See external documentation. +-doc "". -spec checkForIntersection(This, Pos, Span, [Option]) -> boolean() when This::wxGridBagSizer(), Pos::{R::integer(), C::integer()}, Span::{RS::integer(), CS::integer()}, Option :: {'excludeItem', wxGBSizerItem:wxGBSizerItem()}. @@ -238,7 +218,6 @@ checkForIntersection(#wx_ref{type=ThisT}=This,{PosR,PosC} = Pos,{SpanRS,SpanCS} wxe_util:queue_cmd(This,Pos,Span, Opts,?get_env(),?wxGridBagSizer_CheckForIntersection_3), wxe_util:rec(?wxGridBagSizer_CheckForIntersection_3). -%% @doc See external documentation. -doc """ Find the sizer item for the given window or subsizer, returns NULL if not found. @@ -258,13 +237,12 @@ findItem(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType),?get_env(),?wxGridBagSizer_FindItem), wxe_util:rec(?wxGridBagSizer_FindItem). -%% @doc See external documentation. -doc """ -Return the sizer item located at the point given in pt, or NULL if there is no -item at that point. +Return the sizer item located at the point given in pt, or NULL if there is no item at +that point. -The (x,y) coordinates in `pt` correspond to the client coordinates of the window -using the sizer for layout. (non-recursive) +The (x,y) coordinates in `pt` correspond to the client coordinates of the window using +the sizer for layout. (non-recursive) """. -spec findItemAtPoint(This, Pt) -> wxGBSizerItem:wxGBSizerItem() when This::wxGridBagSizer(), Pt::{X::integer(), Y::integer()}. @@ -274,10 +252,9 @@ findItemAtPoint(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxGridBagSizer_FindItemAtPoint), wxe_util:rec(?wxGridBagSizer_FindItemAtPoint). -%% @doc See external documentation. -doc """ -Return the sizer item for the given grid cell, or NULL if there is no item at -that position. +Return the sizer item for the given grid cell, or NULL if there is no item at that +position. (non-recursive) """. @@ -289,10 +266,9 @@ findItemAtPosition(#wx_ref{type=ThisT}=This,{PosR,PosC} = Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxGridBagSizer_FindItemAtPosition), wxe_util:rec(?wxGridBagSizer_FindItemAtPosition). -%% @doc See external documentation. -doc """ -Return the sizer item that has a matching user data (it only compares pointer -values) or NULL if not found. +Return the sizer item that has a matching user data (it only compares pointer values) or +NULL if not found. (non-recursive) """. @@ -304,7 +280,6 @@ findItemWithData(#wx_ref{type=ThisT}=This,#wx_ref{type=UserDataT}=UserData) -> wxe_util:queue_cmd(This,UserData,?get_env(),?wxGridBagSizer_FindItemWithData), wxe_util:rec(?wxGridBagSizer_FindItemWithData). -%% @doc See external documentation. -doc """ Get the size of the specified cell, including hgap and vgap. @@ -318,7 +293,6 @@ getCellSize(#wx_ref{type=ThisT}=This,Row,Col) wxe_util:queue_cmd(This,Row,Col,?get_env(),?wxGridBagSizer_GetCellSize), wxe_util:rec(?wxGridBagSizer_GetCellSize). -%% @doc See external documentation. -doc "Get the size used for cells in the grid with no item.". -spec getEmptyCellSize(This) -> {W::integer(), H::integer()} when This::wxGridBagSizer(). @@ -327,11 +301,7 @@ getEmptyCellSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridBagSizer_GetEmptyCellSize), wxe_util:rec(?wxGridBagSizer_GetEmptyCellSize). -%% @doc See external documentation. -%%
Also:
-%% getItemPosition(This, Index) -> {R::integer(), C::integer()} when
-%% This::wxGridBagSizer(), Index::integer().
-%% +-doc "". -spec getItemPosition(This, Window) -> {R::integer(), C::integer()} when This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); (This, Index) -> {R::integer(), C::integer()} when @@ -353,11 +323,7 @@ getItemPosition(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxGridBagSizer_GetItemPosition_1_1), wxe_util:rec(?wxGridBagSizer_GetItemPosition_1_1). -%% @doc See external documentation. -%%
Also:
-%% getItemSpan(This, Index) -> {RS::integer(), CS::integer()} when
-%% This::wxGridBagSizer(), Index::integer().
-%% +-doc "". -spec getItemSpan(This, Window) -> {RS::integer(), CS::integer()} when This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); (This, Index) -> {RS::integer(), CS::integer()} when @@ -379,7 +345,6 @@ getItemSpan(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxGridBagSizer_GetItemSpan_1_1), wxe_util:rec(?wxGridBagSizer_GetItemSpan_1_1). -%% @doc See external documentation. -doc "Set the size used for cells in the grid with no item.". -spec setEmptyCellSize(This, Sz) -> 'ok' when This::wxGridBagSizer(), Sz::{W::integer(), H::integer()}. @@ -388,11 +353,7 @@ setEmptyCellSize(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz) ?CLASS(ThisT,wxGridBagSizer), wxe_util:queue_cmd(This,Sz,?get_env(),?wxGridBagSizer_SetEmptyCellSize). -%% @doc See external documentation. -%%
Also:
-%% setItemPosition(This, Index, Pos) -> boolean() when
-%% This::wxGridBagSizer(), Index::integer(), Pos::{R::integer(), C::integer()}.
-%% +-doc "". -spec setItemPosition(This, Window, Pos) -> boolean() when This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Pos::{R::integer(), C::integer()}; (This, Index, Pos) -> boolean() when @@ -415,11 +376,7 @@ setItemPosition(#wx_ref{type=ThisT}=This,Index,{PosR,PosC} = Pos) wxe_util:queue_cmd(This,Index,Pos,?get_env(),?wxGridBagSizer_SetItemPosition_2_1), wxe_util:rec(?wxGridBagSizer_SetItemPosition_2_1). -%% @doc See external documentation. -%%
Also:
-%% setItemSpan(This, Index, Span) -> boolean() when
-%% This::wxGridBagSizer(), Index::integer(), Span::{RS::integer(), CS::integer()}.
-%% +-doc "". -spec setItemSpan(This, Window, Span) -> boolean() when This::wxGridBagSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Span::{RS::integer(), CS::integer()}; (This, Index, Span) -> boolean() when @@ -442,202 +399,138 @@ setItemSpan(#wx_ref{type=ThisT}=This,Index,{SpanRS,SpanCS} = Span) wxe_util:queue_cmd(This,Index,Span,?get_env(),?wxGridBagSizer_SetItemSpan_2_1), wxe_util:rec(?wxGridBagSizer_SetItemSpan_2_1). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridBagSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridBagSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFlexGridSizer -%% @hidden -doc false. setNonFlexibleGrowMode(This,Mode) -> wxFlexGridSizer:setNonFlexibleGrowMode(This,Mode). -%% @hidden -doc false. setFlexibleDirection(This,Direction) -> wxFlexGridSizer:setFlexibleDirection(This,Direction). -%% @hidden -doc false. removeGrowableRow(This,Idx) -> wxFlexGridSizer:removeGrowableRow(This,Idx). -%% @hidden -doc false. removeGrowableCol(This,Idx) -> wxFlexGridSizer:removeGrowableCol(This,Idx). -%% @hidden -doc false. getNonFlexibleGrowMode(This) -> wxFlexGridSizer:getNonFlexibleGrowMode(This). -%% @hidden -doc false. getFlexibleDirection(This) -> wxFlexGridSizer:getFlexibleDirection(This). -%% @hidden -doc false. addGrowableRow(This,Idx, Options) -> wxFlexGridSizer:addGrowableRow(This,Idx, Options). -%% @hidden -doc false. addGrowableRow(This,Idx) -> wxFlexGridSizer:addGrowableRow(This,Idx). -%% @hidden -doc false. addGrowableCol(This,Idx, Options) -> wxFlexGridSizer:addGrowableCol(This,Idx, Options). -%% @hidden -doc false. addGrowableCol(This,Idx) -> wxFlexGridSizer:addGrowableCol(This,Idx). %% From wxGridSizer -%% @hidden -doc false. setVGap(This,Gap) -> wxGridSizer:setVGap(This,Gap). -%% @hidden -doc false. setRows(This,Rows) -> wxGridSizer:setRows(This,Rows). -%% @hidden -doc false. setHGap(This,Gap) -> wxGridSizer:setHGap(This,Gap). -%% @hidden -doc false. setCols(This,Cols) -> wxGridSizer:setCols(This,Cols). -%% @hidden -doc false. getVGap(This) -> wxGridSizer:getVGap(This). -%% @hidden -doc false. getRows(This) -> wxGridSizer:getRows(This). -%% @hidden -doc false. getHGap(This) -> wxGridSizer:getHGap(This). -%% @hidden -doc false. getCols(This) -> wxGridSizer:getCols(This). %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). diff --git a/lib/wx/src/gen/wxGridCellAttr.erl b/lib/wx/src/gen/wxGridCellAttr.erl index f1b37ae262d1..17690908aee7 100644 --- a/lib/wx/src/gen/wxGridCellAttr.erl +++ b/lib/wx/src/gen/wxGridCellAttr.erl @@ -20,18 +20,16 @@ -module(wxGridCellAttr). -moduledoc """ -Functions for wxGridCellAttr class +This class can be used to alter the cells' appearance in the grid by changing their +attributes from the defaults. -This class can be used to alter the cells' appearance in the grid by changing -their attributes from the defaults. An object of this class may be returned by -`wxGridTableBase::GetAttr()` (not implemented in wx). +An object of this class may be returned by `wxGridTableBase::GetAttr()` (not implemented +in wx). -Note that objects of this class are reference-counted and it's recommended to -use wxGridCellAttrPtr smart pointer class when working with them to avoid memory -leaks. +Note that objects of this class are reference-counted and it's recommended to use +wxGridCellAttrPtr smart pointer class when working with them to avoid memory leaks. -wxWidgets docs: -[wxGridCellAttr](https://docs.wxwidgets.org/3.1/classwx_grid_cell_attr.html) +wxWidgets docs: [wxGridCellAttr](https://docs.wxwidgets.org/3.2/classwx_grid_cell_attr.html) """. -include("wxe.hrl"). -export([getAlignment/1,getBackgroundColour/1,getEditor/4,getFont/1,getRenderer/4, @@ -45,11 +43,9 @@ wxWidgets docs: -type wxGridCellAttr() :: wx:wx_object(). -export_type([wxGridCellAttr/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Sets the text colour.". -spec setTextColour(This, ColText) -> 'ok' when This::wxGridCellAttr(), ColText::wx:wx_colour(). @@ -58,7 +54,6 @@ setTextColour(#wx_ref{type=ThisT}=This,ColText) ?CLASS(ThisT,wxGridCellAttr), wxe_util:queue_cmd(This,wxe_util:color(ColText),?get_env(),?wxGridCellAttr_SetTextColour). -%% @doc See external documentation. -doc "Sets the background colour.". -spec setBackgroundColour(This, ColBack) -> 'ok' when This::wxGridCellAttr(), ColBack::wx:wx_colour(). @@ -67,7 +62,6 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) ?CLASS(ThisT,wxGridCellAttr), wxe_util:queue_cmd(This,wxe_util:color(ColBack),?get_env(),?wxGridCellAttr_SetBackgroundColour). -%% @doc See external documentation. -doc "Sets the font.". -spec setFont(This, Font) -> 'ok' when This::wxGridCellAttr(), Font::wxFont:wxFont(). @@ -76,12 +70,11 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxGridCellAttr_SetFont). -%% @doc See external documentation. -doc """ Sets the alignment. -`hAlign` can be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT` and -`vAlign` can be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. +`hAlign` can be one of `wxALIGN_LEFT`, `wxALIGN_CENTRE` or `wxALIGN_RIGHT` and `vAlign` +can be one of `wxALIGN_TOP`, `wxALIGN_CENTRE` or `wxALIGN_BOTTOM`. """. -spec setAlignment(This, HAlign, VAlign) -> 'ok' when This::wxGridCellAttr(), HAlign::integer(), VAlign::integer(). @@ -90,7 +83,7 @@ setAlignment(#wx_ref{type=ThisT}=This,HAlign,VAlign) ?CLASS(ThisT,wxGridCellAttr), wxe_util:queue_cmd(This,HAlign,VAlign,?get_env(),?wxGridCellAttr_SetAlignment). -%% @equiv setReadOnly(This, []) +-doc(#{equiv => setReadOnly(This, [])}). -spec setReadOnly(This) -> 'ok' when This::wxGridCellAttr(). @@ -98,7 +91,6 @@ setReadOnly(This) when is_record(This, wx_ref) -> setReadOnly(This, []). -%% @doc See external documentation. -doc "Sets the cell as read-only.". -spec setReadOnly(This, [Option]) -> 'ok' when This::wxGridCellAttr(), @@ -111,7 +103,6 @@ setReadOnly(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxGridCellAttr_SetReadOnly). -%% @doc See external documentation. -doc """ Sets the renderer to be used for cells with this attribute. @@ -124,7 +115,6 @@ setRenderer(#wx_ref{type=ThisT}=This,#wx_ref{type=RendererT}=Renderer) -> ?CLASS(RendererT,wxGridCellRenderer), wxe_util:queue_cmd(This,Renderer,?get_env(),?wxGridCellAttr_SetRenderer). -%% @doc See external documentation. -doc "Sets the editor to be used with the cells with this attribute.". -spec setEditor(This, Editor) -> 'ok' when This::wxGridCellAttr(), Editor::wxGridCellEditor:wxGridCellEditor(). @@ -133,7 +123,6 @@ setEditor(#wx_ref{type=ThisT}=This,#wx_ref{type=EditorT}=Editor) -> ?CLASS(EditorT,wxGridCellEditor), wxe_util:queue_cmd(This,Editor,?get_env(),?wxGridCellAttr_SetEditor). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid text colour set.". -spec hasTextColour(This) -> boolean() when This::wxGridCellAttr(). @@ -142,7 +131,6 @@ hasTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasTextColour), wxe_util:rec(?wxGridCellAttr_HasTextColour). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid background colour set.". -spec hasBackgroundColour(This) -> boolean() when This::wxGridCellAttr(). @@ -151,7 +139,6 @@ hasBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasBackgroundColour), wxe_util:rec(?wxGridCellAttr_HasBackgroundColour). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid font set.". -spec hasFont(This) -> boolean() when This::wxGridCellAttr(). @@ -160,7 +147,6 @@ hasFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasFont), wxe_util:rec(?wxGridCellAttr_HasFont). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid alignment set.". -spec hasAlignment(This) -> boolean() when This::wxGridCellAttr(). @@ -169,7 +155,6 @@ hasAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasAlignment), wxe_util:rec(?wxGridCellAttr_HasAlignment). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid cell renderer set.". -spec hasRenderer(This) -> boolean() when This::wxGridCellAttr(). @@ -178,7 +163,6 @@ hasRenderer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasRenderer), wxe_util:rec(?wxGridCellAttr_HasRenderer). -%% @doc See external documentation. -doc "Returns true if this attribute has a valid cell editor set.". -spec hasEditor(This) -> boolean() when This::wxGridCellAttr(). @@ -187,7 +171,6 @@ hasEditor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_HasEditor), wxe_util:rec(?wxGridCellAttr_HasEditor). -%% @doc See external documentation. -doc "Returns the text colour.". -spec getTextColour(This) -> wx:wx_colour4() when This::wxGridCellAttr(). @@ -196,7 +179,6 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_GetTextColour), wxe_util:rec(?wxGridCellAttr_GetTextColour). -%% @doc See external documentation. -doc "Returns the background colour.". -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxGridCellAttr(). @@ -205,7 +187,6 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_GetBackgroundColour), wxe_util:rec(?wxGridCellAttr_GetBackgroundColour). -%% @doc See external documentation. -doc "Returns the font.". -spec getFont(This) -> wxFont:wxFont() when This::wxGridCellAttr(). @@ -214,17 +195,14 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_GetFont), wxe_util:rec(?wxGridCellAttr_GetFont). -%% @doc See external documentation. -doc """ Get the alignment to use for the cell with the given attribute. -If this attribute doesn't specify any alignment, the default attribute alignment -is used (which can be changed using `wxGrid:setDefaultCellAlignment/3` but is -left and top by default). +If this attribute doesn't specify any alignment, the default attribute alignment is used +(which can be changed using `wxGrid:setDefaultCellAlignment/3` but is left and top by default). -Notice that `hAlign` and `vAlign` values are always overwritten by this -function, use `GetNonDefaultAlignment()` (not implemented in wx) if this is not -desirable. +Notice that `hAlign` and `vAlign` values are always overwritten by this function, use `GetNonDefaultAlignment()` +(not implemented in wx) if this is not desirable. """. -spec getAlignment(This) -> {HAlign::integer(), VAlign::integer()} when This::wxGridCellAttr(). @@ -233,13 +211,11 @@ getAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_GetAlignment), wxe_util:rec(?wxGridCellAttr_GetAlignment). -%% @doc See external documentation. -doc """ Returns the cell renderer. -The caller is responsible for calling `DecRef()` (not implemented in wx) on the -returned pointer, use `GetRendererPtr()` (not implemented in wx) to do it -automatically. +The caller is responsible for calling `DecRef()` (not implemented in wx) on the returned +pointer, use `GetRendererPtr()` (not implemented in wx) to do it automatically. """. -spec getRenderer(This, Grid, Row, Col) -> wxGridCellRenderer:wxGridCellRenderer() when This::wxGridCellAttr(), Grid::wxGrid:wxGrid(), Row::integer(), Col::integer(). @@ -250,13 +226,11 @@ getRenderer(#wx_ref{type=ThisT}=This,#wx_ref{type=GridT}=Grid,Row,Col) wxe_util:queue_cmd(This,Grid,Row,Col,?get_env(),?wxGridCellAttr_GetRenderer), wxe_util:rec(?wxGridCellAttr_GetRenderer). -%% @doc See external documentation. -doc """ Returns the cell editor. -The caller is responsible for calling `DecRef()` (not implemented in wx) on the -returned pointer, use `GetEditorPtr()` (not implemented in wx) to do it -automatically. +The caller is responsible for calling `DecRef()` (not implemented in wx) on the returned +pointer, use `GetEditorPtr()` (not implemented in wx) to do it automatically. """. -spec getEditor(This, Grid, Row, Col) -> wxGridCellEditor:wxGridCellEditor() when This::wxGridCellAttr(), Grid::wxGrid:wxGrid(), Row::integer(), Col::integer(). @@ -267,7 +241,6 @@ getEditor(#wx_ref{type=ThisT}=This,#wx_ref{type=GridT}=Grid,Row,Col) wxe_util:queue_cmd(This,Grid,Row,Col,?get_env(),?wxGridCellAttr_GetEditor), wxe_util:rec(?wxGridCellAttr_GetEditor). -%% @doc See external documentation. -doc "Returns true if this cell is set as read-only.". -spec isReadOnly(This) -> boolean() when This::wxGridCellAttr(). @@ -276,7 +249,7 @@ isReadOnly(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellAttr_IsReadOnly), wxe_util:rec(?wxGridCellAttr_IsReadOnly). -%% @doc See external documentation. +-doc "". -spec setDefAttr(This, DefAttr) -> 'ok' when This::wxGridCellAttr(), DefAttr::wxGridCellAttr(). setDefAttr(#wx_ref{type=ThisT}=This,#wx_ref{type=DefAttrT}=DefAttr) -> diff --git a/lib/wx/src/gen/wxGridCellBoolEditor.erl b/lib/wx/src/gen/wxGridCellBoolEditor.erl index 2d7fa3a82d92..9024a6868e78 100644 --- a/lib/wx/src/gen/wxGridCellBoolEditor.erl +++ b/lib/wx/src/gen/wxGridCellBoolEditor.erl @@ -20,19 +20,24 @@ -module(wxGridCellBoolEditor). -moduledoc """ -Functions for wxGridCellBoolEditor class - Grid cell editor for boolean data. -See: `m:wxGridCellEditor`, `wxGridCellAutoWrapStringEditor` (not implemented in -wx), `m:wxGridCellChoiceEditor`, `wxGridCellEnumEditor` (not implemented in wx), -`m:wxGridCellFloatEditor`, `m:wxGridCellNumberEditor`, `m:wxGridCellTextEditor`, -`wxGridCellDateEditor` (not implemented in wx) +See: +* `m:wxGridCellEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellFloatEditor` + +* `m:wxGridCellNumberEditor` + +* `m:wxGridCellTextEditor` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxGridCellEditor` +* `m:wxGridCellEditor` -wxWidgets docs: -[wxGridCellBoolEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_bool_editor.html) +wxWidgets docs: [wxGridCellBoolEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_bool_editor.html) """. -include("wxe.hrl"). -export([destroy/1,isTrueValue/1,new/0,useStringValues/0,useStringValues/1]). @@ -43,22 +48,19 @@ wxWidgets docs: -type wxGridCellBoolEditor() :: wx:wx_object(). -export_type([wxGridCellBoolEditor/0]). -%% @hidden -doc false. parent_class(wxGridCellEditor) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxGridCellBoolEditor(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGridCellBoolEditor_new), wxe_util:rec(?wxGridCellBoolEditor_new). -%% @doc See external documentation. -doc """ -Returns true if the given `value` is equal to the string representation of the -truth value we currently use (see `useStringValues/1`). +Returns true if the given `value` is equal to the string representation of the truth +value we currently use (see `useStringValues/1`). """. -spec isTrueValue(Value) -> boolean() when Value::unicode:chardata(). @@ -68,19 +70,18 @@ isTrueValue(Value) wxe_util:queue_cmd(Value_UC,?get_env(),?wxGridCellBoolEditor_IsTrueValue), wxe_util:rec(?wxGridCellBoolEditor_IsTrueValue). -%% @equiv useStringValues([]) +-doc(#{equiv => useStringValues([])}). -spec useStringValues() -> 'ok'. useStringValues() -> useStringValues([]). -%% @doc See external documentation. -doc """ -This method allows you to customize the values returned by -`wxGridCellNumberEditor:getValue/1` for the cell using this editor. +This method allows you to customize the values returned by `wxGridCellNumberEditor:getValue/1` +for the cell using this editor. -By default, the default values of the arguments are used, i.e. `"1"` is returned -if the cell is checked and an empty string otherwise. +By default, the default values of the arguments are used, i.e. `"1"` is returned if the +cell is checked and an empty string otherwise. """. -spec useStringValues([Option]) -> 'ok' when Option :: {'valueTrue', unicode:chardata()} @@ -93,35 +94,26 @@ useStringValues(Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(Opts,?get_env(),?wxGridCellBoolEditor_UseStringValues). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellBoolEditor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellBoolEditor), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellBoolEditor_destroy), ok. %% From wxGridCellEditor -%% @hidden -doc false. handleReturn(This,Event) -> wxGridCellEditor:handleReturn(This,Event). -%% @hidden -doc false. startingClick(This) -> wxGridCellEditor:startingClick(This). -%% @hidden -doc false. startingKey(This,Event) -> wxGridCellEditor:startingKey(This,Event). -%% @hidden -doc false. reset(This) -> wxGridCellEditor:reset(This). -%% @hidden -doc false. show(This,Show, Options) -> wxGridCellEditor:show(This,Show, Options). -%% @hidden -doc false. show(This,Show) -> wxGridCellEditor:show(This,Show). -%% @hidden -doc false. setSize(This,Rect) -> wxGridCellEditor:setSize(This,Rect). -%% @hidden -doc false. isCreated(This) -> wxGridCellEditor:isCreated(This). diff --git a/lib/wx/src/gen/wxGridCellBoolRenderer.erl b/lib/wx/src/gen/wxGridCellBoolRenderer.erl index 04ea977673f7..df93684c61de 100644 --- a/lib/wx/src/gen/wxGridCellBoolRenderer.erl +++ b/lib/wx/src/gen/wxGridCellBoolRenderer.erl @@ -20,19 +20,22 @@ -module(wxGridCellBoolRenderer). -moduledoc """ -Functions for wxGridCellBoolRenderer class - This class may be used to format boolean data in a cell. -See: `m:wxGridCellRenderer`, `wxGridCellAutoWrapStringRenderer` (not implemented -in wx), `wxGridCellDateTimeRenderer` (not implemented in wx), -`wxGridCellEnumRenderer` (not implemented in wx), `m:wxGridCellFloatRenderer`, -`m:wxGridCellNumberRenderer`, `m:wxGridCellStringRenderer` +See: +* `m:wxGridCellRenderer` + +* `m:wxGridCellFloatRenderer` + +* `m:wxGridCellNumberRenderer` + +* `m:wxGridCellStringRenderer` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxGridCellRenderer` +* `m:wxGridCellRenderer` -wxWidgets docs: -[wxGridCellBoolRenderer](https://docs.wxwidgets.org/3.1/classwx_grid_cell_bool_renderer.html) +wxWidgets docs: [wxGridCellBoolRenderer](https://docs.wxwidgets.org/3.2/classwx_grid_cell_bool_renderer.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -42,28 +45,24 @@ wxWidgets docs: -type wxGridCellBoolRenderer() :: wx:wx_object(). -export_type([wxGridCellBoolRenderer/0]). -%% @hidden -doc false. parent_class(wxGridCellRenderer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxGridCellBoolRenderer(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGridCellBoolRenderer_new), wxe_util:rec(?wxGridCellBoolRenderer_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellBoolRenderer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellBoolRenderer), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellBoolRenderer_destroy), ok. %% From wxGridCellRenderer -%% @hidden -doc false. getBestSize(This,Grid,Attr,Dc,Row,Col) -> wxGridCellRenderer:getBestSize(This,Grid,Attr,Dc,Row,Col). -%% @hidden -doc false. draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected) -> wxGridCellRenderer:draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected). diff --git a/lib/wx/src/gen/wxGridCellChoiceEditor.erl b/lib/wx/src/gen/wxGridCellChoiceEditor.erl index c67e0a1a2742..a5f4197185a5 100644 --- a/lib/wx/src/gen/wxGridCellChoiceEditor.erl +++ b/lib/wx/src/gen/wxGridCellChoiceEditor.erl @@ -20,20 +20,24 @@ -module(wxGridCellChoiceEditor). -moduledoc """ -Functions for wxGridCellChoiceEditor class +Grid cell editor for string data providing the user a choice from a list of strings. -Grid cell editor for string data providing the user a choice from a list of -strings. +See: +* `m:wxGridCellEditor` -See: `m:wxGridCellEditor`, `wxGridCellAutoWrapStringEditor` (not implemented in -wx), `m:wxGridCellBoolEditor`, `wxGridCellEnumEditor` (not implemented in wx), -`m:wxGridCellFloatEditor`, `m:wxGridCellNumberEditor`, `m:wxGridCellTextEditor`, -`wxGridCellDateEditor` (not implemented in wx) +* `m:wxGridCellBoolEditor` -This class is derived (and can use functions) from: `m:wxGridCellEditor` +* `m:wxGridCellFloatEditor` -wxWidgets docs: -[wxGridCellChoiceEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_choice_editor.html) +* `m:wxGridCellNumberEditor` + +* `m:wxGridCellTextEditor` + +This class is derived, and can use functions, from: + +* `m:wxGridCellEditor` + +wxWidgets docs: [wxGridCellChoiceEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_choice_editor.html) """. -include("wxe.hrl"). -export([destroy/1,new/1,new/2,setParameters/2]). @@ -44,12 +48,11 @@ wxWidgets docs: -type wxGridCellChoiceEditor() :: wx:wx_object(). -export_type([wxGridCellChoiceEditor/0]). -%% @hidden -doc false. parent_class(wxGridCellEditor) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Choices, []) +-doc(#{equiv => new(Choices, [])}). -spec new(Choices) -> wxGridCellChoiceEditor() when Choices::[unicode:chardata()]. @@ -57,7 +60,6 @@ new(Choices) when is_list(Choices) -> new(Choices, []). -%% @doc See external documentation. -doc "Choice cell renderer ctor.". -spec new(Choices, [Option]) -> wxGridCellChoiceEditor() when Choices::[unicode:chardata()], @@ -72,13 +74,11 @@ new(Choices, Options) wxe_util:queue_cmd(Choices_UCA, Opts,?get_env(),?wxGridCellChoiceEditor_new), wxe_util:rec(?wxGridCellChoiceEditor_new). -%% @doc See external documentation. -doc """ -Parameters string format is "item1\[,item2[...,itemN]]". +Parameters string format is "item1[,item2[...,itemN]]". -This method can be called before the editor is used for the first time, or -later, in which case it replaces the previously specified strings with the new -ones. +This method can be called before the editor is used for the first time, or later, in +which case it replaces the previously specified strings with the new ones. """. -spec setParameters(This, Params) -> 'ok' when This::wxGridCellChoiceEditor(), Params::unicode:chardata(). @@ -88,35 +88,26 @@ setParameters(#wx_ref{type=ThisT}=This,Params) Params_UC = unicode:characters_to_binary(Params), wxe_util:queue_cmd(This,Params_UC,?get_env(),?wxGridCellChoiceEditor_SetParameters). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellChoiceEditor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellChoiceEditor), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellChoiceEditor_destroy), ok. %% From wxGridCellEditor -%% @hidden -doc false. handleReturn(This,Event) -> wxGridCellEditor:handleReturn(This,Event). -%% @hidden -doc false. startingClick(This) -> wxGridCellEditor:startingClick(This). -%% @hidden -doc false. startingKey(This,Event) -> wxGridCellEditor:startingKey(This,Event). -%% @hidden -doc false. reset(This) -> wxGridCellEditor:reset(This). -%% @hidden -doc false. show(This,Show, Options) -> wxGridCellEditor:show(This,Show, Options). -%% @hidden -doc false. show(This,Show) -> wxGridCellEditor:show(This,Show). -%% @hidden -doc false. setSize(This,Rect) -> wxGridCellEditor:setSize(This,Rect). -%% @hidden -doc false. isCreated(This) -> wxGridCellEditor:isCreated(This). diff --git a/lib/wx/src/gen/wxGridCellEditor.erl b/lib/wx/src/gen/wxGridCellEditor.erl index dc39aa9391f0..87e2c7da6b3a 100644 --- a/lib/wx/src/gen/wxGridCellEditor.erl +++ b/lib/wx/src/gen/wxGridCellEditor.erl @@ -20,29 +20,33 @@ -module(wxGridCellEditor). -moduledoc """ -Functions for wxGridCellEditor class - -This class is responsible for providing and manipulating the in-place edit -controls for the grid. Instances of `m:wxGridCellEditor` (actually, instances of -derived classes since it is an abstract class) can be associated with the cell -attributes for individual cells, rows, columns, or even for the entire grid. - -Normally `m:wxGridCellEditor` shows some UI control allowing the user to edit -the cell, but starting with wxWidgets 3.1.4 it's also possible to define -"activatable" cell editors, that change the value of the cell directly when it's -activated (typically by pressing Space key or clicking on it), see -`TryActivate()` (not implemented in wx) method. Note that when implementing an -editor which is always activatable, i.e. never shows any in-place editor, it is -more convenient to derive its class from `wxGridCellActivatableEditor` (not -implemented in wx) than from `m:wxGridCellEditor` itself. - -See: `wxGridCellAutoWrapStringEditor` (not implemented in wx), -`m:wxGridCellBoolEditor`, `m:wxGridCellChoiceEditor`, `wxGridCellEnumEditor` -(not implemented in wx), `m:wxGridCellFloatEditor`, `m:wxGridCellNumberEditor`, -`m:wxGridCellTextEditor`, `wxGridCellDateEditor` (not implemented in wx) - -wxWidgets docs: -[wxGridCellEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_editor.html) +This class is responsible for providing and manipulating the in-place edit controls for +the grid. + +Instances of `m:wxGridCellEditor` (actually, instances of derived classes since it is an +abstract class) can be associated with the cell attributes for individual cells, rows, +columns, or even for the entire grid. + +Normally `m:wxGridCellEditor` shows some UI control allowing the user to edit the cell, +but starting with wxWidgets 3.1.4 it's also possible to define "activatable" cell editors, +that change the value of the cell directly when it's activated (typically by pressing +Space key or clicking on it), see `TryActivate()` (not implemented in wx) method. Note +that when implementing an editor which is always activatable, i.e. never shows any +in-place editor, it is more convenient to derive its class from `wxGridCellActivatableEditor` +(not implemented in wx) than from `m:wxGridCellEditor` itself. + +See: +* `m:wxGridCellBoolEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellFloatEditor` + +* `m:wxGridCellNumberEditor` + +* `m:wxGridCellTextEditor` + +wxWidgets docs: [wxGridCellEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_editor.html) """. -include("wxe.hrl"). -export([create/4,handleReturn/2,isCreated/1,reset/1,setSize/2,show/2,show/3, @@ -53,11 +57,9 @@ wxWidgets docs: -type wxGridCellEditor() :: wx:wx_object(). -export_type([wxGridCellEditor/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Creates the actual edit control.". -spec create(This, Parent, Id, EvtHandler) -> 'ok' when This::wxGridCellEditor(), Parent::wxWindow:wxWindow(), Id::integer(), EvtHandler::wxEvtHandler:wxEvtHandler(). @@ -68,7 +70,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,#wx_ref{type=Evt ?CLASS(EvtHandlerT,wxEvtHandler), wxe_util:queue_cmd(This,Parent,Id,EvtHandler,?get_env(),?wxGridCellEditor_Create). -%% @doc See external documentation. -doc "Returns true if the edit control has been created.". -spec isCreated(This) -> boolean() when This::wxGridCellEditor(). @@ -77,7 +78,6 @@ isCreated(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellEditor_IsCreated), wxe_util:rec(?wxGridCellEditor_IsCreated). -%% @doc See external documentation. -doc "Size and position the edit control.". -spec setSize(This, Rect) -> 'ok' when This::wxGridCellEditor(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -86,7 +86,7 @@ setSize(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxGridCellEditor), wxe_util:queue_cmd(This,Rect,?get_env(),?wxGridCellEditor_SetSize). -%% @equiv show(This,Show, []) +-doc(#{equiv => show(This,Show, [])}). -spec show(This, Show) -> 'ok' when This::wxGridCellEditor(), Show::boolean(). @@ -94,11 +94,7 @@ show(This,Show) when is_record(This, wx_ref),is_boolean(Show) -> show(This,Show, []). -%% @doc See external documentation. --doc """ -Show or hide the edit control, use the specified attributes to set colours/fonts -for it. -""". +-doc "Show or hide the edit control, use the specified attributes to set colours/fonts for it.". -spec show(This, Show, [Option]) -> 'ok' when This::wxGridCellEditor(), Show::boolean(), Option :: {'attr', wxGridCellAttr:wxGridCellAttr()}. @@ -110,7 +106,6 @@ show(#wx_ref{type=ThisT}=This,Show, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Show, Opts,?get_env(),?wxGridCellEditor_Show). -%% @doc See external documentation. -doc "Reset the value in the control back to its starting value.". -spec reset(This) -> 'ok' when This::wxGridCellEditor(). @@ -118,10 +113,9 @@ reset(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGridCellEditor), wxe_util:queue_cmd(This,?get_env(),?wxGridCellEditor_Reset). -%% @doc See external documentation. -doc """ -If the editor is enabled by pressing keys on the grid, this will be called to -let the editor do something about that first key if desired. +If the editor is enabled by pressing keys on the grid, this will be called to let the +editor do something about that first key if desired. """. -spec startingKey(This, Event) -> 'ok' when This::wxGridCellEditor(), Event::wxKeyEvent:wxKeyEvent(). @@ -130,7 +124,6 @@ startingKey(#wx_ref{type=ThisT}=This,#wx_ref{type=EventT}=Event) -> ?CLASS(EventT,wxKeyEvent), wxe_util:queue_cmd(This,Event,?get_env(),?wxGridCellEditor_StartingKey). -%% @doc See external documentation. -doc "If the editor is enabled by clicking on the cell, this method will be called.". -spec startingClick(This) -> 'ok' when This::wxGridCellEditor(). @@ -138,7 +131,6 @@ startingClick(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxGridCellEditor), wxe_util:queue_cmd(This,?get_env(),?wxGridCellEditor_StartingClick). -%% @doc See external documentation. -doc "Some types of controls on some platforms may need some help with the Return key.". -spec handleReturn(This, Event) -> 'ok' when This::wxGridCellEditor(), Event::wxKeyEvent:wxKeyEvent(). diff --git a/lib/wx/src/gen/wxGridCellFloatEditor.erl b/lib/wx/src/gen/wxGridCellFloatEditor.erl index 7ab57c1f21a9..a75cc02062a8 100644 --- a/lib/wx/src/gen/wxGridCellFloatEditor.erl +++ b/lib/wx/src/gen/wxGridCellFloatEditor.erl @@ -20,19 +20,24 @@ -module(wxGridCellFloatEditor). -moduledoc """ -Functions for wxGridCellFloatEditor class - The editor for floating point numbers data. -See: `m:wxGridCellEditor`, `wxGridCellAutoWrapStringEditor` (not implemented in -wx), `m:wxGridCellBoolEditor`, `m:wxGridCellChoiceEditor`, -`wxGridCellEnumEditor` (not implemented in wx), `m:wxGridCellNumberEditor`, -`m:wxGridCellTextEditor`, `wxGridCellDateEditor` (not implemented in wx) +See: +* `m:wxGridCellEditor` + +* `m:wxGridCellBoolEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellNumberEditor` + +* `m:wxGridCellTextEditor` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxGridCellEditor` +* `m:wxGridCellEditor` -wxWidgets docs: -[wxGridCellFloatEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_float_editor.html) +wxWidgets docs: [wxGridCellFloatEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_float_editor.html) """. -include("wxe.hrl"). -export([destroy/1,new/0,new/1,setParameters/2]). @@ -43,18 +48,16 @@ wxWidgets docs: -type wxGridCellFloatEditor() :: wx:wx_object(). -export_type([wxGridCellFloatEditor/0]). -%% @hidden -doc false. parent_class(wxGridCellEditor) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGridCellFloatEditor(). new() -> new([]). -%% @doc See external documentation. -doc "Float cell editor ctor.". -spec new([Option]) -> wxGridCellFloatEditor() when Option :: {'width', integer()} @@ -70,10 +73,9 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGridCellFloatEditor_new), wxe_util:rec(?wxGridCellFloatEditor_new). -%% @doc See external documentation. -doc """ -The parameters string format is "width\[,precision[,format]]" where `format` -should be chosen between f|e|g|E|G (f is used by default) +The parameters string format is "width[,precision[,format]]" where `format` should be +chosen between f|e|g|E|G (f is used by default) """. -spec setParameters(This, Params) -> 'ok' when This::wxGridCellFloatEditor(), Params::unicode:chardata(). @@ -83,35 +85,26 @@ setParameters(#wx_ref{type=ThisT}=This,Params) Params_UC = unicode:characters_to_binary(Params), wxe_util:queue_cmd(This,Params_UC,?get_env(),?wxGridCellFloatEditor_SetParameters). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellFloatEditor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellFloatEditor), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellFloatEditor_destroy), ok. %% From wxGridCellEditor -%% @hidden -doc false. handleReturn(This,Event) -> wxGridCellEditor:handleReturn(This,Event). -%% @hidden -doc false. startingClick(This) -> wxGridCellEditor:startingClick(This). -%% @hidden -doc false. startingKey(This,Event) -> wxGridCellEditor:startingKey(This,Event). -%% @hidden -doc false. reset(This) -> wxGridCellEditor:reset(This). -%% @hidden -doc false. show(This,Show, Options) -> wxGridCellEditor:show(This,Show, Options). -%% @hidden -doc false. show(This,Show) -> wxGridCellEditor:show(This,Show). -%% @hidden -doc false. setSize(This,Rect) -> wxGridCellEditor:setSize(This,Rect). -%% @hidden -doc false. isCreated(This) -> wxGridCellEditor:isCreated(This). diff --git a/lib/wx/src/gen/wxGridCellFloatRenderer.erl b/lib/wx/src/gen/wxGridCellFloatRenderer.erl index 7d452c40e68c..3dd7a807baf3 100644 --- a/lib/wx/src/gen/wxGridCellFloatRenderer.erl +++ b/lib/wx/src/gen/wxGridCellFloatRenderer.erl @@ -20,20 +20,24 @@ -module(wxGridCellFloatRenderer). -moduledoc """ -Functions for wxGridCellFloatRenderer class - This class may be used to format floating point data in a cell. -See: `m:wxGridCellRenderer`, `wxGridCellAutoWrapStringRenderer` (not implemented -in wx), `m:wxGridCellBoolRenderer`, `wxGridCellDateTimeRenderer` (not -implemented in wx), `wxGridCellEnumRenderer` (not implemented in wx), -`m:wxGridCellNumberRenderer`, `m:wxGridCellStringRenderer` +See: +* `m:wxGridCellRenderer` + +* `m:wxGridCellBoolRenderer` + +* `m:wxGridCellNumberRenderer` + +* `m:wxGridCellStringRenderer` + +This class is derived, and can use functions, from: + +* `m:wxGridCellStringRenderer` -This class is derived (and can use functions) from: `m:wxGridCellStringRenderer` -`m:wxGridCellRenderer` +* `m:wxGridCellRenderer` -wxWidgets docs: -[wxGridCellFloatRenderer](https://docs.wxwidgets.org/3.1/classwx_grid_cell_float_renderer.html) +wxWidgets docs: [wxGridCellFloatRenderer](https://docs.wxwidgets.org/3.2/classwx_grid_cell_float_renderer.html) """. -include("wxe.hrl"). -export([destroy/1,getPrecision/1,getWidth/1,new/0,new/1,setParameters/2,setPrecision/2, @@ -44,19 +48,17 @@ wxWidgets docs: -type wxGridCellFloatRenderer() :: wx:wx_object(). -export_type([wxGridCellFloatRenderer/0]). -%% @hidden -doc false. parent_class(wxGridCellStringRenderer) -> true; parent_class(wxGridCellRenderer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGridCellFloatRenderer(). new() -> new([]). -%% @doc See external documentation. -doc "Float cell renderer ctor.". -spec new([Option]) -> wxGridCellFloatRenderer() when Option :: {'width', integer()} @@ -72,7 +74,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGridCellFloatRenderer_new), wxe_util:rec(?wxGridCellFloatRenderer_new). -%% @doc See external documentation. -doc "Returns the precision.". -spec getPrecision(This) -> integer() when This::wxGridCellFloatRenderer(). @@ -81,7 +82,6 @@ getPrecision(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellFloatRenderer_GetPrecision), wxe_util:rec(?wxGridCellFloatRenderer_GetPrecision). -%% @doc See external documentation. -doc "Returns the width.". -spec getWidth(This) -> integer() when This::wxGridCellFloatRenderer(). @@ -90,10 +90,9 @@ getWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellFloatRenderer_GetWidth), wxe_util:rec(?wxGridCellFloatRenderer_GetWidth). -%% @doc See external documentation. -doc """ -The parameters string format is "width\[,precision[,format]]" where `format` -should be chosen between f|e|g|E|G (f is used by default) +The parameters string format is "width[,precision[,format]]" where `format` should be +chosen between f|e|g|E|G (f is used by default) """. -spec setParameters(This, Params) -> 'ok' when This::wxGridCellFloatRenderer(), Params::unicode:chardata(). @@ -103,7 +102,6 @@ setParameters(#wx_ref{type=ThisT}=This,Params) Params_UC = unicode:characters_to_binary(Params), wxe_util:queue_cmd(This,Params_UC,?get_env(),?wxGridCellFloatRenderer_SetParameters). -%% @doc See external documentation. -doc "Sets the precision.". -spec setPrecision(This, Precision) -> 'ok' when This::wxGridCellFloatRenderer(), Precision::integer(). @@ -112,7 +110,6 @@ setPrecision(#wx_ref{type=ThisT}=This,Precision) ?CLASS(ThisT,wxGridCellFloatRenderer), wxe_util:queue_cmd(This,Precision,?get_env(),?wxGridCellFloatRenderer_SetPrecision). -%% @doc See external documentation. -doc "Sets the width.". -spec setWidth(This, Width) -> 'ok' when This::wxGridCellFloatRenderer(), Width::integer(). @@ -121,8 +118,7 @@ setWidth(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxGridCellFloatRenderer), wxe_util:queue_cmd(This,Width,?get_env(),?wxGridCellFloatRenderer_SetWidth). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellFloatRenderer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellFloatRenderer), @@ -130,9 +126,7 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxGridCellStringRenderer %% From wxGridCellRenderer -%% @hidden -doc false. getBestSize(This,Grid,Attr,Dc,Row,Col) -> wxGridCellRenderer:getBestSize(This,Grid,Attr,Dc,Row,Col). -%% @hidden -doc false. draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected) -> wxGridCellRenderer:draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected). diff --git a/lib/wx/src/gen/wxGridCellNumberEditor.erl b/lib/wx/src/gen/wxGridCellNumberEditor.erl index fdf3ec36e322..a43f9501a62d 100644 --- a/lib/wx/src/gen/wxGridCellNumberEditor.erl +++ b/lib/wx/src/gen/wxGridCellNumberEditor.erl @@ -20,20 +20,26 @@ -module(wxGridCellNumberEditor). -moduledoc """ -Functions for wxGridCellNumberEditor class - Grid cell editor for numeric integer data. -See: `m:wxGridCellEditor`, `wxGridCellAutoWrapStringEditor` (not implemented in -wx), `m:wxGridCellBoolEditor`, `m:wxGridCellChoiceEditor`, -`wxGridCellEnumEditor` (not implemented in wx), `m:wxGridCellFloatEditor`, -`m:wxGridCellTextEditor`, `wxGridCellDateEditor` (not implemented in wx) +See: +* `m:wxGridCellEditor` + +* `m:wxGridCellBoolEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellFloatEditor` + +* `m:wxGridCellTextEditor` + +This class is derived, and can use functions, from: + +* `m:wxGridCellTextEditor` -This class is derived (and can use functions) from: `m:wxGridCellTextEditor` -`m:wxGridCellEditor` +* `m:wxGridCellEditor` -wxWidgets docs: -[wxGridCellNumberEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_number_editor.html) +wxWidgets docs: [wxGridCellNumberEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_number_editor.html) """. -include("wxe.hrl"). -export([destroy/1,getValue/1,new/0,new/1,setParameters/2]). @@ -44,24 +50,22 @@ wxWidgets docs: -type wxGridCellNumberEditor() :: wx:wx_object(). -export_type([wxGridCellNumberEditor/0]). -%% @hidden -doc false. parent_class(wxGridCellTextEditor) -> true; parent_class(wxGridCellEditor) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGridCellNumberEditor(). new() -> new([]). -%% @doc See external documentation. -doc """ Allows you to specify the range for acceptable data. -Values equal to -1 for both `min` and `max` indicate that no range checking -should be done. +Values equal to -1 for both `min` and `max` indicate that no range checking should be +done. """. -spec new([Option]) -> wxGridCellNumberEditor() when Option :: {'min', integer()} @@ -75,7 +79,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGridCellNumberEditor_new), wxe_util:rec(?wxGridCellNumberEditor_new). -%% @doc See external documentation. -doc "Returns the value currently in the editor control.". -spec getValue(This) -> unicode:charlist() when This::wxGridCellNumberEditor(). @@ -84,7 +87,6 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridCellNumberEditor_GetValue), wxe_util:rec(?wxGridCellNumberEditor_GetValue). -%% @doc See external documentation. -doc """ Parameters string format is "min,max". """. @@ -96,8 +98,7 @@ setParameters(#wx_ref{type=ThisT}=This,Params) Params_UC = unicode:characters_to_binary(Params), wxe_util:queue_cmd(This,Params_UC,?get_env(),?wxGridCellNumberEditor_SetParameters). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellNumberEditor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellNumberEditor), @@ -105,27 +106,19 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxGridCellTextEditor %% From wxGridCellEditor -%% @hidden -doc false. handleReturn(This,Event) -> wxGridCellEditor:handleReturn(This,Event). -%% @hidden -doc false. startingClick(This) -> wxGridCellEditor:startingClick(This). -%% @hidden -doc false. startingKey(This,Event) -> wxGridCellEditor:startingKey(This,Event). -%% @hidden -doc false. reset(This) -> wxGridCellEditor:reset(This). -%% @hidden -doc false. show(This,Show, Options) -> wxGridCellEditor:show(This,Show, Options). -%% @hidden -doc false. show(This,Show) -> wxGridCellEditor:show(This,Show). -%% @hidden -doc false. setSize(This,Rect) -> wxGridCellEditor:setSize(This,Rect). -%% @hidden -doc false. isCreated(This) -> wxGridCellEditor:isCreated(This). diff --git a/lib/wx/src/gen/wxGridCellNumberRenderer.erl b/lib/wx/src/gen/wxGridCellNumberRenderer.erl index c2588c4e5a45..a8ccf92d071c 100644 --- a/lib/wx/src/gen/wxGridCellNumberRenderer.erl +++ b/lib/wx/src/gen/wxGridCellNumberRenderer.erl @@ -20,20 +20,24 @@ -module(wxGridCellNumberRenderer). -moduledoc """ -Functions for wxGridCellNumberRenderer class - This class may be used to format integer data in a cell. -See: `m:wxGridCellRenderer`, `wxGridCellAutoWrapStringRenderer` (not implemented -in wx), `m:wxGridCellBoolRenderer`, `wxGridCellDateTimeRenderer` (not -implemented in wx), `wxGridCellEnumRenderer` (not implemented in wx), -`m:wxGridCellFloatRenderer`, `m:wxGridCellStringRenderer` +See: +* `m:wxGridCellRenderer` + +* `m:wxGridCellBoolRenderer` + +* `m:wxGridCellFloatRenderer` + +* `m:wxGridCellStringRenderer` + +This class is derived, and can use functions, from: + +* `m:wxGridCellStringRenderer` -This class is derived (and can use functions) from: `m:wxGridCellStringRenderer` -`m:wxGridCellRenderer` +* `m:wxGridCellRenderer` -wxWidgets docs: -[wxGridCellNumberRenderer](https://docs.wxwidgets.org/3.1/classwx_grid_cell_number_renderer.html) +wxWidgets docs: [wxGridCellNumberRenderer](https://docs.wxwidgets.org/3.2/classwx_grid_cell_number_renderer.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -43,21 +47,18 @@ wxWidgets docs: -type wxGridCellNumberRenderer() :: wx:wx_object(). -export_type([wxGridCellNumberRenderer/0]). -%% @hidden -doc false. parent_class(wxGridCellStringRenderer) -> true; parent_class(wxGridCellRenderer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default constructor.". -spec new() -> wxGridCellNumberRenderer(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGridCellNumberRenderer_new), wxe_util:rec(?wxGridCellNumberRenderer_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellNumberRenderer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellNumberRenderer), @@ -65,9 +66,7 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxGridCellStringRenderer %% From wxGridCellRenderer -%% @hidden -doc false. getBestSize(This,Grid,Attr,Dc,Row,Col) -> wxGridCellRenderer:getBestSize(This,Grid,Attr,Dc,Row,Col). -%% @hidden -doc false. draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected) -> wxGridCellRenderer:draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected). diff --git a/lib/wx/src/gen/wxGridCellRenderer.erl b/lib/wx/src/gen/wxGridCellRenderer.erl index 2dd933595f39..f61923480bf7 100644 --- a/lib/wx/src/gen/wxGridCellRenderer.erl +++ b/lib/wx/src/gen/wxGridCellRenderer.erl @@ -20,22 +20,22 @@ -module(wxGridCellRenderer). -moduledoc """ -Functions for wxGridCellRenderer class +This class is responsible for actually drawing the cell in the grid. -This class is responsible for actually drawing the cell in the grid. You may -pass it to the `m:wxGridCellAttr` (below) to change the format of one given cell -or to `wxGrid:setDefaultRenderer/2` to change the view of all cells. This is an -abstract class, and you will normally use one of the predefined derived classes -or derive your own class from it. +You may pass it to the `m:wxGridCellAttr` (below) to change the format of one given cell +or to `wxGrid:setDefaultRenderer/2` to change the view of all cells. This is an abstract class, and you will normally +use one of the predefined derived classes or derive your own class from it. -See: `wxGridCellAutoWrapStringRenderer` (not implemented in wx), -`m:wxGridCellBoolRenderer`, `wxGridCellDateTimeRenderer` (not implemented in -wx), `wxGridCellEnumRenderer` (not implemented in wx), -`m:wxGridCellFloatRenderer`, `m:wxGridCellNumberRenderer`, -`m:wxGridCellStringRenderer` +See: +* `m:wxGridCellBoolRenderer` -wxWidgets docs: -[wxGridCellRenderer](https://docs.wxwidgets.org/3.1/classwx_grid_cell_renderer.html) +* `m:wxGridCellFloatRenderer` + +* `m:wxGridCellNumberRenderer` + +* `m:wxGridCellStringRenderer` + +wxWidgets docs: [wxGridCellRenderer](https://docs.wxwidgets.org/3.2/classwx_grid_cell_renderer.html) """. -include("wxe.hrl"). -export([draw/8,getBestSize/6]). @@ -45,19 +45,17 @@ wxWidgets docs: -type wxGridCellRenderer() :: wx:wx_object(). -export_type([wxGridCellRenderer/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Draw the given cell on the provided DC inside the given rectangle using the -style specified by the attribute and the default or selected state corresponding -to the isSelected value. +Draw the given cell on the provided DC inside the given rectangle using the style +specified by the attribute and the default or selected state corresponding to the +isSelected value. -This pure virtual function has a default implementation which will prepare the -DC using the given attribute: it will draw the rectangle with the background -colour from attr and set the text colour and font. +This pure virtual function has a default implementation which will prepare the DC using +the given attribute: it will draw the rectangle with the background colour from attr and +set the text colour and font. """. -spec draw(This, Grid, Attr, Dc, Rect, Row, Col, IsSelected) -> 'ok' when This::wxGridCellRenderer(), Grid::wxGrid:wxGrid(), Attr::wxGridCellAttr:wxGridCellAttr(), Dc::wxDC:wxDC(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, Row::integer(), Col::integer(), IsSelected::boolean(). @@ -69,15 +67,11 @@ draw(#wx_ref{type=ThisT}=This,#wx_ref{type=GridT}=Grid,#wx_ref{type=AttrT}=Attr, ?CLASS(DcT,wxDC), wxe_util:queue_cmd(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected,?get_env(),?wxGridCellRenderer_Draw). -%% @doc See external documentation. -doc """ Get the preferred size of the cell for its contents. -This method must be overridden in the derived classes to return the minimal -fitting size for displaying the content of the given grid cell. - -See: `GetBestHeight()` (not implemented in wx), `GetBestWidth()` (not -implemented in wx) +This method must be overridden in the derived classes to return the minimal fitting size +for displaying the content of the given grid cell. """. -spec getBestSize(This, Grid, Attr, Dc, Row, Col) -> {W::integer(), H::integer()} when This::wxGridCellRenderer(), Grid::wxGrid:wxGrid(), Attr::wxGridCellAttr:wxGridCellAttr(), Dc::wxDC:wxDC(), Row::integer(), Col::integer(). diff --git a/lib/wx/src/gen/wxGridCellStringRenderer.erl b/lib/wx/src/gen/wxGridCellStringRenderer.erl index 13219686674d..dd447deabdba 100644 --- a/lib/wx/src/gen/wxGridCellStringRenderer.erl +++ b/lib/wx/src/gen/wxGridCellStringRenderer.erl @@ -20,20 +20,23 @@ -module(wxGridCellStringRenderer). -moduledoc """ -Functions for wxGridCellStringRenderer class +This class may be used to format string data in a cell; it is the default for string +cells. -This class may be used to format string data in a cell; it is the default for -string cells. +See: +* `m:wxGridCellRenderer` -See: `m:wxGridCellRenderer`, `wxGridCellAutoWrapStringRenderer` (not implemented -in wx), `m:wxGridCellBoolRenderer`, `wxGridCellDateTimeRenderer` (not -implemented in wx), `wxGridCellEnumRenderer` (not implemented in wx), -`m:wxGridCellFloatRenderer`, `m:wxGridCellNumberRenderer` +* `m:wxGridCellBoolRenderer` -This class is derived (and can use functions) from: `m:wxGridCellRenderer` +* `m:wxGridCellFloatRenderer` -wxWidgets docs: -[wxGridCellStringRenderer](https://docs.wxwidgets.org/3.1/classwx_grid_cell_string_renderer.html) +* `m:wxGridCellNumberRenderer` + +This class is derived, and can use functions, from: + +* `m:wxGridCellRenderer` + +wxWidgets docs: [wxGridCellStringRenderer](https://docs.wxwidgets.org/3.2/classwx_grid_cell_string_renderer.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -43,28 +46,24 @@ wxWidgets docs: -type wxGridCellStringRenderer() :: wx:wx_object(). -export_type([wxGridCellStringRenderer/0]). -%% @hidden -doc false. parent_class(wxGridCellRenderer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. +-doc "". -spec new() -> wxGridCellStringRenderer(). new() -> wxe_util:queue_cmd(?get_env(), ?wxGridCellStringRenderer_new), wxe_util:rec(?wxGridCellStringRenderer_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellStringRenderer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellStringRenderer), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellStringRenderer_destroy), ok. %% From wxGridCellRenderer -%% @hidden -doc false. getBestSize(This,Grid,Attr,Dc,Row,Col) -> wxGridCellRenderer:getBestSize(This,Grid,Attr,Dc,Row,Col). -%% @hidden -doc false. draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected) -> wxGridCellRenderer:draw(This,Grid,Attr,Dc,Rect,Row,Col,IsSelected). diff --git a/lib/wx/src/gen/wxGridCellTextEditor.erl b/lib/wx/src/gen/wxGridCellTextEditor.erl index b6b80155a83d..223a5a9393e8 100644 --- a/lib/wx/src/gen/wxGridCellTextEditor.erl +++ b/lib/wx/src/gen/wxGridCellTextEditor.erl @@ -20,19 +20,24 @@ -module(wxGridCellTextEditor). -moduledoc """ -Functions for wxGridCellTextEditor class - Grid cell editor for string/text data. -See: `m:wxGridCellEditor`, `wxGridCellAutoWrapStringEditor` (not implemented in -wx), `m:wxGridCellBoolEditor`, `m:wxGridCellChoiceEditor`, -`wxGridCellEnumEditor` (not implemented in wx), `m:wxGridCellFloatEditor`, -`m:wxGridCellNumberEditor`, `wxGridCellDateEditor` (not implemented in wx) +See: +* `m:wxGridCellEditor` + +* `m:wxGridCellBoolEditor` + +* `m:wxGridCellChoiceEditor` + +* `m:wxGridCellFloatEditor` + +* `m:wxGridCellNumberEditor` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxGridCellEditor` +* `m:wxGridCellEditor` -wxWidgets docs: -[wxGridCellTextEditor](https://docs.wxwidgets.org/3.1/classwx_grid_cell_text_editor.html) +wxWidgets docs: [wxGridCellTextEditor](https://docs.wxwidgets.org/3.2/classwx_grid_cell_text_editor.html) """. -include("wxe.hrl"). -export([destroy/1,new/0,new/1,setParameters/2]). @@ -43,18 +48,16 @@ wxWidgets docs: -type wxGridCellTextEditor() :: wx:wx_object(). -export_type([wxGridCellTextEditor/0]). -%% @hidden -doc false. parent_class(wxGridCellEditor) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxGridCellTextEditor(). new() -> new([]). -%% @doc See external documentation. -doc "Text cell editor constructor.". -spec new([Option]) -> wxGridCellTextEditor() when Option :: {'maxChars', integer()}. @@ -66,10 +69,8 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxGridCellTextEditor_new), wxe_util:rec(?wxGridCellTextEditor_new). -%% @doc See external documentation. -doc """ -The parameters string format is "n" where n is a number representing the maximum -width. +The parameters string format is "n" where n is a number representing the maximum width. """. -spec setParameters(This, Params) -> 'ok' when This::wxGridCellTextEditor(), Params::unicode:chardata(). @@ -79,35 +80,26 @@ setParameters(#wx_ref{type=ThisT}=This,Params) Params_UC = unicode:characters_to_binary(Params), wxe_util:queue_cmd(This,Params_UC,?get_env(),?wxGridCellTextEditor_SetParameters). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridCellTextEditor()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridCellTextEditor), wxe_util:queue_cmd(Obj, ?get_env(), ?wxGridCellTextEditor_destroy), ok. %% From wxGridCellEditor -%% @hidden -doc false. handleReturn(This,Event) -> wxGridCellEditor:handleReturn(This,Event). -%% @hidden -doc false. startingClick(This) -> wxGridCellEditor:startingClick(This). -%% @hidden -doc false. startingKey(This,Event) -> wxGridCellEditor:startingKey(This,Event). -%% @hidden -doc false. reset(This) -> wxGridCellEditor:reset(This). -%% @hidden -doc false. show(This,Show, Options) -> wxGridCellEditor:show(This,Show, Options). -%% @hidden -doc false. show(This,Show) -> wxGridCellEditor:show(This,Show). -%% @hidden -doc false. setSize(This,Rect) -> wxGridCellEditor:setSize(This,Rect). -%% @hidden -doc false. isCreated(This) -> wxGridCellEditor:isCreated(This). diff --git a/lib/wx/src/gen/wxGridEvent.erl b/lib/wx/src/gen/wxGridEvent.erl index b22d2e1284df..234523bafa71 100644 --- a/lib/wx/src/gen/wxGridEvent.erl +++ b/lib/wx/src/gen/wxGridEvent.erl @@ -20,30 +20,30 @@ -module(wxGridEvent). -moduledoc """ -Functions for wxGridEvent class - This event class contains information about various grid events. -Notice that all grid event table macros are available in two versions: -`EVT_GRID_XXX` and `EVT_GRID_CMD_XXX`. The only difference between the two is -that the former doesn't allow to specify the grid window identifier and so takes -a single parameter, the event handler, but is not suitable if there is more than -one grid control in the window where the event table is used (as it would catch -the events from all the grids). The version with `CMD` takes the id as first -argument and the event handler as the second one and so can be used with -multiple grids as well. Otherwise there are no difference between the two and -only the versions without the id are documented below for brevity. +Notice that all grid event table macros are available in two versions: `EVT_GRID_XXX` and `EVT_GRID_CMD_XXX`. +The only difference between the two is that the former doesn't allow to specify the grid +window identifier and so takes a single parameter, the event handler, but is not suitable +if there is more than one grid control in the window where the event table is used (as it +would catch the events from all the grids). The version with `CMD` takes the id as first +argument and the event handler as the second one and so can be used with multiple grids as +well. Otherwise there are no difference between the two and only the versions without the +id are documented below for brevity. + +This class is derived, and can use functions, from: + +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxGridEvent](https://docs.wxwidgets.org/3.1/classwx_grid_event.html) +wxWidgets docs: [wxGridEvent](https://docs.wxwidgets.org/3.2/classwx_grid_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxGridEventType`](`t:wxGridEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxGridEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([altDown/1,controlDown/1,getCol/1,getPosition/1,getRow/1,metaDown/1, @@ -59,14 +59,12 @@ subscribe to events of this type. -include("wx.hrl"). -type wxGridEventType() :: 'grid_cell_left_click' | 'grid_cell_right_click' | 'grid_cell_left_dclick' | 'grid_cell_right_dclick' | 'grid_label_left_click' | 'grid_label_right_click' | 'grid_label_left_dclick' | 'grid_label_right_dclick' | 'grid_cell_changed' | 'grid_select_cell' | 'grid_cell_begin_drag' | 'grid_editor_shown' | 'grid_editor_hidden' | 'grid_col_move' | 'grid_col_sort' | 'grid_tabbing'. -export_type([wxGridEvent/0, wxGrid/0, wxGridEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Returns true if the Alt key was down at the time of the event.". -spec altDown(This) -> boolean() when This::wxGridEvent(). @@ -75,7 +73,6 @@ altDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_AltDown), wxe_util:rec(?wxGridEvent_AltDown). -%% @doc See external documentation. -doc "Returns true if the Control key was down at the time of the event.". -spec controlDown(This) -> boolean() when This::wxGridEvent(). @@ -84,13 +81,11 @@ controlDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_ControlDown), wxe_util:rec(?wxGridEvent_ControlDown). -%% @doc See external documentation. -doc """ Column at which the event occurred. -Notice that for a `wxEVT_GRID_SELECT_CELL` event this column is the column of -the newly selected cell while the previously selected cell can be retrieved -using `wxGrid:getGridCursorCol/1`. +Notice that for a `wxEVT_GRID_SELECT_CELL` event this column is the column of the newly +selected cell while the previously selected cell can be retrieved using `wxGrid:getGridCursorCol/1`. """. -spec getCol(This) -> integer() when This::wxGridEvent(). @@ -99,7 +94,6 @@ getCol(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_GetCol), wxe_util:rec(?wxGridEvent_GetCol). -%% @doc See external documentation. -doc "Position in pixels at which the event occurred.". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxGridEvent(). @@ -108,13 +102,11 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_GetPosition), wxe_util:rec(?wxGridEvent_GetPosition). -%% @doc See external documentation. -doc """ Row at which the event occurred. -Notice that for a `wxEVT_GRID_SELECT_CELL` event this row is the row of the -newly selected cell while the previously selected cell can be retrieved using -`wxGrid:getGridCursorRow/1`. +Notice that for a `wxEVT_GRID_SELECT_CELL` event this row is the row of the newly +selected cell while the previously selected cell can be retrieved using `wxGrid:getGridCursorRow/1`. """. -spec getRow(This) -> integer() when This::wxGridEvent(). @@ -123,7 +115,6 @@ getRow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_GetRow), wxe_util:rec(?wxGridEvent_GetRow). -%% @doc See external documentation. -doc "Returns true if the Meta key was down at the time of the event.". -spec metaDown(This) -> boolean() when This::wxGridEvent(). @@ -132,7 +123,6 @@ metaDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_MetaDown), wxe_util:rec(?wxGridEvent_MetaDown). -%% @doc See external documentation. -doc "Returns true if the user is selecting grid cells, or false if deselecting.". -spec selecting(This) -> boolean() when This::wxGridEvent(). @@ -141,7 +131,6 @@ selecting(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridEvent_Selecting), wxe_util:rec(?wxGridEvent_Selecting). -%% @doc See external documentation. -doc "Returns true if the Shift key was down at the time of the event.". -spec shiftDown(This) -> boolean() when This::wxGridEvent(). @@ -151,68 +140,47 @@ shiftDown(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxGridEvent_ShiftDown). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxGridSizer.erl b/lib/wx/src/gen/wxGridSizer.erl index 4d2a760b78d1..789a63749518 100644 --- a/lib/wx/src/gen/wxGridSizer.erl +++ b/lib/wx/src/gen/wxGridSizer.erl @@ -20,20 +20,22 @@ -module(wxGridSizer). -moduledoc """ -Functions for wxGridSizer class +A grid sizer is a sizer which lays out its children in a two-dimensional table with all +table fields having the same size, i.e. -A grid sizer is a sizer which lays out its children in a two-dimensional table -with all table fields having the same size, i.e. the width of each field is the -width of the widest child, the height of each field is the height of the tallest -child. +the width of each field is the width of the widest child, the height of each field is the +height of the tallest child. -See: `m:wxSizer`, -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer) +See: +* `m:wxSizer` -This class is derived (and can use functions) from: `m:wxSizer` +* [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) -wxWidgets docs: -[wxGridSizer](https://docs.wxwidgets.org/3.1/classwx_grid_sizer.html) +This class is derived, and can use functions, from: + +* `m:wxSizer` + +wxWidgets docs: [wxGridSizer](https://docs.wxwidgets.org/3.2/classwx_grid_sizer.html) """. -include("wxe.hrl"). -export([destroy/1,getCols/1,getHGap/1,getRows/1,getVGap/1,new/1,new/2,new/3,new/4, @@ -52,12 +54,11 @@ wxWidgets docs: -type wxGridSizer() :: wx:wx_object(). -export_type([wxGridSizer/0]). -%% @hidden -doc false. parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Cols, []) +-doc(#{equiv => new(Cols, [])}). -spec new(Cols) -> wxGridSizer() when Cols::integer(). @@ -65,7 +66,7 @@ new(Cols) when is_integer(Cols) -> new(Cols, []). -%% @doc See external documentation. +-doc "". -spec new(Cols, [Option]) -> wxGridSizer() when Cols::integer(), Option :: {'gap', {W::integer(), H::integer()}}. @@ -77,11 +78,7 @@ new(Cols, Options) wxe_util:queue_cmd(Cols, Opts,?get_env(),?wxGridSizer_new_2), wxe_util:rec(?wxGridSizer_new_2). -%% @doc See external documentation. -%%
Also:
-%% new(Rows, Cols, Gap) -> wxGridSizer() when
-%% Rows::integer(), Cols::integer(), Gap::{W::integer(), H::integer()}.
-%% +-doc "". -spec new(Cols, Vgap, Hgap) -> wxGridSizer() when Cols::integer(), Vgap::integer(), Hgap::integer(); (Rows, Cols, Gap) -> wxGridSizer() when @@ -95,7 +92,7 @@ new(Rows,Cols,{GapW,GapH} = Gap) wxe_util:queue_cmd(Rows,Cols,Gap,?get_env(),?wxGridSizer_new_3_1), wxe_util:rec(?wxGridSizer_new_3_1). -%% @doc See external documentation. +-doc "". -spec new(Rows, Cols, Vgap, Hgap) -> wxGridSizer() when Rows::integer(), Cols::integer(), Vgap::integer(), Hgap::integer(). new(Rows,Cols,Vgap,Hgap) @@ -103,13 +100,12 @@ new(Rows,Cols,Vgap,Hgap) wxe_util:queue_cmd(Rows,Cols,Vgap,Hgap,?get_env(),?wxGridSizer_new_4), wxe_util:rec(?wxGridSizer_new_4). -%% @doc See external documentation. -doc """ Returns the number of columns that has been specified for the sizer. -Returns zero if the sizer is automatically adjusting the number of columns -depending on number of its children. To get the effective number of columns or -rows being currently used, see `GetEffectiveColsCount()` (not implemented in wx) +Returns zero if the sizer is automatically adjusting the number of columns depending on +number of its children. To get the effective number of columns or rows being currently +used, see `GetEffectiveColsCount()` (not implemented in wx) """. -spec getCols(This) -> integer() when This::wxGridSizer(). @@ -118,7 +114,6 @@ getCols(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridSizer_GetCols), wxe_util:rec(?wxGridSizer_GetCols). -%% @doc See external documentation. -doc "Returns the horizontal gap (in pixels) between cells in the sizer.". -spec getHGap(This) -> integer() when This::wxGridSizer(). @@ -127,14 +122,12 @@ getHGap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridSizer_GetHGap), wxe_util:rec(?wxGridSizer_GetHGap). -%% @doc See external documentation. -doc """ Returns the number of rows that has been specified for the sizer. -Returns zero if the sizer is automatically adjusting the number of rows -depending on number of its children. To get the effective number of columns or -rows being currently used, see `GetEffectiveRowsCount()` (not implemented in -wx). +Returns zero if the sizer is automatically adjusting the number of rows depending on +number of its children. To get the effective number of columns or rows being currently +used, see `GetEffectiveRowsCount()` (not implemented in wx). """. -spec getRows(This) -> integer() when This::wxGridSizer(). @@ -143,7 +136,6 @@ getRows(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridSizer_GetRows), wxe_util:rec(?wxGridSizer_GetRows). -%% @doc See external documentation. -doc "Returns the vertical gap (in pixels) between the cells in the sizer.". -spec getVGap(This) -> integer() when This::wxGridSizer(). @@ -152,7 +144,6 @@ getVGap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxGridSizer_GetVGap), wxe_util:rec(?wxGridSizer_GetVGap). -%% @doc See external documentation. -doc "Sets the number of columns in the sizer.". -spec setCols(This, Cols) -> 'ok' when This::wxGridSizer(), Cols::integer(). @@ -161,7 +152,6 @@ setCols(#wx_ref{type=ThisT}=This,Cols) ?CLASS(ThisT,wxGridSizer), wxe_util:queue_cmd(This,Cols,?get_env(),?wxGridSizer_SetCols). -%% @doc See external documentation. -doc "Sets the horizontal gap (in pixels) between cells in the sizer.". -spec setHGap(This, Gap) -> 'ok' when This::wxGridSizer(), Gap::integer(). @@ -170,7 +160,6 @@ setHGap(#wx_ref{type=ThisT}=This,Gap) ?CLASS(ThisT,wxGridSizer), wxe_util:queue_cmd(This,Gap,?get_env(),?wxGridSizer_SetHGap). -%% @doc See external documentation. -doc "Sets the number of rows in the sizer.". -spec setRows(This, Rows) -> 'ok' when This::wxGridSizer(), Rows::integer(). @@ -179,7 +168,6 @@ setRows(#wx_ref{type=ThisT}=This,Rows) ?CLASS(ThisT,wxGridSizer), wxe_util:queue_cmd(This,Rows,?get_env(),?wxGridSizer_SetRows). -%% @doc See external documentation. -doc "Sets the vertical gap (in pixels) between the cells in the sizer.". -spec setVGap(This, Gap) -> 'ok' when This::wxGridSizer(), Gap::integer(). @@ -188,158 +176,108 @@ setVGap(#wx_ref{type=ThisT}=This,Gap) ?CLASS(ThisT,wxGridSizer), wxe_util:queue_cmd(This,Gap,?get_env(),?wxGridSizer_SetVGap). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxGridSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxGridSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. calcMin(This) -> wxSizer:calcMin(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). -%% @hidden -doc false. add(This,Width,Height, Options) -> wxSizer:add(This,Width,Height, Options). -%% @hidden -doc false. add(This,Width,Height) -> wxSizer:add(This,Width,Height). -%% @hidden -doc false. add(This,Window) -> wxSizer:add(This,Window). diff --git a/lib/wx/src/gen/wxHelpEvent.erl b/lib/wx/src/gen/wxHelpEvent.erl index 87c2d94302c6..1726d57c407a 100644 --- a/lib/wx/src/gen/wxHelpEvent.erl +++ b/lib/wx/src/gen/wxHelpEvent.erl @@ -20,39 +20,36 @@ -module(wxHelpEvent). -moduledoc """ -Functions for wxHelpEvent class +A help event is sent when the user has requested context-sensitive help. -A help event is sent when the user has requested context-sensitive help. This -can either be caused by the application requesting context-sensitive help mode -via `wxContextHelp` (not implemented in wx), or (on MS Windows) by the system -generating a WM_HELP message when the user pressed F1 or clicked on the query -button in a dialog caption. +This can either be caused by the application requesting context-sensitive help mode via `wxContextHelp` +(not implemented in wx), or (on MS Windows) by the system generating a WM_HELP message +when the user pressed F1 or clicked on the query button in a dialog caption. -A help event is sent to the window that the user clicked on, and is propagated -up the window hierarchy until the event is processed or there are no more event -handlers. +A help event is sent to the window that the user clicked on, and is propagated up the +window hierarchy until the event is processed or there are no more event handlers. -The application should call `wxEvent:getId/1` to check the identity of the -clicked-on window, and then either show some suitable help or call -`wxEvent:skip/2` if the identifier is unrecognised. +The application should call `wxEvent:getId/1` to check the identity of the clicked-on window, and then +either show some suitable help or call `wxEvent:skip/2` if the identifier is unrecognised. -Calling Skip is important because it allows wxWidgets to generate further events -for ancestors of the clicked-on window. Otherwise it would be impossible to show -help for container windows, since processing would stop after the first window -found. +Calling Skip is important because it allows wxWidgets to generate further events for +ancestors of the clicked-on window. Otherwise it would be impossible to show help for +container windows, since processing would stop after the first window found. -See: `wxContextHelp` (not implemented in wx), `m:wxDialog`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +See: +* `m:wxDialog` -This class is derived (and can use functions) from: `m:wxEvent` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -wxWidgets docs: -[wxHelpEvent](https://docs.wxwidgets.org/3.1/classwx_help_event.html) +This class is derived, and can use functions, from: + +* `m:wxEvent` + +wxWidgets docs: [wxHelpEvent](https://docs.wxwidgets.org/3.2/classwx_help_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxHelpEventType`](`t:wxHelpEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxHelpEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getOrigin/1,getPosition/1,setOrigin/2,setPosition/2]). @@ -65,22 +62,20 @@ subscribe to events of this type. -include("wx.hrl"). -type wxHelpEventType() :: 'help' | 'detailed_help'. -export_type([wxHelpEvent/0, wxHelp/0, wxHelpEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -%%
Res = ?wxHelpEvent_Origin_Unknown | ?wxHelpEvent_Origin_Keyboard | ?wxHelpEvent_Origin_HelpButton -doc """ -Returns the origin of the help event which is one of the `wxHelpEvent::Origin` -(not implemented in wx) values. +Returns the origin of the help event which is one of the `wxHelpEvent::Origin` (not +implemented in wx) values. -The application may handle events generated using the keyboard or mouse -differently, e.g. by using `wx_misc:getMousePosition/0` for the mouse events. +The application may handle events generated using the keyboard or mouse differently, e.g. +by using `wx_misc:getMousePosition/0` for the mouse events. See: `setOrigin/2` """. +%% Res = ?wxHelpEvent_Origin_Unknown | ?wxHelpEvent_Origin_Keyboard | ?wxHelpEvent_Origin_HelpButton -spec getOrigin(This) -> wx:wx_enum() when This::wxHelpEvent(). getOrigin(#wx_ref{type=ThisT}=This) -> @@ -88,7 +83,6 @@ getOrigin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHelpEvent_GetOrigin), wxe_util:rec(?wxHelpEvent_GetOrigin). -%% @doc See external documentation. -doc """ Returns the left-click position of the mouse, in screen coordinates. @@ -101,13 +95,12 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHelpEvent_GetPosition), wxe_util:rec(?wxHelpEvent_GetPosition). -%% @doc See external documentation. -%%
Origin = ?wxHelpEvent_Origin_Unknown | ?wxHelpEvent_Origin_Keyboard | ?wxHelpEvent_Origin_HelpButton -doc """ Set the help event origin, only used internally by wxWidgets normally. See: `getOrigin/1` """. +%% Origin = ?wxHelpEvent_Origin_Unknown | ?wxHelpEvent_Origin_Keyboard | ?wxHelpEvent_Origin_HelpButton -spec setOrigin(This, Origin) -> 'ok' when This::wxHelpEvent(), Origin::wx:wx_enum(). setOrigin(#wx_ref{type=ThisT}=This,Origin) @@ -115,7 +108,6 @@ setOrigin(#wx_ref{type=ThisT}=This,Origin) ?CLASS(ThisT,wxHelpEvent), wxe_util:queue_cmd(This,Origin,?get_env(),?wxHelpEvent_SetOrigin). -%% @doc See external documentation. -doc "Sets the left-click position of the mouse, in screen coordinates.". -spec setPosition(This, Pt) -> 'ok' when This::wxHelpEvent(), Pt::{X::integer(), Y::integer()}. @@ -125,30 +117,21 @@ setPosition(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxHelpEvent_SetPosition). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxHtmlEasyPrinting.erl b/lib/wx/src/gen/wxHtmlEasyPrinting.erl index 268d2b490083..62a7a287ab0e 100644 --- a/lib/wx/src/gen/wxHtmlEasyPrinting.erl +++ b/lib/wx/src/gen/wxHtmlEasyPrinting.erl @@ -20,17 +20,15 @@ -module(wxHtmlEasyPrinting). -moduledoc """ -Functions for wxHtmlEasyPrinting class +This class provides very simple interface to printing architecture. -This class provides very simple interface to printing architecture. It allows -you to print HTML documents using only a few commands. +It allows you to print HTML documents using only a few commands. -Note: Do not create this class on the stack only. You should create an instance -on app startup and use this instance for all printing operations. The reason is -that this class stores various settings in it. +Note: Do not create this class on the stack only. You should create an instance on app +startup and use this instance for all printing operations. The reason is that this class +stores various settings in it. -wxWidgets docs: -[wxHtmlEasyPrinting](https://docs.wxwidgets.org/3.1/classwx_html_easy_printing.html) +wxWidgets docs: [wxHtmlEasyPrinting](https://docs.wxwidgets.org/3.2/classwx_html_easy_printing.html) """. -include("wxe.hrl"). -export([destroy/1,getPageSetupData/1,getPrintData/1,new/0,new/1,pageSetup/1, @@ -43,17 +41,15 @@ wxWidgets docs: -type wxHtmlEasyPrinting() :: wx:wx_object(). -export_type([wxHtmlEasyPrinting/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxHtmlEasyPrinting(). new() -> new([]). -%% @doc See external documentation. -doc "Constructor.". -spec new([Option]) -> wxHtmlEasyPrinting() when Option :: {'name', unicode:chardata()} @@ -67,7 +63,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxHtmlEasyPrinting_new), wxe_util:rec(?wxHtmlEasyPrinting_new). -%% @doc See external documentation. -doc """ Returns pointer to `m:wxPrintData` instance used by this class. @@ -80,7 +75,6 @@ getPrintData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlEasyPrinting_GetPrintData), wxe_util:rec(?wxHtmlEasyPrinting_GetPrintData). -%% @doc See external documentation. -doc """ Returns a pointer to `m:wxPageSetupDialogData` instance used by this class. @@ -93,12 +87,11 @@ getPageSetupData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlEasyPrinting_GetPageSetupData), wxe_util:rec(?wxHtmlEasyPrinting_GetPageSetupData). -%% @doc See external documentation. -doc """ Preview HTML file. -Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed -information about the kind of the error. +Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed information about the kind of the +error. """. -spec previewFile(This, Htmlfile) -> boolean() when This::wxHtmlEasyPrinting(), Htmlfile::unicode:chardata(). @@ -109,7 +102,7 @@ previewFile(#wx_ref{type=ThisT}=This,Htmlfile) wxe_util:queue_cmd(This,Htmlfile_UC,?get_env(),?wxHtmlEasyPrinting_PreviewFile), wxe_util:rec(?wxHtmlEasyPrinting_PreviewFile). -%% @equiv previewText(This,Htmltext, []) +-doc(#{equiv => previewText(This,Htmltext, [])}). -spec previewText(This, Htmltext) -> boolean() when This::wxHtmlEasyPrinting(), Htmltext::unicode:chardata(). @@ -117,12 +110,10 @@ previewText(This,Htmltext) when is_record(This, wx_ref),?is_chardata(Htmltext) -> previewText(This,Htmltext, []). -%% @doc See external documentation. -doc """ -Preview HTML text (not file\!). +Preview HTML text (not file!). -Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed -information about the kind of the error. +Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed information about the kind of the error. """. -spec previewText(This, Htmltext, [Option]) -> boolean() when This::wxHtmlEasyPrinting(), Htmltext::unicode:chardata(), @@ -137,12 +128,11 @@ previewText(#wx_ref{type=ThisT}=This,Htmltext, Options) wxe_util:queue_cmd(This,Htmltext_UC, Opts,?get_env(),?wxHtmlEasyPrinting_PreviewText), wxe_util:rec(?wxHtmlEasyPrinting_PreviewText). -%% @doc See external documentation. -doc """ Print HTML file. -Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed -information about the kind of the error. +Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed information about the kind of the +error. """. -spec printFile(This, Htmlfile) -> boolean() when This::wxHtmlEasyPrinting(), Htmlfile::unicode:chardata(). @@ -153,7 +143,7 @@ printFile(#wx_ref{type=ThisT}=This,Htmlfile) wxe_util:queue_cmd(This,Htmlfile_UC,?get_env(),?wxHtmlEasyPrinting_PrintFile), wxe_util:rec(?wxHtmlEasyPrinting_PrintFile). -%% @equiv printText(This,Htmltext, []) +-doc(#{equiv => printText(This,Htmltext, [])}). -spec printText(This, Htmltext) -> boolean() when This::wxHtmlEasyPrinting(), Htmltext::unicode:chardata(). @@ -161,12 +151,10 @@ printText(This,Htmltext) when is_record(This, wx_ref),?is_chardata(Htmltext) -> printText(This,Htmltext, []). -%% @doc See external documentation. -doc """ -Print HTML text (not file\!). +Print HTML text (not file!). -Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed -information about the kind of the error. +Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed information about the kind of the error. """. -spec printText(This, Htmltext, [Option]) -> boolean() when This::wxHtmlEasyPrinting(), Htmltext::unicode:chardata(), @@ -181,7 +169,6 @@ printText(#wx_ref{type=ThisT}=This,Htmltext, Options) wxe_util:queue_cmd(This,Htmltext_UC, Opts,?get_env(),?wxHtmlEasyPrinting_PrintText), wxe_util:rec(?wxHtmlEasyPrinting_PrintText). -%% @doc See external documentation. -doc "Display page setup dialog and allows the user to modify settings.". -spec pageSetup(This) -> 'ok' when This::wxHtmlEasyPrinting(). @@ -189,7 +176,7 @@ pageSetup(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxHtmlEasyPrinting), wxe_util:queue_cmd(This,?get_env(),?wxHtmlEasyPrinting_PageSetup). -%% @equiv setFonts(This,Normal_face,Fixed_face, []) +-doc(#{equiv => setFonts(This,Normal_face,Fixed_face, [])}). -spec setFonts(This, Normal_face, Fixed_face) -> 'ok' when This::wxHtmlEasyPrinting(), Normal_face::unicode:chardata(), Fixed_face::unicode:chardata(). @@ -197,12 +184,10 @@ setFonts(This,Normal_face,Fixed_face) when is_record(This, wx_ref),?is_chardata(Normal_face),?is_chardata(Fixed_face) -> setFonts(This,Normal_face,Fixed_face, []). -%% @doc See external documentation. -doc """ Sets fonts. -See `wxHtmlDCRenderer::SetFonts` (not implemented in wx) for detailed -description. +See `wxHtmlDCRenderer::SetFonts` (not implemented in wx) for detailed description. """. -spec setFonts(This, Normal_face, Fixed_face, [Option]) -> 'ok' when This::wxHtmlEasyPrinting(), Normal_face::unicode:chardata(), Fixed_face::unicode:chardata(), @@ -217,7 +202,7 @@ setFonts(#wx_ref{type=ThisT}=This,Normal_face,Fixed_face, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Normal_face_UC,Fixed_face_UC, Opts,?get_env(),?wxHtmlEasyPrinting_SetFonts). -%% @equiv setHeader(This,Header, []) +-doc(#{equiv => setHeader(This,Header, [])}). -spec setHeader(This, Header) -> 'ok' when This::wxHtmlEasyPrinting(), Header::unicode:chardata(). @@ -225,11 +210,20 @@ setHeader(This,Header) when is_record(This, wx_ref),?is_chardata(Header) -> setHeader(This,Header, []). -%% @doc See external documentation. -doc """ Set page header. The following macros can be used inside it: + +* @DATE@ is replaced by the current date in default format + +* @PAGENUM@ is replaced by page number + +* @PAGESCNT@ is replaced by total number of pages + +* @TIME@ is replaced by the current time in default format + +* @TITLE@ is replaced with the title of the document """. -spec setHeader(This, Header, [Option]) -> 'ok' when This::wxHtmlEasyPrinting(), Header::unicode:chardata(), @@ -243,7 +237,7 @@ setHeader(#wx_ref{type=ThisT}=This,Header, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Header_UC, Opts,?get_env(),?wxHtmlEasyPrinting_SetHeader). -%% @equiv setFooter(This,Footer, []) +-doc(#{equiv => setFooter(This,Footer, [])}). -spec setFooter(This, Footer) -> 'ok' when This::wxHtmlEasyPrinting(), Footer::unicode:chardata(). @@ -251,14 +245,13 @@ setFooter(This,Footer) when is_record(This, wx_ref),?is_chardata(Footer) -> setFooter(This,Footer, []). -%% @doc See external documentation. -doc """ Set page footer. -The following macros can be used inside it: @DATE@ is replaced by the current -date in default format @PAGENUM@ is replaced by page number @PAGESCNT@ is -replaced by total number of pages @TIME@ is replaced by the current time in -default format @TITLE@ is replaced with the title of the document +The following macros can be used inside it: @DATE@ is replaced by the current date in +default format @PAGENUM@ is replaced by page number @PAGESCNT@ is replaced by total number +of pages @TIME@ is replaced by the current time in default format @TITLE@ is replaced with +the title of the document """. -spec setFooter(This, Footer, [Option]) -> 'ok' when This::wxHtmlEasyPrinting(), Footer::unicode:chardata(), @@ -272,8 +265,7 @@ setFooter(#wx_ref{type=ThisT}=This,Footer, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Footer_UC, Opts,?get_env(),?wxHtmlEasyPrinting_SetFooter). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxHtmlEasyPrinting()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxHtmlEasyPrinting), diff --git a/lib/wx/src/gen/wxHtmlLinkEvent.erl b/lib/wx/src/gen/wxHtmlLinkEvent.erl index d9b70dae092c..360e8ff47b5a 100644 --- a/lib/wx/src/gen/wxHtmlLinkEvent.erl +++ b/lib/wx/src/gen/wxHtmlLinkEvent.erl @@ -20,21 +20,19 @@ -module(wxHtmlLinkEvent). -moduledoc """ -Functions for wxHtmlLinkEvent class - This event class is used for the events generated by `m:wxHtmlWindow`. -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxHtmlLinkEvent](https://docs.wxwidgets.org/3.1/classwx_html_link_event.html) +wxWidgets docs: [wxHtmlLinkEvent](https://docs.wxwidgets.org/3.2/classwx_html_link_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxHtmlLinkEventType`](`t:wxHtmlLinkEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxHtmlLinkEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getLinkInfo/1]). @@ -49,16 +47,14 @@ this type. -include("wx.hrl"). -type wxHtmlLinkEventType() :: 'command_html_link_clicked' | 'html_cell_clicked' | 'html_cell_hover'. -export_type([wxHtmlLinkEvent/0, wxHtmlLink/0, wxHtmlLinkEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc """ -Returns the [`wx_wxHtmlLinkInfo()`](`t:wx:wx_wxHtmlLinkInfo/0`) which contains -info about the cell clicked and the hyperlink it contains. +Returns the `wx_wxHtmlLinkInfo()` which contains info about the cell clicked and the +hyperlink it contains. """. -spec getLinkInfo(This) -> wx:wx_wxHtmlLinkInfo() when This::wxHtmlLinkEvent(). @@ -68,58 +64,40 @@ getLinkInfo(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxHtmlLinkEvent_GetLinkInfo). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxHtmlWindow.erl b/lib/wx/src/gen/wxHtmlWindow.erl index 786019bc452c..6bd83ed05924 100644 --- a/lib/wx/src/gen/wxHtmlWindow.erl +++ b/lib/wx/src/gen/wxHtmlWindow.erl @@ -20,43 +20,56 @@ -module(wxHtmlWindow). -moduledoc """ -Functions for wxHtmlWindow class - -`m:wxHtmlWindow` is probably the only class you will directly use unless you -want to do something special (like adding new tag handlers or MIME filters). +`m:wxHtmlWindow` is probably the only class you will directly use unless you want to do +something special (like adding new tag handlers or MIME filters). The purpose of this class is to display rich content pages (either local file or -downloaded via HTTP protocol) in a window based on a subset of the HTML -standard. The width of the window is constant, given in the constructor and -virtual height is changed dynamically depending on page size. Once the window is -created you can set its content by calling `setPage/2` with raw HTML, -`loadPage/2` with a `wxFileSystem` (not implemented in wx) location or -`loadFile/2` with a filename. +downloaded via HTTP protocol) in a window based on a subset of the HTML standard. The +width of the window is constant, given in the constructor and virtual height is changed +dynamically depending on page size. Once the window is created you can set its content by +calling `setPage/2` with raw HTML, `loadPage/2` with a `wxFileSystem` (not implemented in wx) location or `loadFile/2` with a filename. -Note: If you want complete HTML/CSS support as well as a Javascript engine, -consider using `m:wxWebView` instead. +Note: If you want complete HTML/CSS support as well as a Javascript engine, consider +using `m:wxWebView` instead. -`m:wxHtmlWindow` uses the `m:wxImage` class for displaying images, so you need -to initialize the handlers for any image formats you use before loading a page. -See ?wxInitAllImageHandlers and `wxImage::AddHandler` (not implemented in wx). +`m:wxHtmlWindow` uses the `m:wxImage` class for displaying images, so you need to +initialize the handlers for any image formats you use before loading a page. See +?wxInitAllImageHandlers and `wxImage::AddHandler` (not implemented in wx). -Styles +## Styles This class supports the following styles: -See: `m:wxHtmlLinkEvent`, `wxHtmlCellEvent` (not implemented in wx) +* wxHW_SCROLLBAR_NEVER: Never display scrollbars, not even when the page is larger than the +window. + +* wxHW_SCROLLBAR_AUTO: Display scrollbars only if page's size exceeds window's size. + +* wxHW_NO_SELECTION: Don't allow the user to select text. + +See: `m:wxHtmlLinkEvent` + +This class is derived, and can use functions, from: + +* `m:wxScrolledWindow` + +* `m:wxPanel` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxScrolledWindow` -`m:wxPanel` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxHtmlWindow](https://docs.wxwidgets.org/3.1/classwx_html_window.html) +wxWidgets docs: [wxHtmlWindow](https://docs.wxwidgets.org/3.2/classwx_html_window.html) ## Events -Event types emitted from this class: [`html_cell_clicked`](`m:wxHtmlLinkEvent`), -[`html_cell_hover`](`m:wxHtmlLinkEvent`), -[`command_html_link_clicked`](`m:wxHtmlLinkEvent`) +Event types emitted from this class: + +* [`html_cell_clicked`](`m:wxHtmlLinkEvent`) + +* [`html_cell_hover`](`m:wxHtmlLinkEvent`) + +* [`command_html_link_clicked`](`m:wxHtmlLinkEvent`) """. -include("wxe.hrl"). -export([appendToPage/2,destroy/1,getOpenedAnchor/1,getOpenedPage/1,getOpenedPageTitle/1, @@ -110,7 +123,6 @@ Event types emitted from this class: [`html_cell_clicked`](`m:wxHtmlLinkEvent`), -type wxHtmlWindow() :: wx:wx_object(). -export_type([wxHtmlWindow/0]). -%% @hidden -doc false. parent_class(wxScrolledWindow) -> true; parent_class(wxPanel) -> true; @@ -118,14 +130,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See external documentation. -doc "Default ctor.". -spec new() -> wxHtmlWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxHtmlWindow_new_0), wxe_util:rec(?wxHtmlWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxHtmlWindow() when Parent::wxWindow:wxWindow(). @@ -133,12 +144,11 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See external documentation. -doc """ Constructor. -The parameters are the same as `wxScrolled::wxScrolled()` (not implemented in -wx) constructor. +The parameters are the same as `wxScrolled::wxScrolled()` (not implemented in wx) +constructor. """. -spec new(Parent, [Option]) -> wxHtmlWindow() when Parent::wxWindow:wxWindow(), @@ -158,7 +168,6 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxHtmlWindow_new_2), wxe_util:rec(?wxHtmlWindow_new_2). -%% @doc See external documentation. -doc """ Appends HTML fragment to currently displayed text and refreshes the window. @@ -173,12 +182,11 @@ appendToPage(#wx_ref{type=ThisT}=This,Source) wxe_util:queue_cmd(This,Source_UC,?get_env(),?wxHtmlWindow_AppendToPage), wxe_util:rec(?wxHtmlWindow_AppendToPage). -%% @doc See external documentation. -doc """ Returns anchor within currently opened page (see `getOpenedPage/1`). -If no page is opened or if the displayed page wasn't produced by call to -`loadPage/2`, empty string is returned. +If no page is opened or if the displayed page wasn't produced by call to `loadPage/2`, empty string +is returned. """. -spec getOpenedAnchor(This) -> unicode:charlist() when This::wxHtmlWindow(). @@ -187,12 +195,11 @@ getOpenedAnchor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_GetOpenedAnchor), wxe_util:rec(?wxHtmlWindow_GetOpenedAnchor). -%% @doc See external documentation. -doc """ Returns full location of the opened page. -If no page is opened or if the displayed page wasn't produced by call to -`loadPage/2`, empty string is returned. +If no page is opened or if the displayed page wasn't produced by call to `loadPage/2`, empty string +is returned. """. -spec getOpenedPage(This) -> unicode:charlist() when This::wxHtmlWindow(). @@ -201,10 +208,9 @@ getOpenedPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_GetOpenedPage), wxe_util:rec(?wxHtmlWindow_GetOpenedPage). -%% @doc See external documentation. -doc """ -Returns title of the opened page or wxEmptyString if the current page does not -contain tag. +Returns title of the opened page or wxEmptyString if the current page does not contain +*<TITLE>* tag. """. -spec getOpenedPageTitle(This) -> unicode:charlist() when This::wxHtmlWindow(). @@ -213,7 +219,6 @@ getOpenedPageTitle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_GetOpenedPageTitle), wxe_util:rec(?wxHtmlWindow_GetOpenedPageTitle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowgetrelatedframe">external documentation</a>. -doc "Returns the related frame.". -spec getRelatedFrame(This) -> wxFrame:wxFrame() when This::wxHtmlWindow(). @@ -222,7 +227,6 @@ getRelatedFrame(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_GetRelatedFrame), wxe_util:rec(?wxHtmlWindow_GetRelatedFrame). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowhistoryback">external documentation</a>. -doc """ Moves back to the previous page. @@ -235,7 +239,6 @@ historyBack(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_HistoryBack), wxe_util:rec(?wxHtmlWindow_HistoryBack). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowhistorycanback">external documentation</a>. -doc """ Returns true if it is possible to go back in the history i.e. @@ -248,7 +251,6 @@ historyCanBack(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_HistoryCanBack), wxe_util:rec(?wxHtmlWindow_HistoryCanBack). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowhistorycanforward">external documentation</a>. -doc """ Returns true if it is possible to go forward in the history i.e. @@ -261,7 +263,6 @@ historyCanForward(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_HistoryCanForward), wxe_util:rec(?wxHtmlWindow_HistoryCanForward). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowhistoryclear">external documentation</a>. -doc "Clears history.". -spec historyClear(This) -> 'ok' when This::wxHtmlWindow(). @@ -269,7 +270,6 @@ historyClear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_HistoryClear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowhistoryforward">external documentation</a>. -doc """ Moves to next page in history. @@ -282,7 +282,6 @@ historyForward(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_HistoryForward), wxe_util:rec(?wxHtmlWindow_HistoryForward). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowloadfile">external documentation</a>. -doc """ Loads an HTML page from a file and displays it. @@ -299,10 +298,9 @@ loadFile(#wx_ref{type=ThisT}=This,Filename) wxe_util:queue_cmd(This,Filename_UC,?get_env(),?wxHtmlWindow_LoadFile), wxe_util:rec(?wxHtmlWindow_LoadFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowloadpage">external documentation</a>. -doc """ -Unlike `setPage/2` this function first loads the HTML page from `location` and -then displays it. +Unlike `setPage/2` this function first loads the HTML page from `location` and then +displays it. Return: false if an error occurred, true otherwise @@ -317,11 +315,13 @@ loadPage(#wx_ref{type=ThisT}=This,Location) wxe_util:queue_cmd(This,Location_UC,?get_env(),?wxHtmlWindow_LoadPage), wxe_util:rec(?wxHtmlWindow_LoadPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowselectall">external documentation</a>. -doc """ Selects all text in the window. -See: `selectLine/2`, `selectWord/2` +See: +* `selectLine/2` + +* `selectWord/2` """. -spec selectAll(This) -> 'ok' when This::wxHtmlWindow(). @@ -329,7 +329,6 @@ selectAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_SelectAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowselectiontotext">external documentation</a>. -doc """ Returns the current selection as plain text. @@ -342,15 +341,16 @@ selectionToText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_SelectionToText), wxe_util:rec(?wxHtmlWindow_SelectionToText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowselectline">external documentation</a>. -doc """ Selects the line of text that `pos` points at. -Note that `pos` is relative to the top of displayed page, not to window's -origin, use `wxScrolledWindow:calcUnscrolledPosition/3` to convert physical -coordinate. +Note that `pos` is relative to the top of displayed page, not to window's origin, use `wxScrolledWindow:calcUnscrolledPosition/3` to +convert physical coordinate. -See: `selectAll/1`, `selectWord/2` +See: +* `selectAll/1` + +* `selectWord/2` """. -spec selectLine(This, Pos) -> 'ok' when This::wxHtmlWindow(), Pos::{X::integer(), Y::integer()}. @@ -359,15 +359,16 @@ selectLine(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos) ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,Pos,?get_env(),?wxHtmlWindow_SelectLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowselectword">external documentation</a>. -doc """ Selects the word at position `pos`. -Note that `pos` is relative to the top of displayed page, not to window's -origin, use `wxScrolledWindow:calcUnscrolledPosition/3` to convert physical -coordinate. +Note that `pos` is relative to the top of displayed page, not to window's origin, use `wxScrolledWindow:calcUnscrolledPosition/3` to +convert physical coordinate. + +See: +* `selectAll/1` -See: `selectAll/1`, `selectLine/2` +* `selectLine/2` """. -spec selectWord(This, Pos) -> 'ok' when This::wxHtmlWindow(), Pos::{X::integer(), Y::integer()}. @@ -376,7 +377,6 @@ selectWord(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos) ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,Pos,?get_env(),?wxHtmlWindow_SelectWord). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetborders">external documentation</a>. -doc """ This function sets the space between border of window and HTML contents. @@ -389,7 +389,7 @@ setBorders(#wx_ref{type=ThisT}=This,B) ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,B,?get_env(),?wxHtmlWindow_SetBorders). -%% @equiv setFonts(This,Normal_face,Fixed_face, []) +-doc(#{equiv => setFonts(This,Normal_face,Fixed_face, [])}). -spec setFonts(This, Normal_face, Fixed_face) -> 'ok' when This::wxHtmlWindow(), Normal_face::unicode:chardata(), Fixed_face::unicode:chardata(). @@ -397,14 +397,10 @@ setFonts(This,Normal_face,Fixed_face) when is_record(This, wx_ref),?is_chardata(Normal_face),?is_chardata(Fixed_face) -> setFonts(This,Normal_face,Fixed_face, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetfonts">external documentation</a>. -doc """ This function sets font sizes and faces. -See `wxHtmlDCRenderer::SetFonts` (not implemented in wx) for detailed -description. - -See: SetSize() +See `wxHtmlDCRenderer::SetFonts` (not implemented in wx) for detailed description. """. -spec setFonts(This, Normal_face, Fixed_face, [Option]) -> 'ok' when This::wxHtmlWindow(), Normal_face::unicode:chardata(), Fixed_face::unicode:chardata(), @@ -419,7 +415,6 @@ setFonts(#wx_ref{type=ThisT}=This,Normal_face,Fixed_face, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Normal_face_UC,Fixed_face_UC, Opts,?get_env(),?wxHtmlWindow_SetFonts). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetpage">external documentation</a>. -doc """ Sets the source of a page and displays it, for example: @@ -436,12 +431,11 @@ setPage(#wx_ref{type=ThisT}=This,Source) wxe_util:queue_cmd(This,Source_UC,?get_env(),?wxHtmlWindow_SetPage), wxe_util:rec(?wxHtmlWindow_SetPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetrelatedframe">external documentation</a>. -doc """ Sets the frame in which page title will be displayed. -`format` is the format of the frame title, e.g. "HtmlHelp : %s". It must contain -exactly one s. This s is substituted with HTML page title. +`format` is the format of the frame title, e.g. "HtmlHelp : %s". It must contain exactly +one s. This s is substituted with HTML page title. """. -spec setRelatedFrame(This, Frame, Format) -> 'ok' when This::wxHtmlWindow(), Frame::wxFrame:wxFrame(), Format::unicode:chardata(). @@ -452,14 +446,9 @@ setRelatedFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame,Format) Format_UC = unicode:characters_to_binary(Format), wxe_util:queue_cmd(This,Frame,Format_UC,?get_env(),?wxHtmlWindow_SetRelatedFrame). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetrelatedstatusbar">external documentation</a>. -%% <br /> Also:<br /> -%% setRelatedStatusBar(This, Index) -> 'ok' when<br /> -%% This::wxHtmlWindow(), Index::integer().<br /> -%% -doc """ -`After` calling `setRelatedFrame/3`, this sets statusbar slot where messages -will be displayed. +`After` calling `setRelatedFrame/3`, this sets statusbar slot where messages will be +displayed. (Default is -1 = no messages.) """. @@ -476,12 +465,10 @@ setRelatedStatusBar(#wx_ref{type=ThisT}=This,Index) ?CLASS(ThisT,wxHtmlWindow), wxe_util:queue_cmd(This,Index,?get_env(),?wxHtmlWindow_SetRelatedStatusBar_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowsetrelatedstatusbar">external documentation</a>. -doc """ `Sets` the associated statusbar where messages will be displayed. -Call this instead of `setRelatedFrame/3` if you want statusbar updates only, no -changing of the frame title. +Call this instead of `setRelatedFrame/3` if you want statusbar updates only, no changing of the frame title. Since: 2.9.0 """. @@ -497,7 +484,6 @@ setRelatedStatusBar(#wx_ref{type=ThisT}=This,#wx_ref{type=StatusbarT}=Statusbar, Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Statusbar, Opts,?get_env(),?wxHtmlWindow_SetRelatedStatusBar_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxhtmlwindow.html#wxhtmlwindowtotext">external documentation</a>. -doc "Returns content of currently displayed page as plain text.". -spec toText(This) -> unicode:charlist() when This::wxHtmlWindow(). @@ -506,611 +492,411 @@ toText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxHtmlWindow_ToText), wxe_util:rec(?wxHtmlWindow_ToText). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxHtmlWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxHtmlWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxScrolledWindow -%% @hidden -doc false. setTargetWindow(This,Window) -> wxScrolledWindow:setTargetWindow(This,Window). -%% @hidden -doc false. setScrollRate(This,Xstep,Ystep) -> wxScrolledWindow:setScrollRate(This,Xstep,Ystep). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY). -%% @hidden -doc false. scroll(This,X,Y) -> wxScrolledWindow:scroll(This,X,Y). -%% @hidden -doc false. scroll(This,Pt) -> wxScrolledWindow:scroll(This,Pt). -%% @hidden -doc false. prepareDC(This,Dc) -> wxScrolledWindow:prepareDC(This,Dc). -%% @hidden -doc false. doPrepareDC(This,Dc) -> wxScrolledWindow:doPrepareDC(This,Dc). -%% @hidden -doc false. getViewStart(This) -> wxScrolledWindow:getViewStart(This). -%% @hidden -doc false. getScrollPixelsPerUnit(This) -> wxScrolledWindow:getScrollPixelsPerUnit(This). -%% @hidden -doc false. enableScrolling(This,XScrolling,YScrolling) -> wxScrolledWindow:enableScrolling(This,XScrolling,YScrolling). -%% @hidden -doc false. calcUnscrolledPosition(This,X,Y) -> wxScrolledWindow:calcUnscrolledPosition(This,X,Y). -%% @hidden -doc false. calcUnscrolledPosition(This,Pt) -> wxScrolledWindow:calcUnscrolledPosition(This,Pt). -%% @hidden -doc false. calcScrolledPosition(This,X,Y) -> wxScrolledWindow:calcScrolledPosition(This,X,Y). -%% @hidden -doc false. calcScrolledPosition(This,Pt) -> wxScrolledWindow:calcScrolledPosition(This,Pt). %% From wxPanel -%% @hidden -doc false. setFocusIgnoringChildren(This) -> wxPanel:setFocusIgnoringChildren(This). -%% @hidden -doc false. initDialog(This) -> wxPanel:initDialog(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxIcon.erl b/lib/wx/src/gen/wxIcon.erl index 350b22ef1077..5e2ccf683597 100644 --- a/lib/wx/src/gen/wxIcon.erl +++ b/lib/wx/src/gen/wxIcon.erl @@ -20,40 +20,43 @@ -module(wxIcon). -moduledoc """ -Functions for wxIcon class - -An icon is a small rectangular bitmap usually used for denoting a minimized -application. - -It differs from a `m:wxBitmap` in always having a mask associated with it for -transparent drawing. On some platforms, icons and bitmaps are implemented -identically, since there is no real distinction between a `m:wxBitmap` with a -mask and an icon; and there is no specific icon format on some platforms -(X-based applications usually standardize on XPMs for small bitmaps and icons). -However, some platforms (such as Windows) make the distinction, so a separate -class is provided. - -Remark: It is usually desirable to associate a pertinent icon with a frame. -Icons can also be used for other purposes, for example with `m:wxTreeCtrl` and -`m:wxListCtrl`. Icons have different formats on different platforms therefore -separate icons will usually be created for the different environments. -Platform-specific methods for creating a `m:wxIcon` structure are catered for, -and this is an occasion where conditional compilation will probably be required. -Note that a new icon must be created for every time the icon is to be used for a -new window. In Windows, the icon will not be reloaded if it has already been -used. An icon allocated to a frame will be deleted when the frame is deleted. -For more information please see overview_bitmap. +An icon is a small rectangular bitmap usually used for denoting a minimized application. + +It differs from a `m:wxBitmap` in always having a mask associated with it for transparent +drawing. On some platforms, icons and bitmaps are implemented identically, since there is +no real distinction between a `m:wxBitmap` with a mask and an icon; and there is no +specific icon format on some platforms (X-based applications usually standardize on XPMs +for small bitmaps and icons). However, some platforms (such as Windows) make the +distinction, so a separate class is provided. + +Remark: It is usually desirable to associate a pertinent icon with a frame. Icons can +also be used for other purposes, for example with `m:wxTreeCtrl` and `m:wxListCtrl`. Icons +have different formats on different platforms therefore separate icons will usually be +created for the different environments. Platform-specific methods for creating a `m:wxIcon` +structure are catered for, and this is an occasion where conditional compilation will +probably be required. Note that a new icon must be created for every time the icon is to +be used for a new window. In Windows, the icon will not be reloaded if it has already been +used. An icon allocated to a frame will be deleted when the frame is deleted. For more +information please see overview_bitmap. Predefined objects (include wx.hrl): ?wxNullIcon See: -[Overview bitmap](https://docs.wxwidgets.org/3.1/overview_bitmap.html#overview_bitmap), -[Overview bitmap](https://docs.wxwidgets.org/3.1/overview_bitmap.html#overview_bitmap_supportedformats), -`m:wxIconBundle`, `wxDC:drawIcon/3`, `m:wxCursor` +* [Overview bitmap](https://docs.wxwidgets.org/3.2/overview_bitmap.html#overview_bitmap) -This class is derived (and can use functions) from: `m:wxBitmap` +* [Overview bitmap](https://docs.wxwidgets.org/3.2/overview_bitmap.html#overview_bitmap_supportedformats) -wxWidgets docs: [wxIcon](https://docs.wxwidgets.org/3.1/classwx_icon.html) +* `m:wxIconBundle` + +* `wxDC:drawIcon/3` + +* `m:wxCursor` + +This class is derived, and can use functions, from: + +* `m:wxBitmap` + +wxWidgets docs: [wxIcon](https://docs.wxwidgets.org/3.2/classwx_icon.html) """. -include("wxe.hrl"). -export([copyFromBitmap/2,destroy/1,new/0,new/1,new/2]). @@ -66,30 +69,23 @@ wxWidgets docs: [wxIcon](https://docs.wxwidgets.org/3.1/classwx_icon.html) -type wxIcon() :: wx:wx_object(). -export_type([wxIcon/0]). -%% @hidden -doc false. parent_class(wxBitmap) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxicon.html#wxiconwxicon">external documentation</a>. -doc """ Default ctor. -Constructs an icon object with no data; an assignment or another member function -such as `wxBitmap:loadFile/3` must be called subsequently. +Constructs an icon object with no data; an assignment or another member function such as `wxBitmap:loadFile/3` +must be called subsequently. """. -spec new() -> wxIcon(). new() -> wxe_util:queue_cmd(?get_env(), ?wxIcon_new_0), wxe_util:rec(?wxIcon_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxicon.html#wxiconwxicon">external documentation</a>. -%% <br /> Also:<br /> -%% new(Icon) -> wxIcon() when<br /> -%% Icon::wxIcon().<br /> -%% -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc "Copy ctor.". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Name) -> wxIcon() when Name::unicode:chardata(); (Icon) -> wxIcon() when @@ -103,13 +99,12 @@ new(#wx_ref{type=IconT}=Icon) -> wxe_util:queue_cmd(Icon,?get_env(),?wxIcon_new_1), wxe_util:rec(?wxIcon_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxicon.html#wxiconwxicon">external documentation</a>. -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Loads an icon from a file or resource. See: `wxBitmap:loadFile/3` """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Name, [Option]) -> wxIcon() when Name::unicode:chardata(), Option :: {'type', wx:wx_enum()} @@ -126,7 +121,6 @@ new(Name, Options) wxe_util:queue_cmd(Name_UC, Opts,?get_env(),?wxIcon_new_2), wxe_util:rec(?wxIcon_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxicon.html#wxiconcopyfrombitmap">external documentation</a>. -doc """ Copies `bmp` bitmap to this icon. @@ -141,77 +135,48 @@ copyFromBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=BmpT}=Bmp) -> ?CLASS(BmpT,wxBitmap), wxe_util:queue_cmd(This,Bmp,?get_env(),?wxIcon_CopyFromBitmap). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See overview_refcount_destruct for more info. - -If the application omits to delete the icon explicitly, the icon will be -destroyed automatically by wxWidgets when the application exits. - -Warning: Do not delete an icon that is selected into a memory device context. -""". +-doc "Destroys the object". -spec destroy(This::wxIcon()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxIcon), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBitmap -%% @hidden -doc false. setWidth(This,Width) -> wxBitmap:setWidth(This,Width). -%% @hidden -doc false. setPalette(This,Palette) -> wxBitmap:setPalette(This,Palette). -%% @hidden -doc false. setMask(This,Mask) -> wxBitmap:setMask(This,Mask). -%% @hidden -doc false. setHeight(This,Height) -> wxBitmap:setHeight(This,Height). -%% @hidden -doc false. setDepth(This,Depth) -> wxBitmap:setDepth(This,Depth). -%% @hidden -doc false. saveFile(This,Name,Type, Options) -> wxBitmap:saveFile(This,Name,Type, Options). -%% @hidden -doc false. saveFile(This,Name,Type) -> wxBitmap:saveFile(This,Name,Type). -%% @hidden -doc false. isOk(This) -> wxBitmap:isOk(This). -%% @hidden -doc false. ok(This) -> wxBitmap:ok(This). -%% @hidden -doc false. loadFile(This,Name, Options) -> wxBitmap:loadFile(This,Name, Options). -%% @hidden -doc false. loadFile(This,Name) -> wxBitmap:loadFile(This,Name). -%% @hidden -doc false. getSubBitmap(This,Rect) -> wxBitmap:getSubBitmap(This,Rect). -%% @hidden -doc false. getWidth(This) -> wxBitmap:getWidth(This). -%% @hidden -doc false. getMask(This) -> wxBitmap:getMask(This). -%% @hidden -doc false. getPalette(This) -> wxBitmap:getPalette(This). -%% @hidden -doc false. getHeight(This) -> wxBitmap:getHeight(This). -%% @hidden -doc false. getDepth(This) -> wxBitmap:getDepth(This). -%% @hidden -doc false. copyFromIcon(This,Icon) -> wxBitmap:copyFromIcon(This,Icon). -%% @hidden -doc false. convertToImage(This) -> wxBitmap:convertToImage(This). diff --git a/lib/wx/src/gen/wxIconBundle.erl b/lib/wx/src/gen/wxIconBundle.erl index c9593a6f35e4..1c45abf195a1 100644 --- a/lib/wx/src/gen/wxIconBundle.erl +++ b/lib/wx/src/gen/wxIconBundle.erl @@ -20,16 +20,13 @@ -module(wxIconBundle). -moduledoc """ -Functions for wxIconBundle class +This class contains multiple copies of an icon in different sizes. -This class contains multiple copies of an icon in different sizes. It is -typically used in `wxDialog::SetIcons` (not implemented in wx) and -`wxTopLevelWindow:setIcons/2`. +It is typically used in `wxDialog::SetIcons` (not implemented in wx) and `wxTopLevelWindow:setIcons/2`. Predefined objects (include wx.hrl): ?wxNullIconBundle -wxWidgets docs: -[wxIconBundle](https://docs.wxwidgets.org/3.1/classwx_icon_bundle.html) +wxWidgets docs: [wxIconBundle](https://docs.wxwidgets.org/3.2/classwx_icon_bundle.html) """. -include("wxe.hrl"). -export([addIcon/2,addIcon/3,destroy/1,getIcon/1,getIcon/2,getIcon/3,new/0,new/1, @@ -40,22 +37,15 @@ wxWidgets docs: -type wxIconBundle() :: wx:wx_object(). -export_type([wxIconBundle/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundlewxiconbundle">external documentation</a>. -doc "Default ctor.". -spec new() -> wxIconBundle(). new() -> wxe_util:queue_cmd(?get_env(), ?wxIconBundle_new_0), wxe_util:rec(?wxIconBundle_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundlewxiconbundle">external documentation</a>. -%% <br /> Also:<br /> -%% new(File) -> wxIconBundle() when<br /> -%% File::unicode:chardata().<br /> -%% -doc "Initializes the bundle with the icon(s) found in the file.". -spec new(Ic) -> wxIconBundle() when Ic::wxIconBundle:wxIconBundle() | wxIcon:wxIcon(); @@ -77,8 +67,8 @@ new(File) wxe_util:queue_cmd(File_UC,?get_env(),?wxIconBundle_new_1_1), wxe_util:rec(?wxIconBundle_new_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundlewxiconbundle">external documentation</a>. -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY +-doc "". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(File, Type) -> wxIconBundle() when File::unicode:chardata(), Type::wx:wx_enum(). new(File,Type) @@ -87,14 +77,9 @@ new(File,Type) wxe_util:queue_cmd(File_UC,Type,?get_env(),?wxIconBundle_new_2), wxe_util:rec(?wxIconBundle_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundleaddicon">external documentation</a>. -%% <br /> Also:<br /> -%% addIcon(This, Icon) -> 'ok' when<br /> -%% This::wxIconBundle(), Icon::wxIcon:wxIcon().<br /> -%% -doc """ -Adds the icon to the collection; if the collection already contains an icon with -the same width and height, it is replaced by the new one. +Adds the icon to the collection; if the collection already contains an icon with the same +width and height, it is replaced by the new one. """. -spec addIcon(This, File) -> 'ok' when This::wxIconBundle(), File::unicode:chardata(); @@ -110,8 +95,8 @@ addIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon) -> ?CLASS(IconT,wxIcon), wxe_util:queue_cmd(This,Icon,?get_env(),?wxIconBundle_AddIcon_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundleaddicon">external documentation</a>. -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY +-doc "". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec addIcon(This, File, Type) -> 'ok' when This::wxIconBundle(), File::unicode:chardata(), Type::wx:wx_enum(). addIcon(#wx_ref{type=ThisT}=This,File,Type) @@ -120,7 +105,7 @@ addIcon(#wx_ref{type=ThisT}=This,File,Type) File_UC = unicode:characters_to_binary(File), wxe_util:queue_cmd(This,File_UC,Type,?get_env(),?wxIconBundle_AddIcon_2). -%% @equiv getIcon(This, []) +-doc(#{equiv => getIcon(This, [])}). -spec getIcon(This) -> wxIcon:wxIcon() when This::wxIconBundle(). @@ -128,13 +113,6 @@ getIcon(This) when is_record(This, wx_ref) -> getIcon(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundlegeticon">external documentation</a>. -%% <br /> Also:<br /> -%% getIcon(This, [Option]) -> wxIcon:wxIcon() when<br /> -%% This::wxIconBundle(),<br /> -%% Option :: {'size', integer()}<br /> -%% | {'flags', integer()}.<br /> -%% -doc """ Same as. @@ -160,24 +138,20 @@ getIcon(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxIconBundle_GetIcon_1), wxe_util:rec(?wxIconBundle_GetIcon_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconbundle.html#wxiconbundlegeticon">external documentation</a>. -doc """ Returns the icon with the given size. -If `size` is ?wxDefaultSize, it is interpreted as the standard system icon size, -i.e. the size returned by `wxSystemSettings:getMetric/2` for `wxSYS_ICON_X` and -`wxSYS_ICON_Y`. - -If the bundle contains an icon with exactly the requested size, it's always -returned. Otherwise, the behaviour depends on the flags. If only -`wxIconBundle::FALLBACK_NONE` (not implemented in wx) is given, the function -returns an invalid icon. If `wxIconBundle::FALLBACK_SYSTEM` (not implemented in -wx) is given, it tries to find the icon of standard system size, regardless of -the size passed as parameter. Otherwise, or if the icon system size is not found -neither, but `wxIconBundle::FALLBACK_NEAREST_LARGER` (not implemented in wx) -flag is specified, the function returns the smallest icon of the size larger -than the requested one or, if this fails too, just the icon closest to the -specified size. +If `size` is ?wxDefaultSize, it is interpreted as the standard system icon size, i.e. the +size returned by `wxSystemSettings:getMetric/2` for `wxSYS_ICON_X` and `wxSYS_ICON_Y`. + +If the bundle contains an icon with exactly the requested size, it's always returned. +Otherwise, the behaviour depends on the flags. If only `wxIconBundle::FALLBACK_NONE` (not +implemented in wx) is given, the function returns an invalid icon. If `wxIconBundle::FALLBACK_SYSTEM` +(not implemented in wx) is given, it tries to find the icon of standard system size, +regardless of the size passed as parameter. Otherwise, or if the icon system size is not +found neither, but `wxIconBundle::FALLBACK_NEAREST_LARGER` (not implemented in wx) flag is +specified, the function returns the smallest icon of the size larger than the requested +one or, if this fails too, just the icon closest to the specified size. The `flags` parameter is available only since wxWidgets 2.9.4. """. @@ -193,8 +167,7 @@ getIcon(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size, Options) wxe_util:queue_cmd(This,Size, Opts,?get_env(),?wxIconBundle_GetIcon_2), wxe_util:rec(?wxIconBundle_GetIcon_2). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxIconBundle()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxIconBundle), diff --git a/lib/wx/src/gen/wxIconizeEvent.erl b/lib/wx/src/gen/wxIconizeEvent.erl index 3db18d168ba3..4210370965f0 100644 --- a/lib/wx/src/gen/wxIconizeEvent.erl +++ b/lib/wx/src/gen/wxIconizeEvent.erl @@ -20,24 +20,24 @@ -module(wxIconizeEvent). -moduledoc """ -Functions for wxIconizeEvent class - An event being sent when the frame is iconized (minimized) or restored. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxTopLevelWindow:iconize/2`, `wxTopLevelWindow:isIconized/1` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `wxTopLevelWindow:iconize/2` + +* `wxTopLevelWindow:isIconized/1` + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxIconizeEvent](https://docs.wxwidgets.org/3.1/classwx_iconize_event.html) +wxWidgets docs: [wxIconizeEvent](https://docs.wxwidgets.org/3.2/classwx_iconize_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxIconizeEventType`](`t:wxIconizeEventType/0`) to subscribe to events of this -type. +Use `wxEvtHandler:connect/3` with `wxIconizeEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([isIconized/1]). @@ -50,12 +50,10 @@ type. -include("wx.hrl"). -type wxIconizeEventType() :: 'iconize'. -export_type([wxIconizeEvent/0, wxIconize/0, wxIconizeEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxiconizeevent.html#wxiconizeeventisiconized">external documentation</a>. -doc "Returns true if the frame has been iconized, false if it has been restored.". -spec isIconized(This) -> boolean() when This::wxIconizeEvent(). @@ -65,30 +63,21 @@ isIconized(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxIconizeEvent_IsIconized). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxIdleEvent.erl b/lib/wx/src/gen/wxIdleEvent.erl index 288fa959dfaf..5fdcfd12b4ff 100644 --- a/lib/wx/src/gen/wxIdleEvent.erl +++ b/lib/wx/src/gen/wxIdleEvent.erl @@ -20,70 +20,66 @@ -module(wxIdleEvent). -moduledoc """ -Functions for wxIdleEvent class - -This class is used for idle events, which are generated when the system becomes -idle. Note that, unless you do something specifically, the idle events are not -sent if the system remains idle once it has become it, e.g. only a single idle -event will be generated until something else resulting in more normal events -happens and only then is the next idle event sent again. - -If you need to ensure a continuous stream of idle events, you can either use -`requestMore/2` method in your handler or call ?wxWakeUpIdle() periodically (for -example from a timer event handler), but note that both of these approaches (and -especially the first one) increase the system load and so should be avoided if -possible. - -By default, idle events are sent to all windows, including even the hidden ones -because they may be shown if some condition is met from their `wxEVT_IDLE` (or -related `wxEVT_UPDATE_UI`) handler. The children of hidden windows do not -receive idle events however as they can't change their state in any way -noticeable by the user. Finally, the global `wxApp` (not implemented in wx) -object also receives these events, as usual, so it can be used for any global -idle time processing. +This class is used for idle events, which are generated when the system becomes idle. + +Note that, unless you do something specifically, the idle events are not sent if the +system remains idle once it has become it, e.g. only a single idle event will be generated +until something else resulting in more normal events happens and only then is the next +idle event sent again. + +If you need to ensure a continuous stream of idle events, you can either use `requestMore/2` method in +your handler or call ?wxWakeUpIdle() periodically (for example from a timer event +handler), but note that both of these approaches (and especially the first one) increase +the system load and so should be avoided if possible. + +By default, idle events are sent to all windows, including even the hidden ones because +they may be shown if some condition is met from their `wxEVT_IDLE` (or related `wxEVT_UPDATE_UI`) +handler. The children of hidden windows do not receive idle events however as they can't +change their state in any way noticeable by the user. Finally, the global `wxApp` (not +implemented in wx) object also receives these events, as usual, so it can be used for any +global idle time processing. If sending idle events to all windows is causing a significant overhead in your -application, you can call `setMode/1` with the value wxIDLE_PROCESS_SPECIFIED, -and set the wxWS_EX_PROCESS_IDLE extra window style for every window which -should receive idle events, all the other ones will not receive them in this -case. +application, you can call `setMode/1` with the value wxIDLE_PROCESS_SPECIFIED, and set the +wxWS_EX_PROCESS_IDLE extra window style for every window which should receive idle events, +all the other ones will not receive them in this case. Delayed Action Mechanism -`m:wxIdleEvent` can be used to perform some action "at slightly later time". -This can be necessary in several circumstances when, for whatever reason, -something can't be done in the current event handler. For example, if a mouse -event handler is called with the mouse button pressed, the mouse can be -currently captured and some operations with it - notably capturing it again - -might be impossible or lead to undesirable results. If you still want to capture -it, you can do it from `wxEVT_IDLE` handler when it is called the next time +`m:wxIdleEvent` can be used to perform some action "at slightly later time". This can be +necessary in several circumstances when, for whatever reason, something can't be done in +the current event handler. For example, if a mouse event handler is called with the mouse +button pressed, the mouse can be currently captured and some operations with it - notably +capturing it again - might be impossible or lead to undesirable results. If you still want +to capture it, you can do it from `wxEVT_IDLE` handler when it is called the next time instead of doing it immediately. -This can be achieved in two different ways: when using static event tables, you -will need a flag indicating to the (always connected) idle event handler whether -the desired action should be performed. The originally called handler would then -set it to indicate that it should indeed be done and the idle handler itself -would reset it to prevent it from doing the same action again. +This can be achieved in two different ways: when using static event tables, you will need +a flag indicating to the (always connected) idle event handler whether the desired action +should be performed. The originally called handler would then set it to indicate that it +should indeed be done and the idle handler itself would reset it to prevent it from doing +the same action again. -Using dynamically connected event handlers things are even simpler as the -original event handler can simply `wxEvtHandler::Connect()` (not implemented in -wx) or `wxEvtHandler::Bind()` (not implemented in wx) the idle event handler -which would only be executed then and could `wxEvtHandler::Disconnect()` (not -implemented in wx) or `wxEvtHandler::Unbind()` (not implemented in wx) itself. +Using dynamically connected event handlers things are even simpler as the original event +handler can simply `wxEvtHandler::Connect()` (not implemented in wx) or `wxEvtHandler::Bind()` +(not implemented in wx) the idle event handler which would only be executed then and +could `wxEvtHandler::Disconnect()` (not implemented in wx) or `wxEvtHandler::Unbind()` +(not implemented in wx) itself. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxUpdateUIEvent`, `wxWindow::OnInternalIdle` (not implemented in wx) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxUpdateUIEvent` -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxIdleEvent](https://docs.wxwidgets.org/3.1/classwx_idle_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxIdleEvent](https://docs.wxwidgets.org/3.2/classwx_idle_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxIdleEventType`](`t:wxIdleEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxIdleEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getMode/0,moreRequested/1,requestMore/1,requestMore/2,setMode/1]). @@ -96,26 +92,23 @@ subscribe to events of this type. -include("wx.hrl"). -type wxIdleEventType() :: 'idle'. -export_type([wxIdleEvent/0, wxIdle/0, wxIdleEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxidleevent.html#wxidleeventgetmode">external documentation</a>. -%%<br /> Res = ?wxIDLE_PROCESS_ALL | ?wxIDLE_PROCESS_SPECIFIED -doc """ -Static function returning a value specifying how wxWidgets will send idle -events: to all windows, or only to those which specify that they will process -the events. +Static function returning a value specifying how wxWidgets will send idle events: to all +windows, or only to those which specify that they will process the events. See: `setMode/1` """. +%% Res = ?wxIDLE_PROCESS_ALL | ?wxIDLE_PROCESS_SPECIFIED -spec getMode() -> wx:wx_enum(). getMode() -> wxe_util:queue_cmd(?get_env(), ?wxIdleEvent_GetMode), wxe_util:rec(?wxIdleEvent_GetMode). -%% @equiv requestMore(This, []) +-doc(#{equiv => requestMore(This, [])}). -spec requestMore(This) -> 'ok' when This::wxIdleEvent(). @@ -123,17 +116,15 @@ requestMore(This) when is_record(This, wx_ref) -> requestMore(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxidleevent.html#wxidleeventrequestmore">external documentation</a>. -doc """ Tells wxWidgets that more processing is required. -This function can be called by an OnIdle handler for a window or window event -handler to indicate that wxApp::OnIdle should forward the OnIdle event once more -to the application windows. +This function can be called by an OnIdle handler for a window or window event handler to +indicate that wxApp::OnIdle should forward the OnIdle event once more to the application windows. -If no window calls this function during OnIdle, then the application will remain -in a passive event loop (not calling OnIdle) until a new event is posted to the -application by the windowing system. +If no window calls this function during OnIdle, then the application will remain in a +passive event loop (not calling OnIdle) until a new event is posted to the application by +the windowing system. See: `moreRequested/1` """. @@ -148,10 +139,8 @@ requestMore(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxIdleEvent_RequestMore). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxidleevent.html#wxidleeventmorerequested">external documentation</a>. -doc """ -Returns true if the OnIdle function processing this event requested more -processing time. +Returns true if the OnIdle function processing this event requested more processing time. See: `requestMore/2` """. @@ -162,12 +151,11 @@ moreRequested(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxIdleEvent_MoreRequested), wxe_util:rec(?wxIdleEvent_MoreRequested). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxidleevent.html#wxidleeventsetmode">external documentation</a>. -%%<br /> Mode = ?wxIDLE_PROCESS_ALL | ?wxIDLE_PROCESS_SPECIFIED -doc """ -Static function for specifying how wxWidgets will send idle events: to all -windows, or only to those which specify that they will process the events. +Static function for specifying how wxWidgets will send idle events: to all windows, or +only to those which specify that they will process the events. """. +%% Mode = ?wxIDLE_PROCESS_ALL | ?wxIDLE_PROCESS_SPECIFIED -spec setMode(Mode) -> 'ok' when Mode::wx:wx_enum(). setMode(Mode) @@ -175,30 +163,21 @@ setMode(Mode) wxe_util:queue_cmd(Mode,?get_env(),?wxIdleEvent_SetMode). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxImage.erl b/lib/wx/src/gen/wxImage.erl index dfe1969d28f3..b7a8a6331221 100644 --- a/lib/wx/src/gen/wxImage.erl +++ b/lib/wx/src/gen/wxImage.erl @@ -24,78 +24,98 @@ %% -module(wxImage). -moduledoc """ -Functions for wxImage class - This class encapsulates a platform-independent image. -An image can be created from data, or using `wxBitmap:convertToImage/1`. An -image can be loaded from a file in a variety of formats, and is extensible to -new formats via image format handlers. Functions are available to set and get -image bits, so it can be used for basic image manipulation. +An image can be created from data, or using `wxBitmap:convertToImage/1`. An image can be loaded from a file in a +variety of formats, and is extensible to new formats via image format handlers. Functions +are available to set and get image bits, so it can be used for basic image manipulation. A `m:wxImage` cannot (currently) be drawn directly to a `m:wxDC`. Instead, a platform-specific `m:wxBitmap` object must be created from it using the -wxBitmap::wxBitmap(wxImage,int depth) constructor. This bitmap can then be drawn -in a device context, using `wxDC:drawBitmap/4`. - -More on the difference between `m:wxImage` and `m:wxBitmap`: `m:wxImage` is just -a buffer of RGB bytes with an optional buffer for the alpha bytes. It is all -generic, platform independent and image file format independent code. It -includes generic code for scaling, resizing, clipping, and other manipulations -of the image data. OTOH, `m:wxBitmap` is intended to be a wrapper of whatever is -the native image format that is quickest/easiest to draw to a DC or to be the -target of the drawing operations performed on a `m:wxMemoryDC`. By splitting the -responsibilities between wxImage/wxBitmap like this then it's easier to use -generic code shared by all platforms and image types for generic operations and +wxBitmap::wxBitmap(wxImage,int depth) constructor. This bitmap can then be drawn in a +device context, using `wxDC:drawBitmap/4`. + +More on the difference between `m:wxImage` and `m:wxBitmap`: `m:wxImage` is just a buffer +of RGB bytes with an optional buffer for the alpha bytes. It is all generic, platform +independent and image file format independent code. It includes generic code for scaling, +resizing, clipping, and other manipulations of the image data. OTOH, `m:wxBitmap` is +intended to be a wrapper of whatever is the native image format that is quickest/easiest +to draw to a DC or to be the target of the drawing operations performed on a `m:wxMemoryDC`. +By splitting the responsibilities between wxImage/wxBitmap like this then it's easier to +use generic code shared by all platforms and image types for generic operations and platform specific code where performance or compatibility is needed. -One colour value of the image may be used as a mask colour which will lead to -the automatic creation of a `m:wxMask` object associated to the bitmap object. +One colour value of the image may be used as a mask colour which will lead to the +automatic creation of a `m:wxMask` object associated to the bitmap object. Alpha channel support -Starting from wxWidgets 2.5.0 `m:wxImage` supports alpha channel data, that is -in addition to a byte for the red, green and blue colour components for each -pixel it also stores a byte representing the pixel opacity. +Starting from wxWidgets 2.5.0 `m:wxImage` supports alpha channel data, that is in +addition to a byte for the red, green and blue colour components for each pixel it also +stores a byte representing the pixel opacity. -An alpha value of 0 corresponds to a transparent pixel (null opacity) while a -value of 255 means that the pixel is 100% opaque. The constants -?wxIMAGE_ALPHA_TRANSPARENT and ?wxIMAGE_ALPHA_OPAQUE can be used to indicate -those values in a more readable form. +An alpha value of 0 corresponds to a transparent pixel (null opacity) while a value of +255 means that the pixel is 100% opaque. The constants ?wxIMAGE\_ALPHA\_TRANSPARENT and +?wxIMAGE\_ALPHA\_OPAQUE can be used to indicate those values in a more readable form. -While all images have RGB data, not all images have an alpha channel. Before -using `getAlpha/3` you should check if this image contains an alpha channel with -`hasAlpha/1`. Currently the BMP, PNG, TGA, and TIFF format handlers have full -alpha channel support for loading so if you want to use alpha you have to use -one of these formats. If you initialize the image alpha channel yourself using -`setAlpha/4`, you should save it in either PNG, TGA, or TIFF format to avoid -losing it as these are the only handlers that currently support saving with -alpha. +While all images have RGB data, not all images have an alpha channel. Before using `getAlpha/3` you +should check if this image contains an alpha channel with `hasAlpha/1`. Currently the BMP, PNG, TGA, +and TIFF format handlers have full alpha channel support for loading so if you want to use +alpha you have to use one of these formats. If you initialize the image alpha channel +yourself using `setAlpha/4`, you should save it in either PNG, TGA, or TIFF format to avoid losing it +as these are the only handlers that currently support saving with alpha. Available image handlers -The following image handlers are available. wxBMPHandler is always installed by -default. To use other image formats, install the appropriate handler with -`wxImage::AddHandler` (not implemented in wx) or call ?wxInitAllImageHandlers(). +The following image handlers are available. wxBMPHandler is always installed by default. +To use other image formats, install the appropriate handler with `wxImage::AddHandler` +(not implemented in wx) or call ?wxInitAllImageHandlers(). + +* wxBMPHandler: For loading (including alpha support) and saving, always installed. + +* `wxPNGHandler` (not implemented in wx): For loading and saving. Includes alpha support. + +* `wxJPEGHandler` (not implemented in wx): For loading and saving. + +* `wxGIFHandler` (not implemented in wx): For loading and saving (see below). + +* `wxPCXHandler` (not implemented in wx): For loading and saving (see below). + +* `wxPNMHandler` (not implemented in wx): For loading and saving (see below). + +* `wxTIFFHandler` (not implemented in wx): For loading and saving. Includes alpha support. + +* `wxTGAHandler` (not implemented in wx): For loading and saving. Includes alpha support. -When saving in PCX format, `wxPCXHandler` (not implemented in wx) will count the -number of different colours in the image; if there are 256 or less colours, it -will save as 8 bit, else it will save as 24 bit. +* `wxIFFHandler` (not implemented in wx): For loading only. -Loading PNMs only works for ASCII or raw RGB images. When saving in PNM format, -`wxPNMHandler` (not implemented in wx) will always save as raw RGB. +* `wxXPMHandler` (not implemented in wx): For loading and saving. -Saving GIFs requires images of maximum 8 bpp (see `wxQuantize` (not implemented -in wx)), and the alpha channel converted to a mask (see `convertAlphaToMask/5`). -Saving an animated GIF requires images of the same size (see -`wxGIFHandler::SaveAnimation` (not implemented in wx)) +* wxICOHandler: For loading and saving. + +* wxCURHandler: For loading and saving. + +* wxANIHandler: For loading only. + +When saving in PCX format, `wxPCXHandler` (not implemented in wx) will count the number +of different colours in the image; if there are 256 or less colours, it will save as 8 +bit, else it will save as 24 bit. + +Loading PNMs only works for ASCII or raw RGB images. When saving in PNM format, `wxPNMHandler` +(not implemented in wx) will always save as raw RGB. + +Saving GIFs requires images of maximum 8 bpp (see `wxQuantize` (not implemented in wx)), +and the alpha channel converted to a mask (see `convertAlphaToMask/5`). Saving an animated GIF requires images of +the same size (see `wxGIFHandler::SaveAnimation` (not implemented in wx)) Predefined objects (include wx.hrl): ?wxNullImage -See: `m:wxBitmap`, ?wxInitAllImageHandlers(), `wxPixelData` (not implemented in -wx) +See: +* `m:wxBitmap` -wxWidgets docs: [wxImage](https://docs.wxwidgets.org/3.1/classwx_image.html) +* ?wxInitAllImageHandlers() + +wxWidgets docs: [wxImage](https://docs.wxwidgets.org/3.2/classwx_image.html) """. -include("wxe.hrl"). -export(['Destroy'/1,blur/2,blurHorizontal/2,blurVertical/2,convertAlphaToMask/1, @@ -119,23 +139,17 @@ wxWidgets docs: [wxImage](https://docs.wxwidgets.org/3.1/classwx_image.html) -type wxImage() :: wx:wx_object(). -export_type([wxImage/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagewximage">external documentation</a>. -doc "Creates an empty `m:wxImage` object without an alpha channel.". -spec new() -> wxImage(). new() -> wxe_util:queue_cmd(?get_env(), ?wxImage_new_0), wxe_util:rec(?wxImage_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagewximage">external documentation</a>. -%% <br /> Also:<br /> -%% new(Sz) -> wxImage() when<br /> -%% Sz::{W::integer(), H::integer()}.<br /> -%% -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY +-doc "Equivalent to: `new/2`". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Name) -> wxImage() when Name::unicode:chardata(); (Sz) -> wxImage() when @@ -149,23 +163,11 @@ new({SzW,SzH} = Sz) when is_integer(SzW),is_integer(SzH) -> new(Sz, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagewximage">external documentation</a>. -%% <br /> Also:<br /> -%% new(Name, [Option]) -> wxImage() when<br /> -%% Name::unicode:chardata(),<br /> -%% Option :: {'type', wx:wx_enum()}<br /> -%% | {'index', integer()};<br /> -%% (Sz, Data) -> wxImage() when<br /> -%% Sz::{W::integer(), H::integer()}, Data::binary();<br /> -%% (Sz, [Option]) -> wxImage() when<br /> -%% Sz::{W::integer(), H::integer()},<br /> -%% Option :: {'clear', boolean()}.<br /> -%% -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec new(Width, Height) -> wxImage() when Width::integer(), Height::integer(); (Name, [Option]) -> wxImage() when @@ -202,20 +204,9 @@ new({SzW,SzH} = Sz, Options) wxe_util:queue_cmd(Sz, Opts,?get_env(),?wxImage_new_2_2), wxe_util:rec(?wxImage_new_2_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagewximage">external documentation</a>. -%% <br /> Also:<br /> -%% new(Width, Height, [Option]) -> wxImage() when<br /> -%% Width::integer(), Height::integer(),<br /> -%% Option :: {'clear', boolean()};<br /> -%% (Name, Mimetype, [Option]) -> wxImage() when<br /> -%% Name::unicode:chardata(), Mimetype::unicode:chardata(),<br /> -%% Option :: {'index', integer()};<br /> -%% (Sz, Data, Alpha) -> wxImage() when<br /> -%% Sz::{W::integer(), H::integer()}, Data::binary(), Alpha::binary().<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec new(Width, Height, Data) -> wxImage() when Width::integer(), Height::integer(), Data::binary(); @@ -252,12 +243,11 @@ new({SzW,SzH} = Sz,Data,Alpha) wxe_util:queue_cmd(Sz,Data,Alpha,?get_env(),?wxImage_new_3_3), wxe_util:rec(?wxImage_new_3_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagewximage">external documentation</a>. -doc """ Creates an image from data in memory. -If `static_data` is false then the `m:wxImage` will take ownership of the data -and free it afterwards. For this, it has to be allocated with `malloc`. +If `static_data` is false then the `m:wxImage` will take ownership of the data and free +it afterwards. For this, it has to be allocated with `malloc`. """. -spec new(Width, Height, Data, Alpha) -> wxImage() when Width::integer(), Height::integer(), Data::binary(), Alpha::binary(). @@ -266,14 +256,15 @@ new(Width,Height,Data,Alpha) wxe_util:queue_cmd(Width,Height,Data,Alpha,?get_env(),?wxImage_new_4), wxe_util:rec(?wxImage_new_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageblur">external documentation</a>. -doc """ -Blurs the image in both horizontal and vertical directions by the specified -pixel `blurRadius`. +Blurs the image in both horizontal and vertical directions by the specified pixel `blurRadius`. This should not be used when using a single mask colour for transparency. -See: `blurHorizontal/2`, `blurVertical/2` +See: +* `blurHorizontal/2` + +* `blurVertical/2` """. -spec blur(This, BlurRadius) -> wxImage() when This::wxImage(), BlurRadius::integer(). @@ -283,13 +274,15 @@ blur(#wx_ref{type=ThisT}=This,BlurRadius) wxe_util:queue_cmd(This,BlurRadius,?get_env(),?wxImage_Blur), wxe_util:rec(?wxImage_Blur). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageblurhorizontal">external documentation</a>. -doc """ Blurs the image in the horizontal direction only. This should not be used when using a single mask colour for transparency. -See: `blur/2`, `blurVertical/2` +See: +* `blur/2` + +* `blurVertical/2` """. -spec blurHorizontal(This, BlurRadius) -> wxImage() when This::wxImage(), BlurRadius::integer(). @@ -299,13 +292,15 @@ blurHorizontal(#wx_ref{type=ThisT}=This,BlurRadius) wxe_util:queue_cmd(This,BlurRadius,?get_env(),?wxImage_BlurHorizontal), wxe_util:rec(?wxImage_BlurHorizontal). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageblurvertical">external documentation</a>. -doc """ Blurs the image in the vertical direction only. This should not be used when using a single mask colour for transparency. -See: `blur/2`, `blurHorizontal/2` +See: +* `blur/2` + +* `blurHorizontal/2` """. -spec blurVertical(This, BlurRadius) -> wxImage() when This::wxImage(), BlurRadius::integer(). @@ -315,7 +310,7 @@ blurVertical(#wx_ref{type=ThisT}=This,BlurRadius) wxe_util:queue_cmd(This,BlurRadius,?get_env(),?wxImage_BlurVertical), wxe_util:rec(?wxImage_BlurVertical). -%% @equiv convertAlphaToMask(This, []) +-doc(#{equiv => convertAlphaToMask(This, [])}). -spec convertAlphaToMask(This) -> boolean() when This::wxImage(). @@ -323,16 +318,13 @@ convertAlphaToMask(This) when is_record(This, wx_ref) -> convertAlphaToMask(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageconvertalphatomask">external documentation</a>. -doc """ If the image has alpha channel, this method converts it to mask. -If the image has an alpha channel, all pixels with alpha value less than -`threshold` are replaced with the mask colour and the alpha channel is removed. -Otherwise nothing is done. +If the image has an alpha channel, all pixels with alpha value less than `threshold` are +replaced with the mask colour and the alpha channel is removed. Otherwise nothing is done. -The mask colour is chosen automatically using `findFirstUnusedColour/2`, see the -overload below if this is not appropriate. +The mask colour is chosen automatically using `findFirstUnusedColour/2`, see the overload below if this is not appropriate. Return: Returns true on success, false on error. """. @@ -348,7 +340,7 @@ convertAlphaToMask(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxImage_ConvertAlphaToMask_1), wxe_util:rec(?wxImage_ConvertAlphaToMask_1). -%% @equiv convertAlphaToMask(This,Mr,Mg,Mb, []) +-doc(#{equiv => convertAlphaToMask(This,Mr,Mg,Mb, [])}). -spec convertAlphaToMask(This, Mr, Mg, Mb) -> boolean() when This::wxImage(), Mr::integer(), Mg::integer(), Mb::integer(). @@ -356,14 +348,12 @@ convertAlphaToMask(This,Mr,Mg,Mb) when is_record(This, wx_ref),is_integer(Mr),is_integer(Mg),is_integer(Mb) -> convertAlphaToMask(This,Mr,Mg,Mb, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageconvertalphatomask">external documentation</a>. -doc """ -If the image has alpha channel, this method converts it to mask using the -specified colour as the mask colour. +If the image has alpha channel, this method converts it to mask using the specified +colour as the mask colour. -If the image has an alpha channel, all pixels with alpha value less than -`threshold` are replaced with the mask colour and the alpha channel is removed. -Otherwise nothing is done. +If the image has an alpha channel, all pixels with alpha value less than `threshold` are +replaced with the mask colour and the alpha channel is removed. Otherwise nothing is done. Since: 2.9.0 @@ -381,7 +371,6 @@ convertAlphaToMask(#wx_ref{type=ThisT}=This,Mr,Mg,Mb, Options) wxe_util:queue_cmd(This,Mr,Mg,Mb, Opts,?get_env(),?wxImage_ConvertAlphaToMask_4), wxe_util:rec(?wxImage_ConvertAlphaToMask_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageconverttogreyscale">external documentation</a>. -doc """ Returns a greyscale version of the image. @@ -394,14 +383,12 @@ convertToGreyscale(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_ConvertToGreyscale_0), wxe_util:rec(?wxImage_ConvertToGreyscale_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageconverttogreyscale">external documentation</a>. -doc """ Returns a greyscale version of the image. The returned image uses the luminance component of the original to calculate the -greyscale. Defaults to using the standard ITU-T BT.601 when converting to YUV, -where every pixel equals (R _ `weight_r`) + (G _ `weight_g`) + (B \* -`weight_b`). +greyscale. Defaults to using the standard ITU-T BT.601 when converting to YUV, where every +pixel equals (R * `weight_r`) + (G * `weight_g`) + (B * `weight_b`). """. -spec convertToGreyscale(This, Weight_r, Weight_g, Weight_b) -> wxImage() when This::wxImage(), Weight_r::number(), Weight_g::number(), Weight_b::number(). @@ -411,12 +398,11 @@ convertToGreyscale(#wx_ref{type=ThisT}=This,Weight_r,Weight_g,Weight_b) wxe_util:queue_cmd(This,Weight_r,Weight_g,Weight_b,?get_env(),?wxImage_ConvertToGreyscale_3), wxe_util:rec(?wxImage_ConvertToGreyscale_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageconverttomono">external documentation</a>. -doc """ Returns monochromatic version of the image. -The returned image has white colour where the original has (r,g,b) colour and -black colour everywhere else. +The returned image has white colour where the original has (r,g,b) colour and black +colour everywhere else. """. -spec convertToMono(This, R, G, B) -> wxImage() when This::wxImage(), R::integer(), G::integer(), B::integer(). @@ -426,7 +412,6 @@ convertToMono(#wx_ref{type=ThisT}=This,R,G,B) wxe_util:queue_cmd(This,R,G,B,?get_env(),?wxImage_ConvertToMono), wxe_util:rec(?wxImage_ConvertToMono). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagecopy">external documentation</a>. -doc "Returns an identical copy of this image.". -spec copy(This) -> wxImage() when This::wxImage(). @@ -435,7 +420,7 @@ copy(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_Copy), wxe_util:rec(?wxImage_Copy). -%% @equiv create(This,Sz, []) +-doc(#{equiv => create(This,Sz, [])}). -spec create(This, Sz) -> boolean() when This::wxImage(), Sz::{W::integer(), H::integer()}. @@ -443,17 +428,9 @@ create(This,{SzW,SzH} = Sz) when is_record(This, wx_ref),is_integer(SzW),is_integer(SzH) -> create(This,Sz, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagecreate">external documentation</a>. -%% <br /> Also:<br /> -%% create(This, Sz, Data) -> boolean() when<br /> -%% This::wxImage(), Sz::{W::integer(), H::integer()}, Data::binary();<br /> -%% (This, Sz, [Option]) -> boolean() when<br /> -%% This::wxImage(), Sz::{W::integer(), H::integer()},<br /> -%% Option :: {'clear', boolean()}.<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec create(This, Width, Height) -> boolean() when This::wxImage(), Width::integer(), Height::integer(); @@ -480,17 +457,9 @@ create(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz, Options) wxe_util:queue_cmd(This,Sz, Opts,?get_env(),?wxImage_Create_2_1), wxe_util:rec(?wxImage_Create_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagecreate">external documentation</a>. -%% <br /> Also:<br /> -%% create(This, Width, Height, [Option]) -> boolean() when<br /> -%% This::wxImage(), Width::integer(), Height::integer(),<br /> -%% Option :: {'clear', boolean()};<br /> -%% (This, Sz, Data, Alpha) -> boolean() when<br /> -%% This::wxImage(), Sz::{W::integer(), H::integer()}, Data::binary(), Alpha::binary().<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec create(This, Width, Height, Data) -> boolean() when This::wxImage(), Width::integer(), Height::integer(), Data::binary(); @@ -518,7 +487,6 @@ create(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz,Data,Alpha) wxe_util:queue_cmd(This,Sz,Data,Alpha,?get_env(),?wxImage_Create_3_2), wxe_util:rec(?wxImage_Create_3_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagecreate">external documentation</a>. -doc """ Creates a fresh image. @@ -534,7 +502,6 @@ create(#wx_ref{type=ThisT}=This,Width,Height,Data,Alpha) wxe_util:queue_cmd(This,Width,Height,Data,Alpha,?get_env(),?wxImage_Create_4), wxe_util:rec(?wxImage_Create_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagedestroy">external documentation</a>. -doc "Destroys the image data.". -spec 'Destroy'(This) -> 'ok' when This::wxImage(). @@ -542,7 +509,7 @@ create(#wx_ref{type=ThisT}=This,Width,Height,Data,Alpha) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,?get_env(),?wxImage_Destroy). -%% @equiv findFirstUnusedColour(This, []) +-doc(#{equiv => findFirstUnusedColour(This, [])}). -spec findFirstUnusedColour(This) -> Result when Result ::{Res ::boolean(), R::integer(), G::integer(), B::integer()}, This::wxImage(). @@ -551,23 +518,21 @@ findFirstUnusedColour(This) when is_record(This, wx_ref) -> findFirstUnusedColour(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagefindfirstunusedcolour">external documentation</a>. -doc """ Finds the first colour that is never used in the image. The search begins at given initial colour and continues by increasing R, G and B -components (in this order) by 1 until an unused colour is found or the colour -space exhausted. +components (in this order) by 1 until an unused colour is found or the colour space exhausted. The parameters `r`, `g`, `b` are pointers to variables to save the colour. -The parameters `startR`, `startG`, `startB` define the initial values of the -colour. The returned colour will have RGB values equal to or greater than these. +The parameters `startR`, `startG`, `startB` define the initial values of the colour. The +returned colour will have RGB values equal to or greater than these. Return: Returns false if there is no unused colour left, true on success. -Note: This method involves computing the histogram, which is a computationally -intensive operation. +Note: This method involves computing the histogram, which is a computationally intensive +operation. """. -spec findFirstUnusedColour(This, [Option]) -> Result when Result :: {Res ::boolean(), R::integer(), G::integer(), B::integer()}, @@ -586,30 +551,26 @@ findFirstUnusedColour(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxImage_FindFirstUnusedColour), wxe_util:rec(?wxImage_FindFirstUnusedColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetimageextwildcard">external documentation</a>. -doc """ -Iterates all registered `wxImageHandler` (not implemented in wx) objects, and -returns a string containing file extension masks suitable for passing to file -open/save dialog boxes. - -Return: The format of the returned string is `"(*.ext1;*.ext2)|*.ext1;*.ext2"`. -It is usually a good idea to prepend a description before passing the result to -the dialog. Example: +Iterates all registered `wxImageHandler` (not implemented in wx) objects, and returns a +string containing file extension masks suitable for passing to file open/save dialog +boxes. -See: `wxImageHandler` (not implemented in wx) +Return: The format of the returned string is `"(*.ext1;*.ext2)|*.ext1;*.ext2"`. It is +usually a good idea to prepend a description before passing the result to the dialog. +Example: """. -spec getImageExtWildcard() -> unicode:charlist(). getImageExtWildcard() -> wxe_util:queue_cmd(?get_env(), ?wxImage_GetImageExtWildcard), wxe_util:rec(?wxImage_GetImageExtWildcard). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetalpha">external documentation</a>. -doc """ Returns pointer to the array storing the alpha values for this image. -This pointer is NULL for the images without the alpha channel. If the image does -have it, this pointer may be used to directly manipulate the alpha values which -are stored as the RGB ones. +This pointer is NULL for the images without the alpha channel. If the image does have it, +this pointer may be used to directly manipulate the alpha values which are stored as the +RGB ones. """. -spec getAlpha(This) -> binary() when This::wxImage(). @@ -618,7 +579,6 @@ getAlpha(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetAlpha_0), wxe_util:rec(?wxImage_GetAlpha_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetalpha">external documentation</a>. -doc "Return alpha value at given pixel location.". -spec getAlpha(This, X, Y) -> integer() when This::wxImage(), X::integer(), Y::integer(). @@ -628,7 +588,6 @@ getAlpha(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxImage_GetAlpha_2), wxe_util:rec(?wxImage_GetAlpha_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetblue">external documentation</a>. -doc "Returns the blue intensity at the given coordinate.". -spec getBlue(This, X, Y) -> integer() when This::wxImage(), X::integer(), Y::integer(). @@ -638,16 +597,14 @@ getBlue(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxImage_GetBlue), wxe_util:rec(?wxImage_GetBlue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetdata">external documentation</a>. -doc """ Returns the image data as an array. -This is most often used when doing direct image manipulation. The return value -points to an array of characters in RGBRGBRGB... format in the top-to-bottom, -left-to-right order, that is the first RGB triplet corresponds to the first -pixel of the first row, the second one - to the second pixel of the first row -and so on until the end of the first row, with second row following after it and -so on. +This is most often used when doing direct image manipulation. The return value points to +an array of characters in RGBRGBRGB... format in the top-to-bottom, left-to-right order, +that is the first RGB triplet corresponds to the first pixel of the first row, the second +one - to the second pixel of the first row and so on until the end of the first row, with +second row following after it and so on. You should not delete the returned pointer nor pass it to `setData/4`. """. @@ -658,7 +615,6 @@ getData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetData), wxe_util:rec(?wxImage_GetData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetgreen">external documentation</a>. -doc "Returns the green intensity at the given coordinate.". -spec getGreen(This, X, Y) -> integer() when This::wxImage(), X::integer(), Y::integer(). @@ -668,7 +624,7 @@ getGreen(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxImage_GetGreen), wxe_util:rec(?wxImage_GetGreen). -%% @equiv getImageCount(Filename, []) +-doc(#{equiv => getImageCount(Filename, [])}). -spec getImageCount(Filename) -> integer() when Filename::unicode:chardata(). @@ -676,25 +632,48 @@ getImageCount(Filename) when ?is_chardata(Filename) -> getImageCount(Filename, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetimagecount">external documentation</a>. -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ -If the image file contains more than one image and the image handler is capable -of retrieving these individually, this function will return the number of -available images. +If the image file contains more than one image and the image handler is capable of +retrieving these individually, this function will return the number of available images. -For the overload taking the parameter `filename`, that's the name of the file to -query. For the overload taking the parameter `stream`, that's the opened input -stream with image data. +For the overload taking the parameter `filename`, that's the name of the file to query. +For the overload taking the parameter `stream`, that's the opened input stream with image data. See `wxImageHandler::GetImageCount()` (not implemented in wx) for more info. The parameter `type` may be one of the following values: -Return: Number of available images. For most image handlers, this is 1 -(exceptions are TIFF and ICO formats as well as animated GIFs for which this -function returns the number of frames in the animation). +* wxBITMAP_TYPE_BMP: Load a Windows bitmap file. + +* wxBITMAP_TYPE_GIF: Load a GIF bitmap file. + +* wxBITMAP_TYPE_JPEG: Load a JPEG bitmap file. + +* wxBITMAP_TYPE_PNG: Load a PNG bitmap file. + +* wxBITMAP_TYPE_PCX: Load a PCX bitmap file. + +* wxBITMAP_TYPE_PNM: Load a PNM bitmap file. + +* wxBITMAP_TYPE_TIFF: Load a TIFF bitmap file. + +* wxBITMAP_TYPE_TGA: Load a TGA bitmap file. + +* wxBITMAP_TYPE_XPM: Load a XPM bitmap file. + +* wxBITMAP_TYPE_ICO: Load a Windows icon file (ICO). + +* wxBITMAP_TYPE_CUR: Load a Windows cursor file (CUR). + +* wxBITMAP_TYPE_ANI: Load a Windows animated cursor file (ANI). + +* wxBITMAP_TYPE_ANY: Will try to autodetect the format. + +Return: Number of available images. For most image handlers, this is 1 (exceptions are +TIFF and ICO formats as well as animated GIFs for which this function returns the number +of frames in the animation). """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec getImageCount(Filename, [Option]) -> integer() when Filename::unicode:chardata(), Option :: {'type', wx:wx_enum()}. @@ -707,11 +686,10 @@ getImageCount(Filename, Options) wxe_util:queue_cmd(Filename_UC, Opts,?get_env(),?wxImage_GetImageCount), wxe_util:rec(?wxImage_GetImageCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetheight">external documentation</a>. -doc """ Gets the height of the image in pixels. -See: `getWidth/1`, `GetSize()` (not implemented in wx) +See: `getWidth/1` """. -spec getHeight(This) -> integer() when This::wxImage(). @@ -720,7 +698,6 @@ getHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetHeight), wxe_util:rec(?wxImage_GetHeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetmaskblue">external documentation</a>. -doc "Gets the blue value of the mask colour.". -spec getMaskBlue(This) -> integer() when This::wxImage(). @@ -729,7 +706,6 @@ getMaskBlue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetMaskBlue), wxe_util:rec(?wxImage_GetMaskBlue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetmaskgreen">external documentation</a>. -doc "Gets the green value of the mask colour.". -spec getMaskGreen(This) -> integer() when This::wxImage(). @@ -738,7 +714,6 @@ getMaskGreen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetMaskGreen), wxe_util:rec(?wxImage_GetMaskGreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetmaskred">external documentation</a>. -doc "Gets the red value of the mask colour.". -spec getMaskRed(This) -> integer() when This::wxImage(). @@ -747,10 +722,9 @@ getMaskRed(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetMaskRed), wxe_util:rec(?wxImage_GetMaskRed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetorfindmaskcolour">external documentation</a>. -doc """ -Get the current mask colour or find a suitable unused colour that could be used -as a mask colour. +Get the current mask colour or find a suitable unused colour that could be used as a mask +colour. Returns true if the image currently has a mask. """. @@ -762,16 +736,13 @@ getOrFindMaskColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetOrFindMaskColour), wxe_util:rec(?wxImage_GetOrFindMaskColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetpalette">external documentation</a>. -doc """ Returns the palette associated with the image. -Currently the palette is only used when converting to `m:wxBitmap` under -Windows. +Currently the palette is only used when converting to `m:wxBitmap` under Windows. -Some of the `m:wxImage` handlers have been modified to set the palette if one -exists in the image file (usually 256 or less colour images in GIF or PNG -format). +Some of the `m:wxImage` handlers have been modified to set the palette if one exists in +the image file (usually 256 or less colour images in GIF or PNG format). """. -spec getPalette(This) -> wxPalette:wxPalette() when This::wxImage(). @@ -780,7 +751,6 @@ getPalette(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetPalette), wxe_util:rec(?wxImage_GetPalette). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetred">external documentation</a>. -doc "Returns the red intensity at the given coordinate.". -spec getRed(This, X, Y) -> integer() when This::wxImage(), X::integer(), Y::integer(). @@ -790,11 +760,7 @@ getRed(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxImage_GetRed), wxe_util:rec(?wxImage_GetRed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetsubimage">external documentation</a>. --doc """ -Returns a sub image of the current one as long as the rect belongs entirely to -the image. -""". +-doc "Returns a sub image of the current one as long as the rect belongs entirely to the image.". -spec getSubImage(This, Rect) -> wxImage() when This::wxImage(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. getSubImage(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) @@ -803,11 +769,10 @@ getSubImage(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) wxe_util:queue_cmd(This,Rect,?get_env(),?wxImage_GetSubImage), wxe_util:rec(?wxImage_GetSubImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetwidth">external documentation</a>. -doc """ Gets the width of the image in pixels. -See: `getHeight/1`, `GetSize()` (not implemented in wx) +See: `getHeight/1` """. -spec getWidth(This) -> integer() when This::wxImage(). @@ -816,11 +781,13 @@ getWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_GetWidth), wxe_util:rec(?wxImage_GetWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagehasalpha">external documentation</a>. -doc """ Returns true if this image has alpha channel, false otherwise. -See: `getAlpha/3`, `setAlpha/4` +See: +* `getAlpha/3` + +* `setAlpha/4` """. -spec hasAlpha(This) -> boolean() when This::wxImage(). @@ -829,7 +796,6 @@ hasAlpha(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_HasAlpha), wxe_util:rec(?wxImage_HasAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagehasmask">external documentation</a>. -doc "Returns true if there is a mask active, false otherwise.". -spec hasMask(This) -> boolean() when This::wxImage(). @@ -838,18 +804,28 @@ hasMask(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_HasMask), wxe_util:rec(?wxImage_HasMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetoption">external documentation</a>. -doc """ Gets a user-defined string-valued option. Generic options: +* `wxIMAGE_OPTION_FILENAME:` The name of the file from which the image was loaded. + Options specific to `wxGIFHandler` (not implemented in wx): -Return: The value of the option or an empty string if not found. Use -`hasOption/2` if an empty string can be a valid option value. +* `wxIMAGE_OPTION_GIF_COMMENT:` The comment text that is read from or written to the GIF +file. In an animated GIF each frame can have its own comment. If there is only a comment +in the first frame of a GIF it will not be repeated in other frames. + +Return: The value of the option or an empty string if not found. Use `hasOption/2` if an empty string +can be a valid option value. + +See: +* `setOption/3` -See: `setOption/3`, `getOptionInt/2`, `hasOption/2` +* `getOptionInt/2` + +* `hasOption/2` """. -spec getOption(This, Name) -> unicode:charlist() when This::wxImage(), Name::unicode:chardata(). @@ -860,34 +836,114 @@ getOption(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxImage_GetOption), wxe_util:rec(?wxImage_GetOption). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagegetoptionint">external documentation</a>. -doc """ Gets a user-defined integer-valued option. -The function is case-insensitive to `name`. If the given option is not present, -the function returns 0. Use `hasOption/2` if 0 is a possibly valid value for the -option. +The function is case-insensitive to `name`. If the given option is not present, the +function returns 0. Use `hasOption/2` if 0 is a possibly valid value for the option. Generic options: +* `wxIMAGE_OPTION_MAX_WIDTH` and `wxIMAGE_OPTION_MAX_HEIGHT:` If either of these options is +specified, the loaded image will be scaled down (preserving its aspect ratio) so that its +width is less than the max width given if it is not 0 `and` its height is less than the +max height given if it is not 0. This is typically used for loading thumbnails and the +advantage of using these options compared to calling `rescale/4` after loading is that some handlers +(only JPEG one right now) support rescaling the image during loading which is vastly more +efficient than loading the entire huge image and rescaling it later (if these options are +not supported by the handler, this is still what happens however). These options must be +set before calling `loadFile/4` to have any effect. + +* `wxIMAGE_OPTION_ORIGINAL_WIDTH` and `wxIMAGE_OPTION_ORIGINAL_HEIGHT:` These options will +return the original size of the image if either `wxIMAGE_OPTION_MAX_WIDTH` or `wxIMAGE_OPTION_MAX_HEIGHT` +is specified. + Since: 2.9.3 +* `wxIMAGE_OPTION_QUALITY:` JPEG quality used when saving. This is an integer in 0..100 +range with 0 meaning very poor and 100 excellent (but very badly compressed). This option +is currently ignored for the other formats. + +* `wxIMAGE_OPTION_RESOLUTIONUNIT:` The value of this option determines whether the +resolution of the image is specified in centimetres or inches, see wxImageResolution enum elements. + +* `wxIMAGE_OPTION_RESOLUTION`, `wxIMAGE_OPTION_RESOLUTIONX` and `wxIMAGE_OPTION_RESOLUTIONY:` +These options define the resolution of the image in the units corresponding to `wxIMAGE_OPTION_RESOLUTIONUNIT` +options value. The first option can be set before saving the image to set both horizontal +and vertical resolution to the same value. The X and Y options are set by the image +handlers if they support the image resolution (currently BMP, JPEG and TIFF handlers do) +and the image provides the resolution information and can be queried after loading the image. + Options specific to `wxPNGHandler` (not implemented in wx): +* `wxIMAGE_OPTION_PNG_FORMAT:` Format for saving a PNG file, see wxImagePNGType for the +supported values. + +* `wxIMAGE_OPTION_PNG_BITDEPTH:` Bit depth for every channel (R/G/B/A). + +* `wxIMAGE_OPTION_PNG_FILTER:` Filter for saving a PNG file, see libpng ([http://www.libpng.org/pub/png/libpng-1.2.5-manual.html](http://www.libpng.org/pub/png/libpng-1.2.5-manual.html)) +for possible values (e.g. PNG_FILTER_NONE, PNG_FILTER_SUB, PNG_FILTER_UP, etc). + +* `wxIMAGE_OPTION_PNG_COMPRESSION_LEVEL:` Compression level (0..9) for saving a PNG file. +An high value creates smaller-but-slower PNG file. Note that unlike other formats (e.g. +JPEG) the PNG format is always lossless and thus this compression level doesn't tradeoff +the image quality. + +* `wxIMAGE_OPTION_PNG_COMPRESSION_MEM_LEVEL:` Compression memory usage level (1..9) for +saving a PNG file. An high value means the saving process consumes more memory, but may +create smaller PNG file. + +* `wxIMAGE_OPTION_PNG_COMPRESSION_STRATEGY:` Possible values are 0 for default strategy, 1 +for filter, and 2 for Huffman-only. You can use OptiPNG ([http://optipng.sourceforge.net/](http://optipng.sourceforge.net/)) +to get a suitable value for your application. + +* `wxIMAGE_OPTION_PNG_COMPRESSION_BUFFER_SIZE:` Internal buffer size (in bytes) for saving +a PNG file. Ideally this should be as big as the resulting PNG file. Use this option if +your application produces images with small size variation. + Options specific to `wxTIFFHandler` (not implemented in wx): +* `wxIMAGE_OPTION_TIFF_BITSPERSAMPLE:` Number of bits per sample (channel). Currently +values of 1 and 8 are supported. A value of 1 results in a black and white image. A value +of 8 (the default) can mean greyscale or RGB, depending on the value of `wxIMAGE_OPTION_TIFF_SAMPLESPERPIXEL`. + +* `wxIMAGE_OPTION_TIFF_SAMPLESPERPIXEL:` Number of samples (channels) per pixel. Currently +values of 1 and 3 are supported. A value of 1 results in either a greyscale (by default) +or black and white image, depending on the value of `wxIMAGE_OPTION_TIFF_BITSPERSAMPLE`. A +value of 3 (the default) will result in an RGB image. + +* `wxIMAGE_OPTION_TIFF_COMPRESSION:` Compression type. By default it is set to 1 +(COMPRESSION_NONE). Typical other values are 5 (COMPRESSION_LZW) and 7 (COMPRESSION_JPEG). +See tiff.h for more options. + +* `wxIMAGE_OPTION_TIFF_PHOTOMETRIC:` Specifies the photometric interpretation. By default +it is set to 2 (PHOTOMETRIC_RGB) for RGB images and 0 (PHOTOMETRIC_MINISWHITE) for +greyscale or black and white images. It can also be set to 1 (PHOTOMETRIC_MINISBLACK) to +treat the lowest value as black and highest as white. If you want a greyscale image it is +also sufficient to only specify `wxIMAGE_OPTION_TIFF_PHOTOMETRIC` and set it to either +PHOTOMETRIC_MINISWHITE or PHOTOMETRIC_MINISBLACK. The other values are taken care of. + Options specific to `wxGIFHandler` (not implemented in wx): -Note: Be careful when combining the options -`wxIMAGE_OPTION_TIFF_SAMPLESPERPIXEL`, `wxIMAGE_OPTION_TIFF_BITSPERSAMPLE`, and -`wxIMAGE_OPTION_TIFF_PHOTOMETRIC`. While some measures are taken to prevent -illegal combinations and/or values, it is still easy to abuse them and come up -with invalid results in the form of either corrupted images or crashes. +* `wxIMAGE_OPTION_GIF_TRANSPARENCY:` How to deal with transparent pixels. By default, the +color of transparent pixels is changed to bright pink, so that if the image is +accidentally drawn without transparency, it will be obvious. Normally, this would not be +noticed, as these pixels will not be rendered. But in some cases it might be useful to +load a GIF without making any modifications to its colours. Use `wxIMAGE_OPTION_GIF_TRANSPARENCY_UNCHANGED` +to keep the colors correct. Use `wxIMAGE_OPTION_GIF_TRANSPARENCY_HIGHLIGHT` to convert +transparent pixels to pink (default). This option has been added in wxWidgets 3.1.1. + +Note: Be careful when combining the options `wxIMAGE_OPTION_TIFF_SAMPLESPERPIXEL`, `wxIMAGE_OPTION_TIFF_BITSPERSAMPLE`, +and `wxIMAGE_OPTION_TIFF_PHOTOMETRIC`. While some measures are taken to prevent illegal +combinations and/or values, it is still easy to abuse them and come up with invalid +results in the form of either corrupted images or crashes. -Return: The value of the option or 0 if not found. Use `hasOption/2` if 0 can be -a valid option value. +Return: The value of the option or 0 if not found. Use `hasOption/2` if 0 can be a valid option value. -See: `setOption/3`, `getOption/2` +See: +* `setOption/3` + +* `getOption/2` """. -spec getOptionInt(This, Name) -> integer() when This::wxImage(), Name::unicode:chardata(). @@ -898,16 +954,19 @@ getOptionInt(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxImage_GetOptionInt), wxe_util:rec(?wxImage_GetOptionInt). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagehasoption">external documentation</a>. -doc """ Returns true if the given option is present. The function is case-insensitive to `name`. -The lists of the currently supported options are in `getOption/2` and -`getOptionInt/2` function docs. +The lists of the currently supported options are in `getOption/2` and `getOptionInt/2` function docs. + +See: +* `setOption/3` -See: `setOption/3`, `getOption/2`, `getOptionInt/2` +* `getOption/2` + +* `getOptionInt/2` """. -spec hasOption(This, Name) -> boolean() when This::wxImage(), Name::unicode:chardata(). @@ -918,13 +977,12 @@ hasOption(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxImage_HasOption), wxe_util:rec(?wxImage_HasOption). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageinitalpha">external documentation</a>. -doc """ Initializes the image alpha channel data. -It is an error to call it if the image already has alpha data. If it doesn't, -alpha data will be by default initialized to all pixels being fully opaque. But -if the image has a mask colour, all mask pixels will be completely transparent. +It is an error to call it if the image already has alpha data. If it doesn't, alpha data +will be by default initialized to all pixels being fully opaque. But if the image has a +mask colour, all mask pixels will be completely transparent. """. -spec initAlpha(This) -> 'ok' when This::wxImage(). @@ -932,24 +990,21 @@ initAlpha(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,?get_env(),?wxImage_InitAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageinitstandardhandlers">external documentation</a>. -doc """ Internal use only. -Adds standard image format handlers. It only install wxBMPHandler for the time -being, which is used by `m:wxBitmap`. +Adds standard image format handlers. It only install wxBMPHandler for the time being, +which is used by `m:wxBitmap`. -This function is called by wxWidgets on startup, and shouldn't be called by the -user. +This function is called by wxWidgets on startup, and shouldn't be called by the user. -See: `wxImageHandler` (not implemented in wx), ?wxInitAllImageHandlers(), -`wxQuantize` (not implemented in wx) +See: ?wxInitAllImageHandlers() """. -spec initStandardHandlers() -> 'ok'. initStandardHandlers() -> wxe_util:queue_cmd(?get_env(), ?wxImage_InitStandardHandlers). -%% @equiv isTransparent(This,X,Y, []) +-doc(#{equiv => isTransparent(This,X,Y, [])}). -spec isTransparent(This, X, Y) -> boolean() when This::wxImage(), X::integer(), Y::integer(). @@ -957,11 +1012,10 @@ isTransparent(This,X,Y) when is_record(This, wx_ref),is_integer(X),is_integer(Y) -> isTransparent(This,X,Y, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageistransparent">external documentation</a>. -doc """ -Returns true if the given pixel is transparent, i.e. either has the mask colour -if this image has a mask or if this image has alpha channel and alpha value of -this pixel is strictly less than `threshold`. +Returns true if the given pixel is transparent, i.e. either has the mask colour if this +image has a mask or if this image has alpha channel and alpha value of this pixel is +strictly less than `threshold`. """. -spec isTransparent(This, X, Y, [Option]) -> boolean() when This::wxImage(), X::integer(), Y::integer(), @@ -975,7 +1029,7 @@ isTransparent(#wx_ref{type=ThisT}=This,X,Y, Options) wxe_util:queue_cmd(This,X,Y, Opts,?get_env(),?wxImage_IsTransparent), wxe_util:rec(?wxImage_IsTransparent). -%% @equiv loadFile(This,Name, []) +-doc(#{equiv => loadFile(This,Name, [])}). -spec loadFile(This, Name) -> boolean() when This::wxImage(), Name::unicode:chardata(). @@ -983,13 +1037,12 @@ loadFile(This,Name) when is_record(This, wx_ref),?is_chardata(Name) -> loadFile(This,Name, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageloadfile">external documentation</a>. -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc """ Loads an image from a file. If no handler type is provided, the library will try to autodetect the format. """. +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec loadFile(This, Name, [Option]) -> boolean() when This::wxImage(), Name::unicode:chardata(), Option :: {'type', wx:wx_enum()} @@ -1005,7 +1058,6 @@ loadFile(#wx_ref{type=ThisT}=This,Name, Options) wxe_util:queue_cmd(This,Name_UC, Opts,?get_env(),?wxImage_LoadFile_2), wxe_util:rec(?wxImage_LoadFile_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageloadfile">external documentation</a>. -doc """ Loads an image from a file. @@ -1025,8 +1077,7 @@ loadFile(#wx_ref{type=ThisT}=This,Name,Mimetype, Options) wxe_util:queue_cmd(This,Name_UC,Mimetype_UC, Opts,?get_env(),?wxImage_LoadFile_3), wxe_util:rec(?wxImage_LoadFile_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageisok">external documentation</a>. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxImage(). @@ -1034,7 +1085,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageisok">external documentation</a>. -doc "Returns true if image data is present.". -spec isOk(This) -> boolean() when This::wxImage(). @@ -1043,15 +1093,12 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImage_IsOk), wxe_util:rec(?wxImage_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageremovehandler">external documentation</a>. -doc """ Finds the handler with the given name, and removes it. The handler is also deleted. Return: true if the handler was found and removed, false otherwise. - -See: `wxImageHandler` (not implemented in wx) """. -spec removeHandler(Name) -> boolean() when Name::unicode:chardata(). @@ -1061,7 +1108,7 @@ removeHandler(Name) wxe_util:queue_cmd(Name_UC,?get_env(),?wxImage_RemoveHandler), wxe_util:rec(?wxImage_RemoveHandler). -%% @equiv mirror(This, []) +-doc(#{equiv => mirror(This, [])}). -spec mirror(This) -> wxImage() when This::wxImage(). @@ -1069,7 +1116,6 @@ mirror(This) when is_record(This, wx_ref) -> mirror(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagemirror">external documentation</a>. -doc """ Returns a mirrored copy of the image. @@ -1087,7 +1133,6 @@ mirror(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxImage_Mirror), wxe_util:rec(?wxImage_Mirror). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagereplace">external documentation</a>. -doc "Replaces the colour specified by `r1`,g1,b1 by the colour `r2`,g2,b2.". -spec replace(This, R1, G1, B1, R2, G2, B2) -> 'ok' when This::wxImage(), R1::integer(), G1::integer(), B1::integer(), R2::integer(), G2::integer(), B2::integer(). @@ -1096,7 +1141,7 @@ replace(#wx_ref{type=ThisT}=This,R1,G1,B1,R2,G2,B2) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,R1,G1,B1,R2,G2,B2,?get_env(),?wxImage_Replace). -%% @equiv rescale(This,Width,Height, []) +-doc(#{equiv => rescale(This,Width,Height, [])}). -spec rescale(This, Width, Height) -> wxImage() when This::wxImage(), Width::integer(), Height::integer(). @@ -1104,17 +1149,16 @@ rescale(This,Width,Height) when is_record(This, wx_ref),is_integer(Width),is_integer(Height) -> rescale(This,Width,Height, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagerescale">external documentation</a>. -%%<br /> Quality = ?wxIMAGE_QUALITY_NEAREST | ?wxIMAGE_QUALITY_BILINEAR | ?wxIMAGE_QUALITY_BICUBIC | ?wxIMAGE_QUALITY_BOX_AVERAGE | ?wxIMAGE_QUALITY_NORMAL | ?wxIMAGE_QUALITY_HIGH -doc """ -Changes the size of the image in-place by scaling it: after a call to this -function,the image will have the given width and height. +Changes the size of the image in-place by scaling it: after a call to this function,the +image will have the given width and height. -For a description of the `quality` parameter, see the `scale/4` function. -Returns the (modified) image itself. +For a description of the `quality` parameter, see the `scale/4` function. Returns the (modified) +image itself. See: `scale/4` """. +%% Quality = ?wxIMAGE_QUALITY_NEAREST | ?wxIMAGE_QUALITY_BILINEAR | ?wxIMAGE_QUALITY_BICUBIC | ?wxIMAGE_QUALITY_BOX_AVERAGE | ?wxIMAGE_QUALITY_NORMAL | ?wxIMAGE_QUALITY_HIGH -spec rescale(This, Width, Height, [Option]) -> wxImage() when This::wxImage(), Width::integer(), Height::integer(), Option :: {'quality', wx:wx_enum()}. @@ -1127,7 +1171,7 @@ rescale(#wx_ref{type=ThisT}=This,Width,Height, Options) wxe_util:queue_cmd(This,Width,Height, Opts,?get_env(),?wxImage_Rescale), wxe_util:rec(?wxImage_Rescale). -%% @equiv resize(This,Size,Pos, []) +-doc(#{equiv => resize(This,Size,Pos, [])}). -spec resize(This, Size, Pos) -> wxImage() when This::wxImage(), Size::{W::integer(), H::integer()}, Pos::{X::integer(), Y::integer()}. @@ -1135,16 +1179,15 @@ resize(This,{SizeW,SizeH} = Size,{PosX,PosY} = Pos) when is_record(This, wx_ref),is_integer(SizeW),is_integer(SizeH),is_integer(PosX),is_integer(PosY) -> resize(This,Size,Pos, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximageresize">external documentation</a>. -doc """ -Changes the size of the image in-place without scaling it by adding either a -border with the given colour or cropping as necessary. +Changes the size of the image in-place without scaling it by adding either a border with +the given colour or cropping as necessary. -The image is pasted into a new image with the given `size` and background colour -at the position `pos` relative to the upper left of the new image. +The image is pasted into a new image with the given `size` and background colour at the +position `pos` relative to the upper left of the new image. -If `red` = green = blue = -1 then use either the current mask colour if set or -find, use, and set a suitable mask colour for any newly exposed areas. +If `red` = green = blue = -1 then use either the current mask colour if set or find, use, +and set a suitable mask colour for any newly exposed areas. Return: The (modified) image itself. @@ -1166,7 +1209,7 @@ resize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size,{PosX,PosY} = Pos, Options) wxe_util:queue_cmd(This,Size,Pos, Opts,?get_env(),?wxImage_Resize), wxe_util:rec(?wxImage_Resize). -%% @equiv rotate(This,Angle,RotationCentre, []) +-doc(#{equiv => rotate(This,Angle,RotationCentre, [])}). -spec rotate(This, Angle, RotationCentre) -> wxImage() when This::wxImage(), Angle::number(), RotationCentre::{X::integer(), Y::integer()}. @@ -1174,14 +1217,13 @@ rotate(This,Angle,{RotationCentreX,RotationCentreY} = RotationCentre) when is_record(This, wx_ref),is_number(Angle),is_integer(RotationCentreX),is_integer(RotationCentreY) -> rotate(This,Angle,RotationCentre, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagerotate">external documentation</a>. -doc """ Rotates the image about the given point, by `angle` radians. Passing true to `interpolating` results in better image quality, but is slower. -If the image has a mask, then the mask colour is used for the uncovered pixels -in the rotated image background. Else, black (rgb 0, 0, 0) will be used. +If the image has a mask, then the mask colour is used for the uncovered pixels in the +rotated image background. Else, black (rgb 0, 0, 0) will be used. Returns the rotated image, leaving this image intact. """. @@ -1199,11 +1241,9 @@ rotate(#wx_ref{type=ThisT}=This,Angle,{RotationCentreX,RotationCentreY} = Rotati wxe_util:queue_cmd(This,Angle,RotationCentre, Opts,?get_env(),?wxImage_Rotate), wxe_util:rec(?wxImage_Rotate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagerotatehue">external documentation</a>. -doc """ -Rotates the hue of each pixel in the image by `angle`, which is a double in the -range of -1.0 to +1.0, where -1.0 corresponds to -360 degrees and +1.0 -corresponds to +360 degrees. +Rotates the hue of each pixel in the image by `angle`, which is a double in the range of +-1.0 to +1.0, where -1.0 corresponds to -360 degrees and +1.0 corresponds to +360 degrees. """. -spec rotateHue(This, Angle) -> 'ok' when This::wxImage(), Angle::number(). @@ -1212,7 +1252,7 @@ rotateHue(#wx_ref{type=ThisT}=This,Angle) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Angle,?get_env(),?wxImage_RotateHue). -%% @equiv rotate90(This, []) +-doc(#{equiv => rotate90(This, [])}). -spec rotate90(This) -> wxImage() when This::wxImage(). @@ -1220,11 +1260,7 @@ rotate90(This) when is_record(This, wx_ref) -> rotate90(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagerotate90">external documentation</a>. --doc """ -Returns a copy of the image rotated 90 degrees in the direction indicated by -`clockwise`. -""". +-doc "Returns a copy of the image rotated 90 degrees in the direction indicated by `clockwise`.". -spec rotate90(This, [Option]) -> wxImage() when This::wxImage(), Option :: {'clockwise', boolean()}. @@ -1237,13 +1273,12 @@ rotate90(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxImage_Rotate90), wxe_util:rec(?wxImage_Rotate90). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesavefile">external documentation</a>. -doc """ Saves an image in the named file. -File type is determined from the extension of the file name. Note that this -function may fail if the extension is not recognized\! You can use one of the -forms above to save images to files with non-standard extensions. +File type is determined from the extension of the file name. Note that this function may +fail if the extension is not recognized! You can use one of the forms above to save images +to files with non-standard extensions. """. -spec saveFile(This, Name) -> boolean() when This::wxImage(), Name::unicode:chardata(). @@ -1254,13 +1289,8 @@ saveFile(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxImage_SaveFile_1), wxe_util:rec(?wxImage_SaveFile_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesavefile">external documentation</a>. -%% <br /> Also:<br /> -%% saveFile(This, Name, Mimetype) -> boolean() when<br /> -%% This::wxImage(), Name::unicode:chardata(), Mimetype::unicode:chardata().<br /> -%% -%%<br /> Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -doc "Saves an image in the named file.". +%% Type = ?wxBITMAP_TYPE_INVALID | ?wxBITMAP_TYPE_BMP | ?wxBITMAP_TYPE_BMP_RESOURCE | ?wxBITMAP_TYPE_RESOURCE | ?wxBITMAP_TYPE_ICO | ?wxBITMAP_TYPE_ICO_RESOURCE | ?wxBITMAP_TYPE_CUR | ?wxBITMAP_TYPE_CUR_RESOURCE | ?wxBITMAP_TYPE_XBM | ?wxBITMAP_TYPE_XBM_DATA | ?wxBITMAP_TYPE_XPM | ?wxBITMAP_TYPE_XPM_DATA | ?wxBITMAP_TYPE_TIFF | ?wxBITMAP_TYPE_TIF | ?wxBITMAP_TYPE_TIFF_RESOURCE | ?wxBITMAP_TYPE_TIF_RESOURCE | ?wxBITMAP_TYPE_GIF | ?wxBITMAP_TYPE_GIF_RESOURCE | ?wxBITMAP_TYPE_PNG | ?wxBITMAP_TYPE_PNG_RESOURCE | ?wxBITMAP_TYPE_JPEG | ?wxBITMAP_TYPE_JPEG_RESOURCE | ?wxBITMAP_TYPE_PNM | ?wxBITMAP_TYPE_PNM_RESOURCE | ?wxBITMAP_TYPE_PCX | ?wxBITMAP_TYPE_PCX_RESOURCE | ?wxBITMAP_TYPE_PICT | ?wxBITMAP_TYPE_PICT_RESOURCE | ?wxBITMAP_TYPE_ICON | ?wxBITMAP_TYPE_ICON_RESOURCE | ?wxBITMAP_TYPE_ANI | ?wxBITMAP_TYPE_IFF | ?wxBITMAP_TYPE_TGA | ?wxBITMAP_TYPE_MACCURSOR | ?wxBITMAP_TYPE_MACCURSOR_RESOURCE | ?wxBITMAP_TYPE_ANY -spec saveFile(This, Name, Type) -> boolean() when This::wxImage(), Name::unicode:chardata(), Type::wx:wx_enum(); (This, Name, Mimetype) -> boolean() when @@ -1279,7 +1309,7 @@ saveFile(#wx_ref{type=ThisT}=This,Name,Mimetype) wxe_util:queue_cmd(This,Name_UC,Mimetype_UC,?get_env(),?wxImage_SaveFile_2_1), wxe_util:rec(?wxImage_SaveFile_2_1). -%% @equiv scale(This,Width,Height, []) +-doc(#{equiv => scale(This,Width,Height, [])}). -spec scale(This, Width, Height) -> wxImage() when This::wxImage(), Width::integer(), Height::integer(). @@ -1287,33 +1317,30 @@ scale(This,Width,Height) when is_record(This, wx_ref),is_integer(Width),is_integer(Height) -> scale(This,Width,Height, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagescale">external documentation</a>. -%%<br /> Quality = ?wxIMAGE_QUALITY_NEAREST | ?wxIMAGE_QUALITY_BILINEAR | ?wxIMAGE_QUALITY_BICUBIC | ?wxIMAGE_QUALITY_BOX_AVERAGE | ?wxIMAGE_QUALITY_NORMAL | ?wxIMAGE_QUALITY_HIGH -doc """ Returns a scaled version of the image. -This is also useful for scaling bitmaps in general as the only other way to -scale bitmaps is to blit a `m:wxMemoryDC` into another `m:wxMemoryDC`. +This is also useful for scaling bitmaps in general as the only other way to scale bitmaps +is to blit a `m:wxMemoryDC` into another `m:wxMemoryDC`. -The parameter `quality` determines what method to use for resampling the image, -see wxImageResizeQuality documentation. +The parameter `quality` determines what method to use for resampling the image, see +wxImageResizeQuality documentation. -It should be noted that although using `wxIMAGE_QUALITY_HIGH` produces much -nicer looking results it is a slower method. Downsampling will use the box -averaging method which seems to operate very fast. If you are upsampling larger -images using this method you will most likely notice that it is a bit slower and -in extreme cases it will be quite substantially slower as the bicubic algorithm -has to process a lot of data. +It should be noted that although using `wxIMAGE_QUALITY_HIGH` produces much nicer looking +results it is a slower method. Downsampling will use the box averaging method which seems +to operate very fast. If you are upsampling larger images using this method you will most +likely notice that it is a bit slower and in extreme cases it will be quite substantially +slower as the bicubic algorithm has to process a lot of data. -It should also be noted that the high quality scaling may not work as expected -when using a single mask colour for transparency, as the scaling will blur the -image and will therefore remove the mask partially. Using the alpha channel will -work. +It should also be noted that the high quality scaling may not work as expected when using +a single mask colour for transparency, as the scaling will blur the image and will +therefore remove the mask partially. Using the alpha channel will work. Example: See: `rescale/4` """. +%% Quality = ?wxIMAGE_QUALITY_NEAREST | ?wxIMAGE_QUALITY_BILINEAR | ?wxIMAGE_QUALITY_BICUBIC | ?wxIMAGE_QUALITY_BOX_AVERAGE | ?wxIMAGE_QUALITY_NORMAL | ?wxIMAGE_QUALITY_HIGH -spec scale(This, Width, Height, [Option]) -> wxImage() when This::wxImage(), Width::integer(), Height::integer(), Option :: {'quality', wx:wx_enum()}. @@ -1326,7 +1353,7 @@ scale(#wx_ref{type=ThisT}=This,Width,Height, Options) wxe_util:queue_cmd(This,Width,Height, Opts,?get_env(),?wxImage_Scale), wxe_util:rec(?wxImage_Scale). -%% @equiv size(This,Size,Pos, []) +-doc(#{equiv => size(This,Size,Pos, [])}). -spec size(This, Size, Pos) -> wxImage() when This::wxImage(), Size::{W::integer(), H::integer()}, Pos::{X::integer(), Y::integer()}. @@ -1334,20 +1361,18 @@ size(This,{SizeW,SizeH} = Size,{PosX,PosY} = Pos) when is_record(This, wx_ref),is_integer(SizeW),is_integer(SizeH),is_integer(PosX),is_integer(PosY) -> size(This,Size,Pos, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesize">external documentation</a>. -doc """ -Returns a resized version of this image without scaling it by adding either a -border with the given colour or cropping as necessary. +Returns a resized version of this image without scaling it by adding either a border with +the given colour or cropping as necessary. -The image is pasted into a new image with the given `size` and background colour -at the position `pos` relative to the upper left of the new image. +The image is pasted into a new image with the given `size` and background colour at the +position `pos` relative to the upper left of the new image. -If `red` = green = blue = -1 then the areas of the larger image not covered by -this image are made transparent by filling them with the image mask colour -(which will be allocated automatically if it isn't currently set). +If `red` = green = blue = -1 then the areas of the larger image not covered by this image +are made transparent by filling them with the image mask colour (which will be allocated +automatically if it isn't currently set). -Otherwise, the areas will be filled with the colour with the specified RGB -components. +Otherwise, the areas will be filled with the colour with the specified RGB components. See: `resize/4` """. @@ -1367,18 +1392,16 @@ size(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size,{PosX,PosY} = Pos, Options) wxe_util:queue_cmd(This,Size,Pos, Opts,?get_env(),?wxImage_Size), wxe_util:rec(?wxImage_Size). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetalpha">external documentation</a>. -doc """ This function is similar to `setData/4` and has similar restrictions. -The pointer passed to it may however be NULL in which case the function will -allocate the alpha array internally - this is useful to add alpha channel data -to an image which doesn't have any. +The pointer passed to it may however be NULL in which case the function will allocate the +alpha array internally - this is useful to add alpha channel data to an image which +doesn't have any. -If the pointer is not NULL, it must have one byte for each image pixel and be -allocated with malloc(). `m:wxImage` takes ownership of the pointer and will -free it unless `static_data` parameter is set to true - in this case the caller -should do it. +If the pointer is not NULL, it must have one byte for each image pixel and be allocated +with malloc(). `m:wxImage` takes ownership of the pointer and will free it unless `static_data` +parameter is set to true - in this case the caller should do it. """. -spec setAlpha(This, Alpha) -> 'ok' when This::wxImage(), Alpha::binary(). @@ -1387,12 +1410,11 @@ setAlpha(#wx_ref{type=ThisT}=This,Alpha) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Alpha,?get_env(),?wxImage_SetAlpha_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetalpha">external documentation</a>. -doc """ Sets the alpha value for the given pixel. -This function should only be called if the image has alpha channel data, use -`hasAlpha/1` to check for this. +This function should only be called if the image has alpha channel data, use `hasAlpha/1` to check +for this. """. -spec setAlpha(This, X, Y, Alpha) -> 'ok' when This::wxImage(), X::integer(), Y::integer(), Alpha::integer(). @@ -1401,19 +1423,17 @@ setAlpha(#wx_ref{type=ThisT}=This,X,Y,Alpha) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,X,Y,Alpha,?get_env(),?wxImage_SetAlpha_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetdata">external documentation</a>. -doc """ Sets the image data without performing checks. -The data given must have the size (width*height*3) or results will be -unexpected. Don't use this method if you aren't sure you know what you are -doing. +The data given must have the size (width*height*3) or results will be unexpected. Don't +use this method if you aren't sure you know what you are doing. The data must have been allocated with `malloc()`, `NOT` with `operator` new. -If `static_data` is false, after this call the pointer to the data is owned by -the `m:wxImage` object, that will be responsible for deleting it. Do not pass to -this function a pointer obtained through `getData/1`. +If `static_data` is false, after this call the pointer to the data is owned by the `m:wxImage` +object, that will be responsible for deleting it. Do not pass to this function a pointer +obtained through `getData/1`. """. -spec setData(This, Data) -> 'ok' when This::wxImage(), Data::binary(). @@ -1422,10 +1442,9 @@ setData(#wx_ref{type=ThisT}=This,Data) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Data,?get_env(),?wxImage_SetData_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetdata">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setData(This, Data, New_width, New_height) -> 'ok' when This::wxImage(), Data::binary(), New_width::integer(), New_height::integer(). @@ -1434,7 +1453,7 @@ setData(#wx_ref{type=ThisT}=This,Data,New_width,New_height) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Data,New_width,New_height,?get_env(),?wxImage_SetData_3). -%% @equiv setMask(This, []) +-doc(#{equiv => setMask(This, [])}). -spec setMask(This) -> 'ok' when This::wxImage(). @@ -1442,7 +1461,6 @@ setMask(This) when is_record(This, wx_ref) -> setMask(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetmask">external documentation</a>. -doc """ Specifies whether there is a mask or not. @@ -1459,7 +1477,6 @@ setMask(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxImage_SetMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetmaskcolour">external documentation</a>. -doc "Sets the mask colour for this image (and tells the image to use the mask).". -spec setMaskColour(This, Red, Green, Blue) -> 'ok' when This::wxImage(), Red::integer(), Green::integer(), Blue::integer(). @@ -1468,27 +1485,25 @@ setMaskColour(#wx_ref{type=ThisT}=This,Red,Green,Blue) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Red,Green,Blue,?get_env(),?wxImage_SetMaskColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetmaskfromimage">external documentation</a>. -doc """ -Sets image's mask so that the pixels that have RGB value of mr,mg,mb in mask -will be masked in the image. +Sets image's mask so that the pixels that have RGB value of mr,mg,mb in mask will be +masked in the image. -This is done by first finding an unused colour in the image, setting this colour -as the mask colour and then using this colour to draw all pixels in the image -who corresponding pixel in mask has given RGB value. +This is done by first finding an unused colour in the image, setting this colour as the +mask colour and then using this colour to draw all pixels in the image who corresponding +pixel in mask has given RGB value. -The parameter `mask` is the mask image to extract mask shape from. It must have -the same dimensions as the image. +The parameter `mask` is the mask image to extract mask shape from. It must have the same +dimensions as the image. -The parameters `mr`, `mg`, `mb` are the RGB values of the pixels in mask that -will be used to create the mask. +The parameters `mr`, `mg`, `mb` are the RGB values of the pixels in mask that will be +used to create the mask. -Return: Returns false if mask does not have same dimensions as the image or if -there is no unused colour left. Returns true if the mask was successfully -applied. +Return: Returns false if mask does not have same dimensions as the image or if there is +no unused colour left. Returns true if the mask was successfully applied. -Note: Note that this method involves computing the histogram, which is a -computationally intensive operation. +Note: Note that this method involves computing the histogram, which is a computationally +intensive operation. """. -spec setMaskFromImage(This, Mask, Mr, Mg, Mb) -> boolean() when This::wxImage(), Mask::wxImage(), Mr::integer(), Mg::integer(), Mb::integer(). @@ -1499,23 +1514,22 @@ setMaskFromImage(#wx_ref{type=ThisT}=This,#wx_ref{type=MaskT}=Mask,Mr,Mg,Mb) wxe_util:queue_cmd(This,Mask,Mr,Mg,Mb,?get_env(),?wxImage_SetMaskFromImage), wxe_util:rec(?wxImage_SetMaskFromImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetoption">external documentation</a>. -%% <br /> Also:<br /> -%% setOption(This, Name, Value) -> 'ok' when<br /> -%% This::wxImage(), Name::unicode:chardata(), Value::unicode:chardata().<br /> -%% -doc """ Sets a user-defined option. The function is case-insensitive to `name`. -For example, when saving as a JPEG file, the option `quality` is used, which is -a number between 0 and 100 (0 is terrible, 100 is very good). +For example, when saving as a JPEG file, the option `quality` is used, which is a number +between 0 and 100 (0 is terrible, 100 is very good). + +The lists of the currently supported options are in `getOption/2` and `getOptionInt/2` function docs. -The lists of the currently supported options are in `getOption/2` and -`getOptionInt/2` function docs. +See: +* `getOption/2` -See: `getOption/2`, `getOptionInt/2`, `hasOption/2` +* `getOptionInt/2` + +* `hasOption/2` """. -spec setOption(This, Name, Value) -> 'ok' when This::wxImage(), Name::unicode:chardata(), Value::integer(); @@ -1533,12 +1547,11 @@ setOption(#wx_ref{type=ThisT}=This,Name,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Name_UC,Value_UC,?get_env(),?wxImage_SetOption_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetpalette">external documentation</a>. -doc """ Associates a palette with the image. -The palette may be used when converting `m:wxImage` to `m:wxBitmap` (MSW only at -present) or in file save operations (none as yet). +The palette may be used when converting `m:wxImage` to `m:wxBitmap` (MSW only at present) +or in file save operations (none as yet). """. -spec setPalette(This, Palette) -> 'ok' when This::wxImage(), Palette::wxPalette:wxPalette(). @@ -1547,12 +1560,11 @@ setPalette(#wx_ref{type=ThisT}=This,#wx_ref{type=PaletteT}=Palette) -> ?CLASS(PaletteT,wxPalette), wxe_util:queue_cmd(This,Palette,?get_env(),?wxImage_SetPalette). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetrgb">external documentation</a>. -doc """ Sets the colour of the pixels within the given rectangle. -This routine performs bounds-checks for the coordinate so it can be considered a -safe way to manipulate the data. +This routine performs bounds-checks for the coordinate so it can be considered a safe way +to manipulate the data. """. -spec setRGB(This, Rect, Red, Green, Blue) -> 'ok' when This::wxImage(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, Red::integer(), Green::integer(), Blue::integer(). @@ -1561,7 +1573,6 @@ setRGB(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect,Red,Green,Blue) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,Rect,Red,Green,Blue,?get_env(),?wxImage_SetRGB_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximage.html#wximagesetrgb">external documentation</a>. -doc "Set the color of the pixel at the given x and y coordinate.". -spec setRGB(This, X, Y, R, G, B) -> 'ok' when This::wxImage(), X::integer(), Y::integer(), R::integer(), G::integer(), B::integer(). @@ -1570,12 +1581,7 @@ setRGB(#wx_ref{type=ThisT}=This,X,Y,R,G,B) ?CLASS(ThisT,wxImage), wxe_util:queue_cmd(This,X,Y,R,G,B,?get_env(),?wxImage_SetRGB_5). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See reference-counted object destruction for more info. -""". +-doc "Destroys the object". -spec destroy(This::wxImage()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxImage), diff --git a/lib/wx/src/gen/wxImageList.erl b/lib/wx/src/gen/wxImageList.erl index e47391995d74..e0086930693a 100644 --- a/lib/wx/src/gen/wxImageList.erl +++ b/lib/wx/src/gen/wxImageList.erl @@ -20,19 +20,19 @@ -module(wxImageList). -moduledoc """ -Functions for wxImageList class +A `m:wxImageList` contains a list of images, which are stored in an unspecified form. -A `m:wxImageList` contains a list of images, which are stored in an unspecified -form. Images can have masks for transparent drawing, and can be made from a -variety of sources including bitmaps and icons. +Images can have masks for transparent drawing, and can be made from a variety of sources +including bitmaps and icons. -`m:wxImageList` is used principally in conjunction with `m:wxTreeCtrl` and -`m:wxListCtrl` classes. +`m:wxImageList` is used principally in conjunction with `m:wxTreeCtrl` and `m:wxListCtrl` classes. -See: `m:wxTreeCtrl`, `m:wxListCtrl` +See: +* `m:wxTreeCtrl` -wxWidgets docs: -[wxImageList](https://docs.wxwidgets.org/3.1/classwx_image_list.html) +* `m:wxListCtrl` + +wxWidgets docs: [wxImageList](https://docs.wxwidgets.org/3.2/classwx_image_list.html) """. -include("wxe.hrl"). -export([add/2,add/3,create/3,create/4,destroy/1,draw/5,draw/6,getBitmap/2,getIcon/2, @@ -44,18 +44,16 @@ wxWidgets docs: -type wxImageList() :: wx:wx_object(). -export_type([wxImageList/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistwximagelist">external documentation</a>. -doc "Default ctor.". -spec new() -> wxImageList(). new() -> wxe_util:queue_cmd(?get_env(), ?wxImageList_new_0), wxe_util:rec(?wxImageList_new_0). -%% @equiv new(Width,Height, []) +-doc(#{equiv => new(Width,Height, [])}). -spec new(Width, Height) -> wxImageList() when Width::integer(), Height::integer(). @@ -63,10 +61,9 @@ new(Width,Height) when is_integer(Width),is_integer(Height) -> new(Width,Height, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistwximagelist">external documentation</a>. -doc """ -Constructor specifying the image size, whether image masks should be created, -and the initial size of the list. +Constructor specifying the image size, whether image masks should be created, and the +initial size of the list. See: `create/4` """. @@ -83,17 +80,15 @@ new(Width,Height, Options) wxe_util:queue_cmd(Width,Height, Opts,?get_env(),?wxImageList_new_3), wxe_util:rec(?wxImageList_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistadd">external documentation</a>. -doc """ Adds a new image using an icon. Return: The new zero-based image index. -Remark: The original bitmap or icon is not affected by the `add/3` operation, -and can be deleted afterwards. If the bitmap is wider than the images in the -list, then the bitmap will automatically be split into smaller images, each -matching the dimensions of the image list. This does not apply when adding -icons. +Remark: The original bitmap or icon is not affected by the `add/3` operation, and can be deleted +afterwards. If the bitmap is wider than the images in the list, then the bitmap will +automatically be split into smaller images, each matching the dimensions of the image +list. This does not apply when adding icons. Only for:wxmsw,wxosx """. @@ -111,21 +106,15 @@ add(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon) -> wxe_util:queue_cmd(This,wx:typeCast(Icon, IconType),?get_env(),?wxImageList_Add_1), wxe_util:rec(?wxImageList_Add_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistadd">external documentation</a>. -%% <br /> Also:<br /> -%% add(This, Bitmap, MaskColour) -> integer() when<br /> -%% This::wxImageList(), Bitmap::wxBitmap:wxBitmap(), MaskColour::wx:wx_colour().<br /> -%% -doc """ Adds a new image or images using a bitmap and mask colour. Return: The new zero-based image index. -Remark: The original bitmap or icon is not affected by the `add/3` operation, -and can be deleted afterwards. If the bitmap is wider than the images in the -list, then the bitmap will automatically be split into smaller images, each -matching the dimensions of the image list. This does not apply when adding -icons. +Remark: The original bitmap or icon is not affected by the `add/3` operation, and can be deleted +afterwards. If the bitmap is wider than the images in the list, then the bitmap will +automatically be split into smaller images, each matching the dimensions of the image +list. This does not apply when adding icons. """. -spec add(This, Bitmap, Mask) -> integer() when This::wxImageList(), Bitmap::wxBitmap:wxBitmap(), Mask::wxBitmap:wxBitmap(); @@ -144,7 +133,7 @@ add(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap,MaskColour) wxe_util:queue_cmd(This,Bitmap,wxe_util:color(MaskColour),?get_env(),?wxImageList_Add_2_1), wxe_util:rec(?wxImageList_Add_2_1). -%% @equiv create(This,Width,Height, []) +-doc(#{equiv => create(This,Width,Height, [])}). -spec create(This, Width, Height) -> boolean() when This::wxImageList(), Width::integer(), Height::integer(). @@ -152,7 +141,6 @@ create(This,Width,Height) when is_record(This, wx_ref),is_integer(Width),is_integer(Height) -> create(This,Width,Height, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistcreate">external documentation</a>. -doc """ Initializes the list. @@ -172,7 +160,7 @@ create(#wx_ref{type=ThisT}=This,Width,Height, Options) wxe_util:queue_cmd(This,Width,Height, Opts,?get_env(),?wxImageList_Create), wxe_util:rec(?wxImageList_Create). -%% @equiv draw(This,Index,Dc,X,Y, []) +-doc(#{equiv => draw(This,Index,Dc,X,Y, [])}). -spec draw(This, Index, Dc, X, Y) -> boolean() when This::wxImageList(), Index::integer(), Dc::wxDC:wxDC(), X::integer(), Y::integer(). @@ -180,7 +168,6 @@ draw(This,Index,Dc,X,Y) when is_record(This, wx_ref),is_integer(Index),is_record(Dc, wx_ref),is_integer(X),is_integer(Y) -> draw(This,Index,Dc,X,Y, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistdraw">external documentation</a>. -doc "Draws a specified image onto a device context.". -spec draw(This, Index, Dc, X, Y, [Option]) -> boolean() when This::wxImageList(), Index::integer(), Dc::wxDC:wxDC(), X::integer(), Y::integer(), @@ -197,7 +184,6 @@ draw(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=DcT}=Dc,X,Y, Options) wxe_util:queue_cmd(This,Index,Dc,X,Y, Opts,?get_env(),?wxImageList_Draw), wxe_util:rec(?wxImageList_Draw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistgetbitmap">external documentation</a>. -doc "Returns the bitmap corresponding to the given index.". -spec getBitmap(This, Index) -> wxBitmap:wxBitmap() when This::wxImageList(), Index::integer(). @@ -207,7 +193,6 @@ getBitmap(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxImageList_GetBitmap), wxe_util:rec(?wxImageList_GetBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistgeticon">external documentation</a>. -doc "Returns the icon corresponding to the given index.". -spec getIcon(This, Index) -> wxIcon:wxIcon() when This::wxImageList(), Index::integer(). @@ -217,7 +202,6 @@ getIcon(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxImageList_GetIcon), wxe_util:rec(?wxImageList_GetIcon). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistgetimagecount">external documentation</a>. -doc "Returns the number of images in the list.". -spec getImageCount(This) -> integer() when This::wxImageList(). @@ -226,15 +210,13 @@ getImageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImageList_GetImageCount), wxe_util:rec(?wxImageList_GetImageCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistgetsize">external documentation</a>. -doc """ Retrieves the size of the images in the list. -Currently, the `index` parameter is ignored as all images in the list have the -same size. +Currently, the `index` parameter is ignored as all images in the list have the same size. -Return: true if the function succeeded, false if it failed (for example, if the -image list was not yet initialized). +Return: true if the function succeeded, false if it failed (for example, if the image +list was not yet initialized). """. -spec getSize(This, Index) -> Result when Result ::{Res ::boolean(), Width::integer(), Height::integer()}, @@ -245,7 +227,6 @@ getSize(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxImageList_GetSize), wxe_util:rec(?wxImageList_GetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistremove">external documentation</a>. -doc "Removes the image at the given position.". -spec remove(This, Index) -> boolean() when This::wxImageList(), Index::integer(). @@ -255,7 +236,6 @@ remove(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxImageList_Remove), wxe_util:rec(?wxImageList_Remove). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistremoveall">external documentation</a>. -doc "Removes all the images in the list.". -spec removeAll(This) -> boolean() when This::wxImageList(). @@ -264,14 +244,12 @@ removeAll(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxImageList_RemoveAll), wxe_util:rec(?wxImageList_RemoveAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistreplace">external documentation</a>. -doc """ Replaces the existing image with the new image. Return: true if the replacement was successful, false otherwise. -Remark: The original bitmap or icon is not affected by the `replace/4` -operation, and can be deleted afterwards. +Remark: The original bitmap or icon is not affected by the `replace/4` operation, and can be deleted afterwards. Only for:wxmsw,wxosx """. @@ -290,7 +268,6 @@ replace(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=IconT}=Icon) wxe_util:queue_cmd(This,Index,wx:typeCast(Icon, IconType),?get_env(),?wxImageList_Replace_2), wxe_util:rec(?wxImageList_Replace_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wximagelist.html#wximagelistreplace">external documentation</a>. -doc """ Replaces the existing image with the new image. @@ -298,8 +275,8 @@ Windows only. Return: true if the replacement was successful, false otherwise. -Remark: The original bitmap or icon is not affected by the `replace/4` -operation, and can be deleted afterwards. +Remark: The original bitmap or icon is not affected by the `replace/4` operation, and can be deleted +afterwards. """. -spec replace(This, Index, Bitmap, Mask) -> boolean() when This::wxImageList(), Index::integer(), Bitmap::wxBitmap:wxBitmap(), Mask::wxBitmap:wxBitmap(). @@ -311,8 +288,7 @@ replace(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=BitmapT}=Bitmap,#wx_ref{type wxe_util:queue_cmd(This,Index,Bitmap,Mask,?get_env(),?wxImageList_Replace_3), wxe_util:rec(?wxImageList_Replace_3). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxImageList()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxImageList), diff --git a/lib/wx/src/gen/wxInitDialogEvent.erl b/lib/wx/src/gen/wxInitDialogEvent.erl index 5f91957f62eb..3b66cf6d97eb 100644 --- a/lib/wx/src/gen/wxInitDialogEvent.erl +++ b/lib/wx/src/gen/wxInitDialogEvent.erl @@ -20,26 +20,23 @@ -module(wxInitDialogEvent). -moduledoc """ -Functions for wxInitDialogEvent class - A `m:wxInitDialogEvent` is sent as a dialog or panel is being initialised. + Handlers for this event can transfer data to the window. The default handler calls `wxWindow:transferDataToWindow/1`. -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxInitDialogEvent](https://docs.wxwidgets.org/3.1/classwx_init_dialog_event.html) +wxWidgets docs: [wxInitDialogEvent](https://docs.wxwidgets.org/3.2/classwx_init_dialog_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxInitDialogEventType`](`t:wxInitDialogEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxInitDialogEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -52,36 +49,26 @@ this type. -include("wx.hrl"). -type wxInitDialogEventType() :: 'init_dialog'. -export_type([wxInitDialogEvent/0, wxInitDialog/0, wxInitDialogEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxJoystickEvent.erl b/lib/wx/src/gen/wxJoystickEvent.erl index a3a83fcbddd2..15e58c7f323b 100644 --- a/lib/wx/src/gen/wxJoystickEvent.erl +++ b/lib/wx/src/gen/wxJoystickEvent.erl @@ -20,23 +20,18 @@ -module(wxJoystickEvent). -moduledoc """ -Functions for wxJoystickEvent class +This event class contains information about joystick events, particularly events received +by windows. -This event class contains information about joystick events, particularly events -received by windows. +This class is derived, and can use functions, from: -See: `wxJoystick` (not implemented in wx) +* `m:wxEvent` -This class is derived (and can use functions) from: `m:wxEvent` - -wxWidgets docs: -[wxJoystickEvent](https://docs.wxwidgets.org/3.1/classwx_joystick_event.html) +wxWidgets docs: [wxJoystickEvent](https://docs.wxwidgets.org/3.2/classwx_joystick_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxJoystickEventType`](`t:wxJoystickEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxJoystickEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([buttonDown/1,buttonDown/2,buttonIsDown/1,buttonIsDown/2,buttonUp/1, @@ -51,12 +46,11 @@ this type. -include("wx.hrl"). -type wxJoystickEventType() :: 'joy_button_down' | 'joy_button_up' | 'joy_move' | 'joy_zmove'. -export_type([wxJoystickEvent/0, wxJoystick/0, wxJoystickEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv buttonDown(This, []) +-doc(#{equiv => buttonDown(This, [])}). -spec buttonDown(This) -> boolean() when This::wxJoystickEvent(). @@ -64,11 +58,7 @@ buttonDown(This) when is_record(This, wx_ref) -> buttonDown(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventbuttondown">external documentation</a>. --doc """ -Returns true if the event was a down event from the specified button (or any -button). -""". +-doc "Returns true if the event was a down event from the specified button (or any button).". -spec buttonDown(This, [Option]) -> boolean() when This::wxJoystickEvent(), Option :: {'but', integer()}. @@ -81,7 +71,7 @@ buttonDown(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxJoystickEvent_ButtonDown), wxe_util:rec(?wxJoystickEvent_ButtonDown). -%% @equiv buttonIsDown(This, []) +-doc(#{equiv => buttonIsDown(This, [])}). -spec buttonIsDown(This) -> boolean() when This::wxJoystickEvent(). @@ -89,7 +79,6 @@ buttonIsDown(This) when is_record(This, wx_ref) -> buttonIsDown(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventbuttonisdown">external documentation</a>. -doc "Returns true if the specified button (or any button) was in a down state.". -spec buttonIsDown(This, [Option]) -> boolean() when This::wxJoystickEvent(), @@ -103,7 +92,7 @@ buttonIsDown(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxJoystickEvent_ButtonIsDown), wxe_util:rec(?wxJoystickEvent_ButtonIsDown). -%% @equiv buttonUp(This, []) +-doc(#{equiv => buttonUp(This, [])}). -spec buttonUp(This) -> boolean() when This::wxJoystickEvent(). @@ -111,11 +100,7 @@ buttonUp(This) when is_record(This, wx_ref) -> buttonUp(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventbuttonup">external documentation</a>. --doc """ -Returns true if the event was an up event from the specified button (or any -button). -""". +-doc "Returns true if the event was an up event from the specified button (or any button).". -spec buttonUp(This, [Option]) -> boolean() when This::wxJoystickEvent(), Option :: {'but', integer()}. @@ -128,16 +113,15 @@ buttonUp(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxJoystickEvent_ButtonUp), wxe_util:rec(?wxJoystickEvent_ButtonUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventgetbuttonchange">external documentation</a>. -doc """ Returns the identifier of the button changing state. -The return value is where `n` is the index of the button changing state, which -can also be retrieved using `GetButtonOrdinal()` (not implemented in wx). +The return value is where `n` is the index of the button changing state, which can also +be retrieved using `GetButtonOrdinal()` (not implemented in wx). -Note that for `n` equal to 1, 2, 3 or 4 there are predefined `wxJOY_BUTTONn` -constants which can be used for more clarity, however these constants are not -defined for the buttons beyond the first four. +Note that for `n` equal to 1, 2, 3 or 4 there are predefined `wxJOY_BUTTONn` constants +which can be used for more clarity, however these constants are not defined for the +buttons beyond the first four. """. -spec getButtonChange(This) -> integer() when This::wxJoystickEvent(). @@ -146,7 +130,6 @@ getButtonChange(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_GetButtonChange), wxe_util:rec(?wxJoystickEvent_GetButtonChange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventgetbuttonstate">external documentation</a>. -doc """ Returns the down state of the buttons. @@ -159,10 +142,9 @@ getButtonState(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_GetButtonState), wxe_util:rec(?wxJoystickEvent_GetButtonState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventgetjoystick">external documentation</a>. -doc """ -Returns the identifier of the joystick generating the event - one of wxJOYSTICK1 -and wxJOYSTICK2. +Returns the identifier of the joystick generating the event - one of wxJOYSTICK1 and +wxJOYSTICK2. """. -spec getJoystick(This) -> integer() when This::wxJoystickEvent(). @@ -171,7 +153,6 @@ getJoystick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_GetJoystick), wxe_util:rec(?wxJoystickEvent_GetJoystick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventgetposition">external documentation</a>. -doc """ Returns the x, y position of the joystick event. @@ -184,7 +165,6 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_GetPosition), wxe_util:rec(?wxJoystickEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventgetzposition">external documentation</a>. -doc """ Returns the z position of the joystick event. @@ -197,11 +177,7 @@ getZPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_GetZPosition), wxe_util:rec(?wxJoystickEvent_GetZPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventisbutton">external documentation</a>. --doc """ -Returns true if this was a button up or down event (`not` 'is any button -down?'). -""". +-doc "Returns true if this was a button up or down event (`not` 'is any button down?').". -spec isButton(This) -> boolean() when This::wxJoystickEvent(). isButton(#wx_ref{type=ThisT}=This) -> @@ -209,7 +185,6 @@ isButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_IsButton), wxe_util:rec(?wxJoystickEvent_IsButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventismove">external documentation</a>. -doc "Returns true if this was an x, y move event.". -spec isMove(This) -> boolean() when This::wxJoystickEvent(). @@ -218,7 +193,6 @@ isMove(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxJoystickEvent_IsMove), wxe_util:rec(?wxJoystickEvent_IsMove). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxjoystickevent.html#wxjoystickeventiszmove">external documentation</a>. -doc "Returns true if this was a z move event.". -spec isZMove(This) -> boolean() when This::wxJoystickEvent(). @@ -228,30 +202,21 @@ isZMove(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxJoystickEvent_IsZMove). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxKeyEvent.erl b/lib/wx/src/gen/wxKeyEvent.erl index 958ed7758f33..720464fc2e30 100644 --- a/lib/wx/src/gen/wxKeyEvent.erl +++ b/lib/wx/src/gen/wxKeyEvent.erl @@ -20,118 +20,110 @@ -module(wxKeyEvent). -moduledoc """ -Functions for wxKeyEvent class - This event class contains information about key press and release events. -The main information carried by this event is the key being pressed or released. -It can be accessed using either `getKeyCode/1` function or `getUnicodeKey/1`. -For the printable characters, the latter should be used as it works for any -keys, including non-Latin-1 characters that can be entered when using national -keyboard layouts. `getKeyCode/1` should be used to handle special characters -(such as cursor arrows keys or `HOME` or `INS` and so on) which correspond to -?wxKeyCode enum elements above the `WXK_START` constant. While `getKeyCode/1` -also returns the character code for Latin-1 keys for compatibility, it doesn't -work for Unicode characters in general and will return `WXK_NONE` for any -non-Latin-1 ones. For this reason, it's recommended to always use -`getUnicodeKey/1` and only fall back to `getKeyCode/1` if `getUnicodeKey/1` -returned `WXK_NONE` meaning that the event corresponds to a non-printable -special keys. - -While both of these functions can be used with the events of `wxEVT_KEY_DOWN`, -`wxEVT_KEY_UP` and `wxEVT_CHAR` types, the values returned by them are different -for the first two events and the last one. For the latter, the key returned -corresponds to the character that would appear in e.g. a text zone if the user -pressed the key in it. As such, its value depends on the current state of the -Shift key and, for the letters, on the state of Caps Lock modifier. For example, -if `A` key is pressed without Shift being held down, `m:wxKeyEvent` of type -`wxEVT_CHAR` generated for this key press will return (from either -`getKeyCode/1` or `getUnicodeKey/1` as their meanings coincide for ASCII -characters) key code of 97 corresponding the ASCII value of `a`. And if the same -key is pressed but with Shift being held (or Caps Lock being active), then the -key could would be 65, i.e. ASCII value of capital `A`. +The main information carried by this event is the key being pressed or released. It can +be accessed using either `getKeyCode/1` function or `getUnicodeKey/1`. For the printable characters, the latter should be +used as it works for any keys, including non-Latin-1 characters that can be entered when +using national keyboard layouts. `getKeyCode/1` should be used to handle special characters (such as +cursor arrows keys or `HOME` or `INS` and so on) which correspond to ?wxKeyCode enum +elements above the `WXK_START` constant. While `getKeyCode/1` also returns the character code for +Latin-1 keys for compatibility, it doesn't work for Unicode characters in general and will +return `WXK_NONE` for any non-Latin-1 ones. For this reason, it's recommended to always +use `getUnicodeKey/1` and only fall back to `getKeyCode/1` if `getUnicodeKey/1` returned `WXK_NONE` meaning that the event corresponds to +a non-printable special keys. + +While both of these functions can be used with the events of `wxEVT_KEY_DOWN`, `wxEVT_KEY_UP` +and `wxEVT_CHAR` types, the values returned by them are different for the first two +events and the last one. For the latter, the key returned corresponds to the character +that would appear in e.g. a text zone if the user pressed the key in it. As such, its +value depends on the current state of the Shift key and, for the letters, on the state of +Caps Lock modifier. For example, if `A` key is pressed without Shift being held down, `m:wxKeyEvent` +of type `wxEVT_CHAR` generated for this key press will return (from either `getKeyCode/1` or `getUnicodeKey/1` as their +meanings coincide for ASCII characters) key code of 97 corresponding the ASCII value of `a`. +And if the same key is pressed but with Shift being held (or Caps Lock being active), then +the key could would be 65, i.e. ASCII value of capital `A`. However for the key down and up events the returned key code will instead be `A` -independently of the state of the modifier keys i.e. it depends only on physical -key being pressed and is not translated to its logical representation using the -current keyboard state. Such untranslated key codes are defined as follows: - -Notice that the first rule applies to all Unicode letters, not just the usual -Latin-1 ones. However for non-Latin-1 letters only `getUnicodeKey/1` can be used -to retrieve the key code as `getKeyCode/1` just returns `WXK_NONE` in this case. - -To summarize: you should handle `wxEVT_CHAR` if you need the translated key and -`wxEVT_KEY_DOWN` if you only need the value of the key itself, independent of -the current keyboard state. - -Note: Not all key down events may be generated by the user. As an example, -`wxEVT_KEY_DOWN` with `=` key code can be generated using the standard US -keyboard layout but not using the German one because the `=` key corresponds to -Shift-0 key combination in this layout and the key code for it is `0`, not `=`. -Because of this you should avoid requiring your users to type key events that -might be impossible to enter on their keyboard. - -Another difference between key and char events is that another kind of -translation is done for the latter ones when the Control key is pressed: char -events for ASCII letters in this case carry codes corresponding to the ASCII -value of Ctrl-Latter, i.e. 1 for Ctrl-A, 2 for Ctrl-B and so on until 26 for -Ctrl-Z. This is convenient for terminal-like applications and can be completely -ignored by all the other ones (if you need to handle Ctrl-A it is probably a -better idea to use the key event rather than the char one). Notice that -currently no translation is done for the presses of [, `\`, ], `^` and `_` keys -which might be mapped to ASCII values from 27 to 31. Since version 2.9.2, the -enum values `WXK_CONTROL_A` \- `WXK_CONTROL_Z` can be used instead of the -non-descriptive constant values 1-26. - -Finally, modifier keys only generate key events but no char events at all. The -modifiers keys are `WXK_SHIFT`, `WXK_CONTROL`, `WXK_ALT` and various -`WXK_WINDOWS_XXX` from ?wxKeyCode enum. - -Modifier keys events are special in one additional aspect: usually the keyboard -state associated with a key press is well defined, e.g. `shiftDown/1` returns -`true` only if the Shift key was held pressed when the key that generated this -event itself was pressed. There is an ambiguity for the key press events for -Shift key itself however. By convention, it is considered to be already pressed -when it is pressed and already released when it is released. In other words, -`wxEVT_KEY_DOWN` event for the Shift key itself will have `wxMOD_SHIFT` in -`getModifiers/1` and `shiftDown/1` will return true while the `wxEVT_KEY_UP` -event for Shift itself will not have `wxMOD_SHIFT` in its modifiers and -`shiftDown/1` will return false. - -`Tip:` You may discover the key codes and modifiers generated by all the keys on -your system interactively by running the page_samples_keyboard wxWidgets sample -and pressing some keys in it. - -Note: If a key down (`EVT_KEY_DOWN`) event is caught and the event handler does -not call `event.Skip()` then the corresponding char event (`EVT_CHAR`) will not -happen. This is by design and enables the programs that handle both types of -events to avoid processing the same key twice. As a consequence, if you do not -want to suppress the `wxEVT_CHAR` events for the keys you handle, always call -`event.Skip()` in your `wxEVT_KEY_DOWN` handler. Not doing may also prevent -accelerators defined using this key from working. +independently of the state of the modifier keys i.e. it depends only on physical key being +pressed and is not translated to its logical representation using the current keyboard +state. Such untranslated key codes are defined as follows: + +* For the letters they correspond to the `upper` case value of the letter. + +* For the other alphanumeric keys (e.g. `7` or `+`), the untranslated key code corresponds to +the character produced by the key when it is pressed without Shift. E.g. in standard US +keyboard layout the untranslated key code for the key `=/+` in the upper right corner of +the keyboard is 61 which is the ASCII value of `=`. + +* For the rest of the keys (i.e. special non-printable keys) it is the same as the normal +key code as no translation is used anyhow. + +Notice that the first rule applies to all Unicode letters, not just the usual Latin-1 +ones. However for non-Latin-1 letters only `getUnicodeKey/1` can be used to retrieve the key code as `getKeyCode/1` just +returns `WXK_NONE` in this case. + +To summarize: you should handle `wxEVT_CHAR` if you need the translated key and `wxEVT_KEY_DOWN` +if you only need the value of the key itself, independent of the current keyboard state. + +Note: Not all key down events may be generated by the user. As an example, `wxEVT_KEY_DOWN` +with `=` key code can be generated using the standard US keyboard layout but not using +the German one because the `=` key corresponds to Shift-0 key combination in this layout +and the key code for it is `0`, not `=`. Because of this you should avoid requiring your +users to type key events that might be impossible to enter on their keyboard. + +Another difference between key and char events is that another kind of translation is +done for the latter ones when the Control key is pressed: char events for ASCII letters in +this case carry codes corresponding to the ASCII value of Ctrl-Latter, i.e. 1 for Ctrl-A, +2 for Ctrl-B and so on until 26 for Ctrl-Z. This is convenient for terminal-like +applications and can be completely ignored by all the other ones (if you need to handle +Ctrl-A it is probably a better idea to use the key event rather than the char one). Notice +that currently no translation is done for the presses of [, `\`, ], `^` and `_` keys which +might be mapped to ASCII values from 27 to 31. Since version 2.9.2, the enum values `WXK_CONTROL_A` +- `WXK_CONTROL_Z` can be used instead of the non-descriptive constant values 1-26. + +Finally, modifier keys only generate key events but no char events at all. The modifiers +keys are `WXK_SHIFT`, `WXK_CONTROL`, `WXK_ALT` and various `WXK_WINDOWS_XXX` from +?wxKeyCode enum. + +Modifier keys events are special in one additional aspect: usually the keyboard state +associated with a key press is well defined, e.g. `shiftDown/1` returns `true` only if the Shift key +was held pressed when the key that generated this event itself was pressed. There is an +ambiguity for the key press events for Shift key itself however. By convention, it is +considered to be already pressed when it is pressed and already released when it is +released. In other words, `wxEVT_KEY_DOWN` event for the Shift key itself will have `wxMOD_SHIFT` +in `getModifiers/1` and `shiftDown/1` will return true while the `wxEVT_KEY_UP` event for Shift itself will not have `wxMOD_SHIFT` +in its modifiers and `shiftDown/1` will return false. + +`Tip:` You may discover the key codes and modifiers generated by all the keys on your +system interactively by running the page_samples_keyboard wxWidgets sample and pressing +some keys in it. + +Note: If a key down (`EVT_KEY_DOWN`) event is caught and the event handler does not call `event.Skip()` +then the corresponding char event (`EVT_CHAR`) will not happen. This is by design and +enables the programs that handle both types of events to avoid processing the same key +twice. As a consequence, if you do not want to suppress the `wxEVT_CHAR` events for the +keys you handle, always call `event.Skip()` in your `wxEVT_KEY_DOWN` handler. Not doing +may also prevent accelerators defined using this key from working. Note: If a key is maintained in a pressed state, you will typically get a lot of -(automatically generated) key down events but only one key up one at the end -when the key is released so it is wrong to assume that there is one up event -corresponding to each down one. +(automatically generated) key down events but only one key up one at the end when the key +is released so it is wrong to assume that there is one up event corresponding to each down one. -Note: For Windows programmers: The key and char events in wxWidgets are similar -to but slightly different from Windows `WM_KEYDOWN` and `WM_CHAR` events. In -particular, Alt-x combination will generate a char event in wxWidgets (unless it -is used as an accelerator) and almost all keys, including ones without ASCII -equivalents, generate char events too. +Note: For Windows programmers: The key and char events in wxWidgets are similar to but +slightly different from Windows `WM_KEYDOWN` and `WM_CHAR` events. In particular, Alt-x +combination will generate a char event in wxWidgets (unless it is used as an accelerator) +and almost all keys, including ones without ASCII equivalents, generate char events too. -See: `wxKeyboardState` (not implemented in wx) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxKeyEvent](https://docs.wxwidgets.org/3.1/classwx_key_event.html) +wxWidgets docs: [wxKeyEvent](https://docs.wxwidgets.org/3.2/classwx_key_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxKeyEventType`](`t:wxKeyEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxKeyEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([altDown/1,cmdDown/1,controlDown/1,getKeyCode/1,getModifiers/1,getPosition/1, @@ -146,12 +138,10 @@ subscribe to events of this type. -include("wx.hrl"). -type wxKeyEventType() :: 'char' | 'char_hook' | 'key_down' | 'key_up'. -export_type([wxKeyEvent/0, wxKey/0, wxKeyEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventaltdown">external documentation</a>. -doc """ Returns true if the Alt key is pressed. @@ -164,7 +154,6 @@ altDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_AltDown), wxe_util:rec(?wxKeyEvent_AltDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventcmddown">external documentation</a>. -doc """ Returns true if the key used for command accelerators is pressed. @@ -179,7 +168,6 @@ cmdDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_CmdDown), wxe_util:rec(?wxKeyEvent_CmdDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventcontroldown">external documentation</a>. -doc """ Returns true if the Control key or Apple/Command key under macOS is pressed. @@ -194,24 +182,21 @@ controlDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_ControlDown), wxe_util:rec(?wxKeyEvent_ControlDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetkeycode">external documentation</a>. -doc """ Returns the key code of the key that generated this event. -ASCII symbols return normal ASCII values, while events from special keys such as -"left cursor arrow" (`WXK_LEFT`) return values outside of the ASCII range. See -?wxKeyCode for a full list of the virtual key codes. +ASCII symbols return normal ASCII values, while events from special keys such as "left +cursor arrow" (`WXK_LEFT`) return values outside of the ASCII range. See ?wxKeyCode for a +full list of the virtual key codes. -Note that this method returns a meaningful value only for special -non-alphanumeric keys or if the user entered a Latin-1 character (this includes -ASCII and the accented letters found in Western European languages but not -letters of other alphabets such as e.g. Cyrillic). Otherwise it simply method -returns `WXK_NONE` and `getUnicodeKey/1` should be used to obtain the +Note that this method returns a meaningful value only for special non-alphanumeric keys +or if the user entered a Latin-1 character (this includes ASCII and the accented letters +found in Western European languages but not letters of other alphabets such as e.g. +Cyrillic). Otherwise it simply method returns `WXK_NONE` and `getUnicodeKey/1` should be used to obtain the corresponding Unicode character. -Using `getUnicodeKey/1` is in general the right thing to do if you are -interested in the characters typed by the user, `getKeyCode/1` should be only -used for special keys (for which `getUnicodeKey/1` returns `WXK_NONE`). To +Using `getUnicodeKey/1` is in general the right thing to do if you are interested in the characters typed +by the user, `getKeyCode/1` should be only used for special keys (for which `getUnicodeKey/1` returns `WXK_NONE`). To handle both kinds of keys you might write: """. -spec getKeyCode(This) -> integer() when @@ -221,24 +206,20 @@ getKeyCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetKeyCode), wxe_util:rec(?wxKeyEvent_GetKeyCode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetmodifiers">external documentation</a>. -doc """ Return the bit mask of all pressed modifier keys. -The return value is a combination of `wxMOD_ALT`, `wxMOD_CONTROL`, `wxMOD_SHIFT` -and `wxMOD_META` bit masks. Additionally, `wxMOD_NONE` is defined as 0, i.e. -corresponds to no modifiers (see `HasAnyModifiers()` (not implemented in wx)) -and `wxMOD_CMD` is either `wxMOD_CONTROL` (MSW and Unix) or `wxMOD_META` (Mac), -see `cmdDown/1`. See ?wxKeyModifier for the full list of modifiers. +The return value is a combination of `wxMOD_ALT`, `wxMOD_CONTROL`, `wxMOD_SHIFT` and `wxMOD_META` +bit masks. Additionally, `wxMOD_NONE` is defined as 0, i.e. corresponds to no modifiers +(see `HasAnyModifiers()` (not implemented in wx)) and `wxMOD_CMD` is either `wxMOD_CONTROL` +(MSW and Unix) or `wxMOD_META` (Mac), see `cmdDown/1`. See ?wxKeyModifier for the full list of modifiers. -Notice that this function is easier to use correctly than, for example, -`controlDown/1` because when using the latter you also have to remember to test -that none of the other modifiers is pressed: +Notice that this function is easier to use correctly than, for example, `controlDown/1` because when +using the latter you also have to remember to test that none of the other modifiers is pressed: -and forgetting to do it can result in serious program bugs (e.g. program not -working with European keyboard layout where `AltGr` key which is seen by the -program as combination of CTRL and ALT is used). On the other hand, you can -simply write: +and forgetting to do it can result in serious program bugs (e.g. program not working with +European keyboard layout where `AltGr` key which is seen by the program as combination of +CTRL and ALT is used). On the other hand, you can simply write: with this function. """. @@ -249,12 +230,11 @@ getModifiers(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetModifiers), wxe_util:rec(?wxKeyEvent_GetModifiers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetposition">external documentation</a>. -doc """ Obtains the position (in client coordinates) at which the key was pressed. -Notice that under most platforms this position is simply the current mouse -pointer position and has no special relationship to the key event itself. +Notice that under most platforms this position is simply the current mouse pointer +position and has no special relationship to the key event itself. `x` and `y` may be NULL if the corresponding coordinate is not needed. """. @@ -265,21 +245,17 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetPosition), wxe_util:rec(?wxKeyEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetrawkeycode">external documentation</a>. -doc """ Returns the raw key code for this event. -The flags are platform-dependent and should only be used if the functionality -provided by other `m:wxKeyEvent` methods is insufficient. +The flags are platform-dependent and should only be used if the functionality provided by +other `m:wxKeyEvent` methods is insufficient. -Under MSW, the raw key code is the value of `wParam` parameter of the -corresponding message. +Under MSW, the raw key code is the value of `wParam` parameter of the corresponding message. -Under GTK, the raw key code is the `keyval` field of the corresponding GDK -event. +Under GTK, the raw key code is the `keyval` field of the corresponding GDK event. -Under macOS, the raw key code is the `keyCode` field of the corresponding -NSEvent. +Under macOS, the raw key code is the `keyCode` field of the corresponding NSEvent. Note: Currently the raw key codes are not supported by all ports, use #ifdef wxHAS_RAW_KEY_CODES to determine if this feature is available. @@ -291,18 +267,15 @@ getRawKeyCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetRawKeyCode), wxe_util:rec(?wxKeyEvent_GetRawKeyCode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetrawkeyflags">external documentation</a>. -doc """ Returns the low level key flags for this event. -The flags are platform-dependent and should only be used if the functionality -provided by other `m:wxKeyEvent` methods is insufficient. +The flags are platform-dependent and should only be used if the functionality provided by +other `m:wxKeyEvent` methods is insufficient. -Under MSW, the raw flags are just the value of `lParam` parameter of the -corresponding message. +Under MSW, the raw flags are just the value of `lParam` parameter of the corresponding message. -Under GTK, the raw flags contain the `hardware_keycode` field of the -corresponding GDK event. +Under GTK, the raw flags contain the `hardware_keycode` field of the corresponding GDK event. Under macOS, the raw flags contain the modifiers state. @@ -316,16 +289,13 @@ getRawKeyFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetRawKeyFlags), wxe_util:rec(?wxKeyEvent_GetRawKeyFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetunicodekey">external documentation</a>. -doc """ Returns the Unicode character corresponding to this key event. -If the key pressed doesn't have any character value (e.g. a cursor key) this -method will return `WXK_NONE`. In this case you should use `getKeyCode/1` to -retrieve the value of the key. +If the key pressed doesn't have any character value (e.g. a cursor key) this method will +return `WXK_NONE`. In this case you should use `getKeyCode/1` to retrieve the value of the key. -This function is only available in Unicode build, i.e. when `wxUSE_UNICODE` -is 1. +This function is only available in Unicode build, i.e. when `wxUSE_UNICODE` is 1. """. -spec getUnicodeKey(This) -> integer() when This::wxKeyEvent(). @@ -334,7 +304,6 @@ getUnicodeKey(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetUnicodeKey), wxe_util:rec(?wxKeyEvent_GetUnicodeKey). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgetx">external documentation</a>. -doc """ Returns the X position (in client coordinates) of the event. @@ -347,7 +316,6 @@ getX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetX), wxe_util:rec(?wxKeyEvent_GetX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventgety">external documentation</a>. -doc """ Returns the Y position (in client coordinates) of the event. @@ -360,17 +328,15 @@ getY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_GetY), wxe_util:rec(?wxKeyEvent_GetY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventhasmodifiers">external documentation</a>. -doc """ Returns true if Control or Alt are pressed. -Checks if Control, Alt or, under macOS only, Command key are pressed (notice -that the real Control key is still taken into account under OS X too). +Checks if Control, Alt or, under macOS only, Command key are pressed (notice that the +real Control key is still taken into account under OS X too). -This method returns false if only Shift is pressed for compatibility reasons and -also because pressing Shift usually doesn't change the interpretation of key -events, see `HasAnyModifiers()` (not implemented in wx) if you want to take -Shift into account as well. +This method returns false if only Shift is pressed for compatibility reasons and also +because pressing Shift usually doesn't change the interpretation of key events, see `HasAnyModifiers()` +(not implemented in wx) if you want to take Shift into account as well. """. -spec hasModifiers(This) -> boolean() when This::wxKeyEvent(). @@ -379,13 +345,11 @@ hasModifiers(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_HasModifiers), wxe_util:rec(?wxKeyEvent_HasModifiers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventmetadown">external documentation</a>. -doc """ Returns true if the Meta/Windows/Apple key is pressed. -This function tests the state of the key traditionally called Meta under Unix -systems, Windows keys under MSW Notice that `getModifiers/1` should usually be -used instead of this one. +This function tests the state of the key traditionally called Meta under Unix systems, +Windows keys under MSW Notice that `getModifiers/1` should usually be used instead of this one. See: `cmdDown/1` """. @@ -396,7 +360,6 @@ metaDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxKeyEvent_MetaDown), wxe_util:rec(?wxKeyEvent_MetaDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxkeyevent.html#wxkeyeventshiftdown">external documentation</a>. -doc """ Returns true if the Shift key is pressed. @@ -412,30 +375,21 @@ shiftDown(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxKeyEvent_ShiftDown). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxLayoutAlgorithm.erl b/lib/wx/src/gen/wxLayoutAlgorithm.erl index 4603c9f35408..f2a9a1a15b78 100644 --- a/lib/wx/src/gen/wxLayoutAlgorithm.erl +++ b/lib/wx/src/gen/wxLayoutAlgorithm.erl @@ -20,76 +20,70 @@ -module(wxLayoutAlgorithm). -moduledoc """ -Functions for wxLayoutAlgorithm class - -`m:wxLayoutAlgorithm` implements layout of subwindows in MDI or SDI frames. It -sends a `wxCalculateLayoutEvent` (not implemented in wx) event to children of -the frame, asking them for information about their size. For MDI parent frames, -the algorithm allocates the remaining space to the MDI client window (which -contains the MDI child frames). - -For SDI (normal) frames, a 'main' window is specified as taking up the remaining -space. - -Because the event system is used, this technique can be applied to any windows, -which are not necessarily 'aware' of the layout classes (no virtual functions in -`m:wxWindow` refer to `m:wxLayoutAlgorithm` or its events). However, you may -wish to use `m:wxSashLayoutWindow` for your subwindows since this class provides -handlers for the required events, and accessors to specify the desired size of -the window. The sash behaviour in the base class can be used, optionally, to -make the windows user-resizable. - -`m:wxLayoutAlgorithm` is typically used in IDE (integrated development -environment) applications, where there are several resizable windows in addition -to the MDI client window, or other primary editing window. Resizable windows -might include toolbars, a project window, and a window for displaying error and -warning messages. - -When a window receives an OnCalculateLayout event, it should call SetRect in the -given event object, to be the old supplied rectangle minus whatever space the -window takes up. It should also set its own size accordingly. -`wxSashLayoutWindow::OnCalculateLayout` (not implemented in wx) generates an -OnQueryLayoutInfo event which it sends to itself to determine the orientation, -alignment and size of the window, which it gets from internal member variables -set by the application. - -The algorithm works by starting off with a rectangle equal to the whole frame -client area. It iterates through the frame children, generating -wxLayoutAlgorithm::OnCalculateLayout events which subtract the window size and -return the remaining rectangle for the next window to process. It is assumed (by -`wxSashLayoutWindow::OnCalculateLayout` (not implemented in wx)) that a window -stretches the full dimension of the frame client, according to the orientation -it specifies. For example, a horizontal window will stretch the full width of -the remaining portion of the frame client area. In the other orientation, the -window will be fixed to whatever size was specified by -wxLayoutAlgorithm::OnQueryLayoutInfo. An alignment setting will make the window -'stick' to the left, top, right or bottom of the remaining client area. This -scheme implies that order of window creation is important. Say you wish to have -an extra toolbar at the top of the frame, a project window to the left of the -MDI client window, and an output window above the status bar. You should -therefore create the windows in this order: toolbar, output window, project -window. This ensures that the toolbar and output window take up space at the top -and bottom, and then the remaining height in-between is used for the project -window. +`m:wxLayoutAlgorithm` implements layout of subwindows in MDI or SDI frames. + +It sends a `wxCalculateLayoutEvent` (not implemented in wx) event to children of the +frame, asking them for information about their size. For MDI parent frames, the algorithm +allocates the remaining space to the MDI client window (which contains the MDI child frames). + +For SDI (normal) frames, a 'main' window is specified as taking up the remaining space. + +Because the event system is used, this technique can be applied to any windows, which are +not necessarily 'aware' of the layout classes (no virtual functions in `m:wxWindow` refer +to `m:wxLayoutAlgorithm` or its events). However, you may wish to use `m:wxSashLayoutWindow` +for your subwindows since this class provides handlers for the required events, and +accessors to specify the desired size of the window. The sash behaviour in the base class +can be used, optionally, to make the windows user-resizable. + +`m:wxLayoutAlgorithm` is typically used in IDE (integrated development environment) +applications, where there are several resizable windows in addition to the MDI client +window, or other primary editing window. Resizable windows might include toolbars, a +project window, and a window for displaying error and warning messages. + +When a window receives an OnCalculateLayout event, it should call SetRect in the given +event object, to be the old supplied rectangle minus whatever space the window takes up. +It should also set its own size accordingly. `wxSashLayoutWindow::OnCalculateLayout` (not +implemented in wx) generates an OnQueryLayoutInfo event which it sends to itself to +determine the orientation, alignment and size of the window, which it gets from internal +member variables set by the application. + +The algorithm works by starting off with a rectangle equal to the whole frame client +area. It iterates through the frame children, generating +wxLayoutAlgorithm::OnCalculateLayout events which subtract the window size and return the +remaining rectangle for the next window to process. It is assumed (by `wxSashLayoutWindow::OnCalculateLayout` +(not implemented in wx)) that a window stretches the full dimension of the frame client, +according to the orientation it specifies. For example, a horizontal window will stretch +the full width of the remaining portion of the frame client area. In the other +orientation, the window will be fixed to whatever size was specified by +wxLayoutAlgorithm::OnQueryLayoutInfo. An alignment setting will make the window 'stick' to +the left, top, right or bottom of the remaining client area. This scheme implies that +order of window creation is important. Say you wish to have an extra toolbar at the top of +the frame, a project window to the left of the MDI client window, and an output window +above the status bar. You should therefore create the windows in this order: toolbar, +output window, project window. This ensures that the toolbar and output window take up +space at the top and bottom, and then the remaining height in-between is used for the +project window. `m:wxLayoutAlgorithm` is quite independent of the way in which -wxLayoutAlgorithm::OnCalculateLayout chooses to interpret a window's size and -alignment. Therefore you could implement a different window class with a new -wxLayoutAlgorithm::OnCalculateLayout event handler, that has a more -sophisticated way of laying out the windows. It might allow specification of -whether stretching occurs in the specified orientation, for example, rather than -always assuming stretching. (This could, and probably should, be added to the -existing implementation). - -Note: `m:wxLayoutAlgorithm` has nothing to do with `wxLayoutConstraints` (not -implemented in wx). It is an alternative way of specifying layouts for which the -normal constraint system is unsuitable. - -See: `m:wxSashEvent`, `m:wxSashLayoutWindow`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) - -wxWidgets docs: -[wxLayoutAlgorithm](https://docs.wxwidgets.org/3.1/classwx_layout_algorithm.html) +wxLayoutAlgorithm::OnCalculateLayout chooses to interpret a window's size and alignment. +Therefore you could implement a different window class with a new +wxLayoutAlgorithm::OnCalculateLayout event handler, that has a more sophisticated way of +laying out the windows. It might allow specification of whether stretching occurs in the +specified orientation, for example, rather than always assuming stretching. (This could, +and probably should, be added to the existing implementation). + +Note: `m:wxLayoutAlgorithm` has nothing to do with `wxLayoutConstraints` (not implemented +in wx). It is an alternative way of specifying layouts for which the normal constraint +system is unsuitable. + +See: +* `m:wxSashEvent` + +* `m:wxSashLayoutWindow` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +wxWidgets docs: [wxLayoutAlgorithm](https://docs.wxwidgets.org/3.2/classwx_layout_algorithm.html) """. -include("wxe.hrl"). -export([destroy/1,layoutFrame/2,layoutFrame/3,layoutMDIFrame/2,layoutMDIFrame/3, @@ -100,18 +94,16 @@ wxWidgets docs: -type wxLayoutAlgorithm() :: wx:wx_object(). -export_type([wxLayoutAlgorithm/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlayoutalgorithm.html#wxlayoutalgorithmwxlayoutalgorithm">external documentation</a>. -doc "Default constructor.". -spec new() -> wxLayoutAlgorithm(). new() -> wxe_util:queue_cmd(?get_env(), ?wxLayoutAlgorithm_new), wxe_util:rec(?wxLayoutAlgorithm_new). -%% @equiv layoutFrame(This,Frame, []) +-doc(#{equiv => layoutFrame(This,Frame, [])}). -spec layoutFrame(This, Frame) -> boolean() when This::wxLayoutAlgorithm(), Frame::wxFrame:wxFrame(). @@ -119,12 +111,10 @@ layoutFrame(This,Frame) when is_record(This, wx_ref),is_record(Frame, wx_ref) -> layoutFrame(This,Frame, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlayoutalgorithm.html#wxlayoutalgorithmlayoutframe">external documentation</a>. -doc """ Lays out the children of a normal frame. -`mainWindow` is set to occupy the remaining space. This function simply calls -`layoutWindow/3`. +`mainWindow` is set to occupy the remaining space. This function simply calls `layoutWindow/3`. """. -spec layoutFrame(This, Frame, [Option]) -> boolean() when This::wxLayoutAlgorithm(), Frame::wxFrame:wxFrame(), @@ -139,7 +129,7 @@ layoutFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame, Options) wxe_util:queue_cmd(This,Frame, Opts,?get_env(),?wxLayoutAlgorithm_LayoutFrame), wxe_util:rec(?wxLayoutAlgorithm_LayoutFrame). -%% @equiv layoutMDIFrame(This,Frame, []) +-doc(#{equiv => layoutMDIFrame(This,Frame, [])}). -spec layoutMDIFrame(This, Frame) -> boolean() when This::wxLayoutAlgorithm(), Frame::wxMDIParentFrame:wxMDIParentFrame(). @@ -147,13 +137,11 @@ layoutMDIFrame(This,Frame) when is_record(This, wx_ref),is_record(Frame, wx_ref) -> layoutMDIFrame(This,Frame, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlayoutalgorithm.html#wxlayoutalgorithmlayoutmdiframe">external documentation</a>. -doc """ Lays out the children of an MDI parent frame. -If `rect` is non-NULL, the given rectangle will be used as a starting point -instead of the frame's client area. The MDI client window is set to occupy the -remaining space. +If `rect` is non-NULL, the given rectangle will be used as a starting point instead of +the frame's client area. The MDI client window is set to occupy the remaining space. """. -spec layoutMDIFrame(This, Frame, [Option]) -> boolean() when This::wxLayoutAlgorithm(), Frame::wxMDIParentFrame:wxMDIParentFrame(), @@ -168,7 +156,7 @@ layoutMDIFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame, Options) wxe_util:queue_cmd(This,Frame, Opts,?get_env(),?wxLayoutAlgorithm_LayoutMDIFrame), wxe_util:rec(?wxLayoutAlgorithm_LayoutMDIFrame). -%% @equiv layoutWindow(This,Parent, []) +-doc(#{equiv => layoutWindow(This,Parent, [])}). -spec layoutWindow(This, Parent) -> boolean() when This::wxLayoutAlgorithm(), Parent::wxWindow:wxWindow(). @@ -176,14 +164,13 @@ layoutWindow(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> layoutWindow(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlayoutalgorithm.html#wxlayoutalgorithmlayoutwindow">external documentation</a>. -doc """ Lays out the children of a normal frame or other window. -`mainWindow` is set to occupy the remaining space. If this is not specified, -then the last window that responds to a calculate layout event in query mode -will get the remaining space (that is, a non-query OnCalculateLayout event will -not be sent to this window and the window will be set to the remaining size). +`mainWindow` is set to occupy the remaining space. If this is not specified, then the +last window that responds to a calculate layout event in query mode will get the remaining +space (that is, a non-query OnCalculateLayout event will not be sent to this window and +the window will be set to the remaining size). """. -spec layoutWindow(This, Parent, [Option]) -> boolean() when This::wxLayoutAlgorithm(), Parent::wxWindow:wxWindow(), @@ -198,8 +185,7 @@ layoutWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxLayoutAlgorithm_LayoutWindow), wxe_util:rec(?wxLayoutAlgorithm_LayoutWindow). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxLayoutAlgorithm()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxLayoutAlgorithm), diff --git a/lib/wx/src/gen/wxListBox.erl b/lib/wx/src/gen/wxListBox.erl index a309a3c45c3e..5dd33a6b8704 100644 --- a/lib/wx/src/gen/wxListBox.erl +++ b/lib/wx/src/gen/wxListBox.erl @@ -20,43 +20,74 @@ -module(wxListBox). -moduledoc """ -Functions for wxListBox class - A listbox is used to select one or more of a list of strings. -The strings are displayed in a scrolling box, with the selected string(s) marked -in reverse video. A listbox can be single selection (if an item is selected, the -previous selection is removed) or multiple selection (clicking an item toggles -the item on or off independently of other selections). +The strings are displayed in a scrolling box, with the selected string(s) marked in +reverse video. A listbox can be single selection (if an item is selected, the previous +selection is removed) or multiple selection (clicking an item toggles the item on or off +independently of other selections). -List box elements are numbered from zero and while the maximal number of -elements is unlimited, it is usually better to use a virtual control, not -requiring to add all the items to it at once, such as `wxDataViewCtrl` (not -implemented in wx) or `m:wxListCtrl` with `wxLC_VIRTUAL` style, once more than a -few hundreds items need to be displayed because this control is not optimized, -neither from performance nor from user interface point of view, for large number -of items. +List box elements are numbered from zero and while the maximal number of elements is +unlimited, it is usually better to use a virtual control, not requiring to add all the +items to it at once, such as `wxDataViewCtrl` (not implemented in wx) or `m:wxListCtrl` +with `wxLC_VIRTUAL` style, once more than a few hundreds items need to be displayed +because this control is not optimized, neither from performance nor from user interface +point of view, for large number of items. Notice that the list box doesn't support control characters other than `TAB`. -Styles +## Styles This class supports the following styles: -See: `wxEditableListBox` (not implemented in wx), `m:wxChoice`, `m:wxComboBox`, -`m:wxListCtrl`, `m:wxCommandEvent` +* wxLB_SINGLE: Single-selection list. + +* wxLB_MULTIPLE: Multiple-selection list: the user can toggle multiple items on and off. +This is the same as wxLB_EXTENDED in wxGTK2 port. + +* wxLB_EXTENDED: Extended-selection list: the user can extend the selection by using `SHIFT` +or `CTRL` keys together with the cursor movement keys or the mouse. + +* wxLB_HSCROLL: Create horizontal scrollbar if contents are too wide (Windows only). + +* wxLB_ALWAYS_SB: Always show a vertical scrollbar. + +* wxLB_NEEDED_SB: Only create a vertical scrollbar if needed. + +* wxLB_NO_SB: Don't create vertical scrollbar (wxMSW and wxGTK only). + +* wxLB_SORT: The listbox contents are sorted in alphabetical order. Note that `wxLB_SINGLE`, `wxLB_MULTIPLE` +and `wxLB_EXTENDED` styles are mutually exclusive and you can specify at most one of them +(single selection is the default). See also overview_windowstyles. + +See: +* `m:wxChoice` + +* `m:wxComboBox` -This class is derived (and can use functions) from: `m:wxControlWithItems` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxListCtrl` -wxWidgets docs: -[wxListBox](https://docs.wxwidgets.org/3.1/classwx_list_box.html) +* `m:wxCommandEvent` + +This class is derived, and can use functions, from: + +* `m:wxControlWithItems` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxListBox](https://docs.wxwidgets.org/3.2/classwx_list_box.html) ## Events Event types emitted from this class: -[`command_listbox_selected`](`m:wxCommandEvent`), -[`command_listbox_doubleclicked`](`m:wxCommandEvent`) + +* [`command_listbox_selected`](`m:wxCommandEvent`) + +* [`command_listbox_doubleclicked`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/6,create/7,deselect/2,destroy/1,getSelections/1,hitTest/2,hitTest/3, @@ -107,7 +138,6 @@ Event types emitted from this class: -type wxListBox() :: wx:wx_object(). -export_type([wxListBox/0]). -%% @hidden -doc false. parent_class(wxControlWithItems) -> true; parent_class(wxControl) -> true; @@ -115,14 +145,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxwxlistbox">external documentation</a>. -doc "Default constructor.". -spec new() -> wxListBox(). new() -> wxe_util:queue_cmd(?get_env(), ?wxListBox_new_0), wxe_util:rec(?wxListBox_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxListBox() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -130,13 +159,12 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxwxlistbox">external documentation</a>. -doc """ Constructor, creating and showing a list box. -See the other `new/3` constructor; the only difference is that this overload -takes a `wxArrayString` (not implemented in wx) instead of a pointer to an array -of `wxString` (not implemented in wx). +See the other `new/3` constructor; the only difference is that this overload takes a `wxArrayString` +(not implemented in wx) instead of a pointer to an array of `wxString` (not implemented +in wx). """. -spec new(Parent, Id, [Option]) -> wxListBox() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -158,7 +186,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxListBox_new_3), wxe_util:rec(?wxListBox_new_3). -%% @equiv create(This,Parent,Id,Pos,Size,Choices, []) +-doc(#{equiv => create(This,Parent,Id,Pos,Size,Choices, [])}). -spec create(This, Parent, Id, Pos, Size, Choices) -> boolean() when This::wxListBox(), Parent::wxWindow:wxWindow(), Id::integer(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()]. @@ -166,7 +194,7 @@ create(This,Parent,Id,{PosX,PosY} = Pos,{SizeW,SizeH} = Size,Choices) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_integer(PosX),is_integer(PosY),is_integer(SizeW),is_integer(SizeH),is_list(Choices) -> create(This,Parent,Id,Pos,Size,Choices, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxcreate">external documentation</a>. +-doc "". -spec create(This, Parent, Id, Pos, Size, Choices, [Option]) -> boolean() when This::wxListBox(), Parent::wxWindow:wxWindow(), Id::integer(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()], Option :: {'style', integer()} @@ -184,7 +212,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,{PosX,PosY} = Po wxe_util:queue_cmd(This,Parent,Id,Pos,Size,Choices_UCA, Opts,?get_env(),?wxListBox_Create), wxe_util:rec(?wxListBox_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxdeselect">external documentation</a>. -doc """ Deselects an item in the list box. @@ -197,7 +224,6 @@ deselect(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxListBox), wxe_util:queue_cmd(This,N,?get_env(),?wxListBox_Deselect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxgetselections">external documentation</a>. -doc """ Fill an array of ints with the positions of the currently selected items. @@ -205,8 +231,12 @@ Return: The number of selections. Remark: Use this with a multiple selection listbox. -See: `wxControlWithItems:getSelection/1`, -`wxControlWithItems:getStringSelection/1`, `wxControlWithItems:setSelection/2` +See: +* `wxControlWithItems:getSelection/1` + +* `wxControlWithItems:getStringSelection/1` + +* `wxControlWithItems:setSelection/2` """. -spec getSelections(This) -> Result when Result ::{Res ::integer(), Selections::[integer()]}, @@ -216,7 +246,6 @@ getSelections(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListBox_GetSelections), wxe_util:rec(?wxListBox_GetSelections). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxinsertitems">external documentation</a>. -doc "Insert the given number of strings before the specified position.". -spec insertItems(This, Items, Pos) -> 'ok' when This::wxListBox(), Items::[unicode:chardata()], Pos::integer(). @@ -227,7 +256,6 @@ insertItems(#wx_ref{type=ThisT}=This,Items,Pos) ItemsTemp <- Items], wxe_util:queue_cmd(This,Items_UCA,Pos,?get_env(),?wxListBox_InsertItems). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxisselected">external documentation</a>. -doc """ Determines whether an item is selected. @@ -241,12 +269,11 @@ isSelected(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxListBox_IsSelected), wxe_util:rec(?wxListBox_IsSelected). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxset">external documentation</a>. -doc """ Replaces the current control contents with the given items. -Notice that calling this method is usually much faster than appending them one -by one if you need to add a lot of items. +Notice that calling this method is usually much faster than appending them one by one if +you need to add a lot of items. """. -spec set(This, Items) -> 'ok' when This::wxListBox(), Items::[unicode:chardata()]. @@ -257,15 +284,12 @@ set(#wx_ref{type=ThisT}=This,Items) ItemsTemp <- Items], wxe_util:queue_cmd(This,Items_UCA,?get_env(),?wxListBox_Set). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxhittest">external documentation</a>. -doc """ -Returns the item located at `point`, or `wxNOT_FOUND` if there is no item -located at `point`. +Returns the item located at `point`, or `wxNOT\_FOUND` if there is no item located at `point`. It is currently implemented for wxMSW, wxMac and wxGTK2 ports. -Return: Item located at point, or wxNOT_FOUND if unimplemented or the item does -not exist. +Return: Item located at point, or wxNOT_FOUND if unimplemented or the item does not exist. Since: 2.7.0 """. @@ -277,10 +301,9 @@ hitTest(#wx_ref{type=ThisT}=This,{PointX,PointY} = Point) wxe_util:queue_cmd(This,Point,?get_env(),?wxListBox_HitTest_1), wxe_util:rec(?wxListBox_HitTest_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxhittest">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec hitTest(This, X, Y) -> integer() when This::wxListBox(), X::integer(), Y::integer(). @@ -290,11 +313,6 @@ hitTest(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxListBox_HitTest_2), wxe_util:rec(?wxListBox_HitTest_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbox.html#wxlistboxsetfirstitem">external documentation</a>. -%% <br /> Also:<br /> -%% setFirstItem(This, String) -> 'ok' when<br /> -%% This::wxListBox(), String::unicode:chardata().<br /> -%% -doc "Set the specified item to be the first visible item.". -spec setFirstItem(This, N) -> 'ok' when This::wxListBox(), N::integer(); @@ -310,632 +328,425 @@ setFirstItem(#wx_ref{type=ThisT}=This,String) String_UC = unicode:characters_to_binary(String), wxe_util:queue_cmd(This,String_UC,?get_env(),?wxListBox_SetFirstItem_1_1). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the list box.". +-doc "Destroys the object". -spec destroy(This::wxListBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxListBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControlWithItems -%% @hidden -doc false. setStringSelection(This,String) -> wxControlWithItems:setStringSelection(This,String). -%% @hidden -doc false. setString(This,N,String) -> wxControlWithItems:setString(This,N,String). -%% @hidden -doc false. setSelection(This,N) -> wxControlWithItems:setSelection(This,N). -%% @hidden -doc false. select(This,N) -> wxControlWithItems:select(This,N). -%% @hidden -doc false. isEmpty(This) -> wxControlWithItems:isEmpty(This). -%% @hidden -doc false. insertStrings(This,Items,Pos,ClientsData) -> wxControlWithItems:insertStrings(This,Items,Pos,ClientsData). -%% @hidden -doc false. insertStrings(This,Items,Pos) -> wxControlWithItems:insertStrings(This,Items,Pos). -%% @hidden -doc false. insert(This,Item,Pos,ClientData) -> wxControlWithItems:insert(This,Item,Pos,ClientData). -%% @hidden -doc false. insert(This,Item,Pos) -> wxControlWithItems:insert(This,Item,Pos). -%% @hidden -doc false. getStringSelection(This) -> wxControlWithItems:getStringSelection(This). -%% @hidden -doc false. getString(This,N) -> wxControlWithItems:getString(This,N). -%% @hidden -doc false. getSelection(This) -> wxControlWithItems:getSelection(This). -%% @hidden -doc false. getCount(This) -> wxControlWithItems:getCount(This). -%% @hidden -doc false. setClientData(This,N,Data) -> wxControlWithItems:setClientData(This,N,Data). -%% @hidden -doc false. getClientData(This,N) -> wxControlWithItems:getClientData(This,N). -%% @hidden -doc false. findString(This,String, Options) -> wxControlWithItems:findString(This,String, Options). -%% @hidden -doc false. findString(This,String) -> wxControlWithItems:findString(This,String). -%% @hidden -doc false. delete(This,N) -> wxControlWithItems:delete(This,N). -%% @hidden -doc false. clear(This) -> wxControlWithItems:clear(This). -%% @hidden -doc false. appendStrings(This,Items,ClientsData) -> wxControlWithItems:appendStrings(This,Items,ClientsData). -%% @hidden -doc false. appendStrings(This,Items) -> wxControlWithItems:appendStrings(This,Items). -%% @hidden -doc false. append(This,Item,ClientData) -> wxControlWithItems:append(This,Item,ClientData). -%% @hidden -doc false. append(This,Item) -> wxControlWithItems:append(This,Item). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxListCtrl.erl b/lib/wx/src/gen/wxListCtrl.erl index cce95287d3e4..f32d549dcfca 100644 --- a/lib/wx/src/gen/wxListCtrl.erl +++ b/lib/wx/src/gen/wxListCtrl.erl @@ -20,85 +20,144 @@ -module(wxListCtrl). -moduledoc """ -Functions for wxListCtrl class - -A list control presents lists in a number of formats: list view, report view, -icon view and small icon view. In any case, elements are numbered from zero. For -all these modes, the items are stored in the control and must be added to it -using `insertItem/4` method. - -A special case of report view quite different from the other modes of the list -control is a virtual control in which the items data (including text, images and -attributes) is managed by the main program and is requested by the control -itself only when needed which allows having controls with millions of items -without consuming much memory. To use virtual list control you must use -`setItemCount/2` first and override at least `wxListCtrl::OnGetItemText` (not -implemented in wx) (and optionally `wxListCtrl::OnGetItemImage` (not implemented -in wx) or `wxListCtrl::OnGetItemColumnImage` (not implemented in wx) and -`wxListCtrl::OnGetItemAttr` (not implemented in wx)) to return the information -about the items when the control requests it. - -Virtual list control can be used as a normal one except that no operations which -can take time proportional to the number of items in the control happen - this -is required to allow having a practically infinite number of items. For example, -in a multiple selection virtual list control, the selections won't be sent when -many items are selected at once because this could mean iterating over all the -items. +A list control presents lists in a number of formats: list view, report view, icon view +and small icon view. + +In any case, elements are numbered from zero. For all these modes, the items are stored +in the control and must be added to it using `insertItem/4` method. + +A special case of report view quite different from the other modes of the list control is +a virtual control in which the items data (including text, images and attributes) is +managed by the main program and is requested by the control itself only when needed which +allows having controls with millions of items without consuming much memory. To use +virtual list control you must use `setItemCount/2` first and override at least `wxListCtrl::OnGetItemText` +(not implemented in wx) (and optionally `wxListCtrl::OnGetItemImage` (not implemented in +wx) or `wxListCtrl::OnGetItemColumnImage` (not implemented in wx) and `wxListCtrl::OnGetItemAttr` +(not implemented in wx)) to return the information about the items when the control +requests it. + +Virtual list control can be used as a normal one except that no operations which can take +time proportional to the number of items in the control happen - this is required to allow +having a practically infinite number of items. For example, in a multiple selection +virtual list control, the selections won't be sent when many items are selected at once +because this could mean iterating over all the items. Using many of `m:wxListCtrl` features is shown in the corresponding sample. -To intercept events from a list control, use the event table macros described in -`m:wxListEvent`. +To intercept events from a list control, use the event table macros described in `m:wxListEvent`. -`wxMac Note`: Starting with wxWidgets 2.8, `m:wxListCtrl` uses a native -implementation for report mode, and uses a generic implementation for other -modes. You can use the generic implementation for report mode as well by setting -the `mac.listctrl.always_use_generic` system option (see `m:wxSystemOptions`) -to 1. +`wxMac Note`: Starting with wxWidgets 2.8, `m:wxListCtrl` uses a native implementation +for report mode, and uses a generic implementation for other modes. You can use the +generic implementation for report mode as well by setting the `mac.listctrl.always_use_generic` +system option (see `m:wxSystemOptions`) to 1. -Styles +## Styles This class supports the following styles: -Note: Under wxMSW this control uses `wxSystemThemedControl` (not implemented in -wx) for an explorer style appearance by default since wxWidgets 3.1.0. If this -is not desired, you can call `wxSystemThemedControl::EnableSystemTheme` (not -implemented in wx) with `false` argument to disable this. +* wxLC_LIST: Multicolumn list view, with optional small icons. Columns are computed +automatically, i.e. you don't set columns as in `wxLC_REPORT`. In other words, the list +wraps, unlike a `m:wxListBox`. + +* wxLC_REPORT: Single or multicolumn report view, with optional header. + +* wxLC_VIRTUAL: The application provides items text on demand. May only be used with `wxLC_REPORT`. + +* wxLC_ICON: Large icon view, with optional labels. + +* wxLC_SMALL_ICON: Small icon view, with optional labels. + +* wxLC_ALIGN_TOP: Icons align to the top. Win32 default, Win32 only. + +* wxLC_ALIGN_LEFT: Icons align to the left. + +* wxLC_AUTOARRANGE: Icons arrange themselves. Win32 only. + +* wxLC_EDIT_LABELS: Labels are editable: the application will be notified when editing +starts. + +* wxLC_NO_HEADER: No header in report mode. + +* wxLC_SINGLE_SEL: Single selection (default is multiple). + +* wxLC_SORT_ASCENDING: Sort in ascending order. (You must still supply a comparison +callback in `sortItems/2`.) + +* wxLC_SORT_DESCENDING: Sort in descending order. (You must still supply a comparison +callback in `sortItems/2`.) + +* wxLC_HRULES: Draws light horizontal rules between rows in report mode. + +* wxLC_VRULES: Draws light vertical rules between columns in report mode. See: -[Overview listctrl](https://docs.wxwidgets.org/3.1/overview_listctrl.html#overview_listctrl), -`m:wxListView`, `m:wxListBox`, `m:wxTreeCtrl`, `m:wxImageList`, `m:wxListEvent`, -`m:wxListItem`, `wxEditableListBox` (not implemented in wx) +* [Overview listctrl](https://docs.wxwidgets.org/3.2/overview_listctrl.html#overview_listctrl) + +* `m:wxListView` + +* `m:wxListBox` + +* `m:wxTreeCtrl` + +* `m:wxImageList` + +* `m:wxListEvent` + +* `m:wxListItem` + +This class is derived, and can use functions, from: + +* `m:wxControl` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxWindow` -wxWidgets docs: -[wxListCtrl](https://docs.wxwidgets.org/3.1/classwx_list_ctrl.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxListCtrl](https://docs.wxwidgets.org/3.2/classwx_list_ctrl.html) ## Events Event types emitted from this class: -[`command_list_begin_drag`](`m:wxListEvent`), -[`command_list_begin_rdrag`](`m:wxListEvent`), -[`command_list_begin_label_edit`](`m:wxListEvent`), -[`command_list_end_label_edit`](`m:wxListEvent`), -[`command_list_delete_item`](`m:wxListEvent`), -[`command_list_delete_all_items`](`m:wxListEvent`), -[`command_list_item_selected`](`m:wxListEvent`), -[`command_list_item_deselected`](`m:wxListEvent`), -[`command_list_item_activated`](`m:wxListEvent`), -[`command_list_item_focused`](`m:wxListEvent`), -[`command_list_item_middle_click`](`m:wxListEvent`), -[`command_list_item_right_click`](`m:wxListEvent`), -[`command_list_key_down`](`m:wxListEvent`), -[`command_list_insert_item`](`m:wxListEvent`), -[`command_list_col_click`](`m:wxListEvent`), -[`command_list_col_right_click`](`m:wxListEvent`), -[`command_list_col_begin_drag`](`m:wxListEvent`), -[`command_list_col_dragging`](`m:wxListEvent`), -[`command_list_col_end_drag`](`m:wxListEvent`), -[`command_list_cache_hint`](`m:wxListEvent`) + +* [`command_list_begin_drag`](`m:wxListEvent`) + +* [`command_list_begin_rdrag`](`m:wxListEvent`) + +* [`command_list_begin_label_edit`](`m:wxListEvent`) + +* [`command_list_end_label_edit`](`m:wxListEvent`) + +* [`command_list_delete_item`](`m:wxListEvent`) + +* [`command_list_delete_all_items`](`m:wxListEvent`) + +* [`command_list_item_selected`](`m:wxListEvent`) + +* [`command_list_item_deselected`](`m:wxListEvent`) + +* [`command_list_item_activated`](`m:wxListEvent`) + +* [`command_list_item_focused`](`m:wxListEvent`) + +* [`command_list_item_middle_click`](`m:wxListEvent`) + +* [`command_list_item_right_click`](`m:wxListEvent`) + +* [`command_list_key_down`](`m:wxListEvent`) + +* [`command_list_insert_item`](`m:wxListEvent`) + +* [`command_list_col_click`](`m:wxListEvent`) + +* [`command_list_col_right_click`](`m:wxListEvent`) + +* [`command_list_col_begin_drag`](`m:wxListEvent`) + +* [`command_list_col_dragging`](`m:wxListEvent`) + +* [`command_list_col_end_drag`](`m:wxListEvent`) + +* [`command_list_cache_hint`](`m:wxListEvent`) """. -include("wxe.hrl"). -export([ create/2, create/3 , new/0, new/1, new/2 , sortItems/2 ,arrange/1, @@ -158,7 +217,6 @@ Event types emitted from this class: -type wxListCtrl() :: wx:wx_object(). -export_type([wxListCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; @@ -167,7 +225,6 @@ parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% @doc See <a href="http://www.wxwidgets.org/manuals/stable/wx_wxlistctrl.html#wxlistctrlwxlistctrl">external documentation</a>. --doc "Default constructor.". -spec new() -> wxListCtrl(). new() -> Op = ?wxListCtrl_new_0, @@ -175,7 +232,6 @@ new() -> wxe_util:rec(Op). --doc false. -spec new(Parent) -> wxListCtrl() when Parent::wxWindow:wxWindow(). new(Parent) @@ -189,11 +245,6 @@ new(Parent) %% OnGetItemColumnImage = (This, Item, Column) -> integer() %% %% See <a href="http://www.wxwidgets.org/manuals/stable/wx_wxlistctrl.html#wxlistctrlwxlistctrl">external documentation</a>. --doc """ -Constructor, creating and showing a list control. - -See: `create/3`, `wxValidator` (not implemented in wx) -""". -spec new(Parent, [Option]) -> wxListCtrl() when Parent::wxWindow:wxWindow(), Option::{winid, integer()} | @@ -212,7 +263,7 @@ new(#wx_ref{}=Parent, Options) true = create(ListCtrl,Parent,Options), ListCtrl. -%% @equiv arrange(This, []) +-doc(#{equiv => arrange(This, [])}). -spec arrange(This) -> boolean() when This::wxListCtrl(). @@ -220,11 +271,18 @@ arrange(This) when is_record(This, wx_ref) -> arrange(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlarrange">external documentation</a>. -doc """ Arranges the items in icon or small icon view. This only has effect on Win32. `flag` is one of: + +* wxLIST_ALIGN_DEFAULT: Default alignment. + +* wxLIST_ALIGN_LEFT: Align to the left side of the control. + +* wxLIST_ALIGN_TOP: Align to the top side of the control. + +* wxLIST_ALIGN_SNAP_TO_GRID: Snap to grid. """. -spec arrange(This, [Option]) -> boolean() when This::wxListCtrl(), @@ -238,13 +296,11 @@ arrange(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxListCtrl_Arrange), wxe_util:rec(?wxListCtrl_Arrange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlassignimagelist">external documentation</a>. -doc """ Sets the image list associated with the control and takes ownership of it (i.e. -the control will, unlike when using `setImageList/3`, delete the list when -destroyed). `which` is one of `wxIMAGE_LIST_NORMAL`, `wxIMAGE_LIST_SMALL`, -`wxIMAGE_LIST_STATE` (the last is unimplemented). +the control will, unlike when using `setImageList/3`, delete the list when destroyed). `which` is one of `wxIMAGE_LIST_NORMAL`, `wxIMAGE_LIST_SMALL`, `wxIMAGE_LIST_STATE` +(the last is unimplemented). See: `setImageList/3` """. @@ -256,12 +312,10 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList,Whic ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,Which,?get_env(),?wxListCtrl_AssignImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlclearall">external documentation</a>. -doc """ Deletes all items and all columns. -Note: This sends an event of type `wxEVT_LIST_DELETE_ALL_ITEMS` under all -platforms. +Note: This sends an event of type `wxEVT_LIST_DELETE_ALL_ITEMS` under all platforms. """. -spec clearAll(This) -> 'ok' when This::wxListCtrl(). @@ -271,7 +325,6 @@ clearAll(#wx_ref{type=ThisT}=This) -> %% @equiv create(This,Parent, []) --doc false. -spec create(This, Parent) -> boolean() when This::wxWindow:wxWindow(), Parent::wxWindow:wxWindow(). @@ -280,11 +333,6 @@ create(This,Parent) create(This,Parent, []). %% @doc See <a href="http://www.wxwidgets.org/manuals/stable/wx_wxlistctrl.html#wxlistctrlcreate">external documentation</a>. --doc """ -Creates the list control. - -See `new/2` for further details. -""". -spec create(This, Parent, [Option]) -> boolean() when This::wxWindow:wxWindow(), Parent::wxWindow:wxWindow(), @@ -317,18 +365,16 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This, Parent, Opts, ?get_env(), Op), wxe_util:rec(Op). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrldeleteallitems">external documentation</a>. -doc """ Deletes all items in the list control. -This function does `not` send the `wxEVT_LIST_DELETE_ITEM` event because -deleting many items from the control would be too slow then (unlike -`deleteItem/2`) but it does send the special `wxEVT_LIST_DELETE_ALL_ITEMS` event -if the control was not empty. If it was already empty, nothing is done and no -event is sent. +This function does `not` send the `wxEVT_LIST_DELETE_ITEM` event because deleting many +items from the control would be too slow then (unlike `deleteItem/2`) but it does send the special `wxEVT_LIST_DELETE_ALL_ITEMS` +event if the control was not empty. If it was already empty, nothing is done and no event +is sent. -Return: true if the items were successfully deleted or if the control was -already empty, false if an error occurred while deleting the items. +Return: true if the items were successfully deleted or if the control was already empty, +false if an error occurred while deleting the items. """. -spec deleteAllItems(This) -> boolean() when This::wxListCtrl(). @@ -337,7 +383,6 @@ deleteAllItems(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_DeleteAllItems), wxe_util:rec(?wxListCtrl_DeleteAllItems). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrldeletecolumn">external documentation</a>. -doc "Deletes a column.". -spec deleteColumn(This, Col) -> boolean() when This::wxListCtrl(), Col::integer(). @@ -347,12 +392,10 @@ deleteColumn(#wx_ref{type=ThisT}=This,Col) wxe_util:queue_cmd(This,Col,?get_env(),?wxListCtrl_DeleteColumn), wxe_util:rec(?wxListCtrl_DeleteColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrldeleteitem">external documentation</a>. -doc """ Deletes the specified item. -This function sends the `wxEVT_LIST_DELETE_ITEM` event for the item being -deleted. +This function sends the `wxEVT_LIST_DELETE_ITEM` event for the item being deleted. See: `deleteAllItems/1` """. @@ -364,16 +407,15 @@ deleteItem(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_DeleteItem), wxe_util:rec(?wxListCtrl_DeleteItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrleditlabel">external documentation</a>. -doc """ Starts editing the label of the given item. -This function generates a `EVT_LIST_BEGIN_LABEL_EDIT` event which can be vetoed -so that no text control will appear for in-place editing. +This function generates a `EVT_LIST_BEGIN_LABEL_EDIT` event which can be vetoed so that +no text control will appear for in-place editing. -If the user changed the label (i.e. s/he does not press ESC or leave the text -control without changes, a `EVT_LIST_END_LABEL_EDIT` event will be sent which -can be vetoed as well. +If the user changed the label (i.e. s/he does not press ESC or leave the text control +without changes, a `EVT_LIST_END_LABEL_EDIT` event will be sent which can be vetoed as +well. """. -spec editLabel(This, Item) -> wxTextCtrl:wxTextCtrl() when This::wxListCtrl(), Item::integer(). @@ -383,7 +425,6 @@ editLabel(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_EditLabel), wxe_util:rec(?wxListCtrl_EditLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlensurevisible">external documentation</a>. -doc "Ensures this item is visible.". -spec ensureVisible(This, Item) -> boolean() when This::wxListCtrl(), Item::integer(). @@ -393,7 +434,7 @@ ensureVisible(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_EnsureVisible), wxe_util:rec(?wxListCtrl_EnsureVisible). -%% @equiv findItem(This,Start,Str, []) +-doc(#{equiv => findItem(This,Start,Str, [])}). -spec findItem(This, Start, Str) -> integer() when This::wxListCtrl(), Start::integer(), Str::unicode:chardata(). @@ -401,14 +442,9 @@ findItem(This,Start,Str) when is_record(This, wx_ref),is_integer(Start),?is_chardata(Str) -> findItem(This,Start,Str, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlfinditem">external documentation</a>. -%% <br /> Also:<br /> -%% findItem(This, Start, Pt, Direction) -> integer() when<br /> -%% This::wxListCtrl(), Start::integer(), Pt::{X::integer(), Y::integer()}, Direction::integer().<br /> -%% -doc """ -Find an item nearest this position in the specified direction, starting from -`start` or the beginning if `start` is -1. +Find an item nearest this position in the specified direction, starting from `start` or +the beginning if `start` is -1. Return: The next matching item if any or `-1` (wxNOT_FOUND) otherwise. """. @@ -432,7 +468,6 @@ findItem(#wx_ref{type=ThisT}=This,Start,{PtX,PtY} = Pt,Direction) wxe_util:queue_cmd(This,Start,Pt,Direction,?get_env(),?wxListCtrl_FindItem_3_1), wxe_util:rec(?wxListCtrl_FindItem_3_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetcolumn">external documentation</a>. -doc """ Gets information about this column. @@ -447,7 +482,6 @@ getColumn(#wx_ref{type=ThisT}=This,Col,#wx_ref{type=ItemT}=Item) wxe_util:queue_cmd(This,Col,Item,?get_env(),?wxListCtrl_GetColumn), wxe_util:rec(?wxListCtrl_GetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetcolumncount">external documentation</a>. -doc "Returns the number of columns.". -spec getColumnCount(This) -> integer() when This::wxListCtrl(). @@ -456,7 +490,6 @@ getColumnCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetColumnCount), wxe_util:rec(?wxListCtrl_GetColumnCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetcolumnwidth">external documentation</a>. -doc "Gets the column width (report view only).". -spec getColumnWidth(This, Col) -> integer() when This::wxListCtrl(), Col::integer(). @@ -466,11 +499,10 @@ getColumnWidth(#wx_ref{type=ThisT}=This,Col) wxe_util:queue_cmd(This,Col,?get_env(),?wxListCtrl_GetColumnWidth), wxe_util:rec(?wxListCtrl_GetColumnWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetcountperpage">external documentation</a>. -doc """ -Gets the number of items that can fit vertically in the visible area of the list -control (list or report view) or the total number of items in the list control -(icon or small icon view). +Gets the number of items that can fit vertically in the visible area of the list control +(list or report view) or the total number of items in the list control (icon or small icon +view). """. -spec getCountPerPage(This) -> integer() when This::wxListCtrl(). @@ -479,14 +511,13 @@ getCountPerPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetCountPerPage), wxe_util:rec(?wxListCtrl_GetCountPerPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgeteditcontrol">external documentation</a>. -doc """ Returns the edit control being currently used to edit a label. Returns NULL if no label is being edited. -Note: It is currently only implemented for wxMSW and the generic version, not -for the native macOS version. +Note: It is currently only implemented for wxMSW and the generic version, not for the +native macOS version. """. -spec getEditControl(This) -> wxTextCtrl:wxTextCtrl() when This::wxListCtrl(). @@ -495,11 +526,16 @@ getEditControl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetEditControl), wxe_util:rec(?wxListCtrl_GetEditControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetimagelist">external documentation</a>. -doc """ Returns the specified image list. `which` may be one of: + +* wxIMAGE_LIST_NORMAL: The normal (large icon) image list. + +* wxIMAGE_LIST_SMALL: The small icon image list. + +* wxIMAGE_LIST_STATE: The user-defined state image list (unimplemented). """. -spec getImageList(This, Which) -> wxImageList:wxImageList() when This::wxListCtrl(), Which::integer(). @@ -509,15 +545,14 @@ getImageList(#wx_ref{type=ThisT}=This,Which) wxe_util:queue_cmd(This,Which,?get_env(),?wxListCtrl_GetImageList), wxe_util:rec(?wxListCtrl_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitem">external documentation</a>. -doc """ Gets information about the item. See `setItem/5` for more information. -You must call `info.SetId()` to set the ID of item you're interested in before -calling this method, and `info.SetMask()` with the flags indicating what fields -you need to retrieve from `info`. +You must call `info.SetId()` to set the ID of item you're interested in before calling +this method, and `info.SetMask()` with the flags indicating what fields you need to +retrieve from `info`. """. -spec getItem(This, Info) -> boolean() when This::wxListCtrl(), Info::wxListItem:wxListItem(). @@ -527,12 +562,11 @@ getItem(#wx_ref{type=ThisT}=This,#wx_ref{type=InfoT}=Info) -> wxe_util:queue_cmd(This,Info,?get_env(),?wxListCtrl_GetItem), wxe_util:rec(?wxListCtrl_GetItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitembackgroundcolour">external documentation</a>. -doc """ Returns the colour for this item. -If the item has no specific colour, returns an invalid colour (and not the -default background control of the control itself). +If the item has no specific colour, returns an invalid colour (and not the default +background control of the control itself). See: `getItemTextColour/2` """. @@ -544,7 +578,6 @@ getItemBackgroundColour(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_GetItemBackgroundColour), wxe_util:rec(?wxListCtrl_GetItemBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemcount">external documentation</a>. -doc "Returns the number of items in the list control.". -spec getItemCount(This) -> integer() when This::wxListCtrl(). @@ -553,7 +586,6 @@ getItemCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetItemCount), wxe_util:rec(?wxListCtrl_GetItemCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemdata">external documentation</a>. -doc "Gets the application-defined data associated with this item.". -spec getItemData(This, Item) -> integer() when This::wxListCtrl(), Item::integer(). @@ -563,7 +595,6 @@ getItemData(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_GetItemData), wxe_util:rec(?wxListCtrl_GetItemData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemfont">external documentation</a>. -doc "Returns the item's font.". -spec getItemFont(This, Item) -> wxFont:wxFont() when This::wxListCtrl(), Item::integer(). @@ -573,7 +604,6 @@ getItemFont(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_GetItemFont), wxe_util:rec(?wxListCtrl_GetItemFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemposition">external documentation</a>. -doc "Returns the position of the item, in icon or small icon view.". -spec getItemPosition(This, Item) -> Result when Result ::{Res ::boolean(), Pos::{X::integer(), Y::integer()}}, @@ -584,7 +614,7 @@ getItemPosition(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_GetItemPosition), wxe_util:rec(?wxListCtrl_GetItemPosition). -%% @equiv getItemRect(This,Item, []) +-doc(#{equiv => getItemRect(This,Item, [])}). -spec getItemRect(This, Item) -> Result when Result ::{Res ::boolean(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}}, This::wxListCtrl(), Item::integer(). @@ -593,10 +623,8 @@ getItemRect(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getItemRect(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemrect">external documentation</a>. -doc """ -Returns the rectangle representing the item's size and position, in physical -coordinates. +Returns the rectangle representing the item's size and position, in physical coordinates. `code` is one of wxLIST_RECT_BOUNDS, wxLIST_RECT_ICON, wxLIST_RECT_LABEL. """. @@ -613,11 +641,9 @@ getItemRect(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxListCtrl_GetItemRect), wxe_util:rec(?wxListCtrl_GetItemRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemspacing">external documentation</a>. -doc """ -Retrieves the spacing between icons in pixels: horizontal spacing is returned as -`x` component of the \{Width,Height\} object and the vertical spacing as its `y` -component. +Retrieves the spacing between icons in pixels: horizontal spacing is returned as `x` +component of the {Width,Height} object and the vertical spacing as its `y` component. """. -spec getItemSpacing(This) -> {W::integer(), H::integer()} when This::wxListCtrl(). @@ -626,12 +652,11 @@ getItemSpacing(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetItemSpacing), wxe_util:rec(?wxListCtrl_GetItemSpacing). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemstate">external documentation</a>. -doc """ Gets the item state. -For a list of state flags, see `setItem/5`. The `stateMask` indicates which -state flags are of interest. +For a list of state flags, see `setItem/5`. The `stateMask` indicates which state flags are of +interest. """. -spec getItemState(This, Item, StateMask) -> integer() when This::wxListCtrl(), Item::integer(), StateMask::integer(). @@ -641,7 +666,7 @@ getItemState(#wx_ref{type=ThisT}=This,Item,StateMask) wxe_util:queue_cmd(This,Item,StateMask,?get_env(),?wxListCtrl_GetItemState), wxe_util:rec(?wxListCtrl_GetItemState). -%% @equiv getItemText(This,Item, []) +-doc(#{equiv => getItemText(This,Item, [])}). -spec getItemText(This, Item) -> unicode:charlist() when This::wxListCtrl(), Item::integer(). @@ -649,7 +674,6 @@ getItemText(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getItemText(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemtext">external documentation</a>. -doc "Gets the item text for this item.". -spec getItemText(This, Item, [Option]) -> unicode:charlist() when This::wxListCtrl(), Item::integer(), @@ -663,15 +687,13 @@ getItemText(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxListCtrl_GetItemText), wxe_util:rec(?wxListCtrl_GetItemText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetitemtextcolour">external documentation</a>. -doc """ Returns the colour for this item. -If the item has no specific colour, returns an invalid colour (and not the -default foreground control of the control itself as this wouldn't allow -distinguishing between items having the same colour as the current control -foreground and items with default colour which, hence, have always the same -colour as the control). +If the item has no specific colour, returns an invalid colour (and not the default +foreground control of the control itself as this wouldn't allow distinguishing between +items having the same colour as the current control foreground and items with default +colour which, hence, have always the same colour as the control). """. -spec getItemTextColour(This, Item) -> wx:wx_colour4() when This::wxListCtrl(), Item::integer(). @@ -681,7 +703,7 @@ getItemTextColour(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_GetItemTextColour), wxe_util:rec(?wxListCtrl_GetItemTextColour). -%% @equiv getNextItem(This,Item, []) +-doc(#{equiv => getNextItem(This,Item, [])}). -spec getNextItem(This, Item) -> integer() when This::wxListCtrl(), Item::integer(). @@ -689,22 +711,39 @@ getNextItem(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getNextItem(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetnextitem">external documentation</a>. -doc """ -Searches for an item with the given geometry or state, starting from `item` but -excluding the `item` itself. +Searches for an item with the given geometry or state, starting from `item` but excluding +the `item` itself. -If `item` is -1, the first item that matches the specified flags will be -returned. Returns the first item with given state following `item` or -1 if no -such item found. This function may be used to find all selected items in the -control like this: +If `item` is -1, the first item that matches the specified flags will be returned. +Returns the first item with given state following `item` or -1 if no such item found. This +function may be used to find all selected items in the control like this: `geometry` can be one of: -Note: this parameter is only supported by wxMSW currently and ignored on other -platforms. +* wxLIST_NEXT_ABOVE: Searches for an item above the specified item. + +* wxLIST_NEXT_ALL: Searches for subsequent item by index. + +* wxLIST_NEXT_BELOW: Searches for an item below the specified item. + +* wxLIST_NEXT_LEFT: Searches for an item to the left of the specified item. + +* wxLIST_NEXT_RIGHT: Searches for an item to the right of the specified item. + +Note: this parameter is only supported by wxMSW currently and ignored on other platforms. `state` can be a bitlist of the following: + +* wxLIST_STATE_DONTCARE: Don't care what the state is. + +* wxLIST_STATE_DROPHILITED: The item indicates it is a drop target. + +* wxLIST_STATE_FOCUSED: The item has the focus. + +* wxLIST_STATE_SELECTED: The item is selected. + +* wxLIST_STATE_CUT: The item is selected as part of a cut and paste operation. """. -spec getNextItem(This, Item, [Option]) -> integer() when This::wxListCtrl(), Item::integer(), @@ -720,7 +759,6 @@ getNextItem(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxListCtrl_GetNextItem), wxe_util:rec(?wxListCtrl_GetNextItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetselecteditemcount">external documentation</a>. -doc "Returns the number of selected items in the list control.". -spec getSelectedItemCount(This) -> integer() when This::wxListCtrl(). @@ -729,7 +767,6 @@ getSelectedItemCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetSelectedItemCount), wxe_util:rec(?wxListCtrl_GetSelectedItemCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgettextcolour">external documentation</a>. -doc "Gets the text colour of the list control.". -spec getTextColour(This) -> wx:wx_colour4() when This::wxListCtrl(). @@ -738,7 +775,6 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetTextColour), wxe_util:rec(?wxListCtrl_GetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgettopitem">external documentation</a>. -doc "Gets the index of the topmost visible item when in list or report view.". -spec getTopItem(This) -> integer() when This::wxListCtrl(). @@ -747,15 +783,14 @@ getTopItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetTopItem), wxe_util:rec(?wxListCtrl_GetTopItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlgetviewrect">external documentation</a>. -doc """ Returns the rectangle taken by all items in the control. -In other words, if the controls client size were equal to the size of this -rectangle, no scrollbars would be needed and no free space would be left. +In other words, if the controls client size were equal to the size of this rectangle, no +scrollbars would be needed and no free space would be left. -Note that this function only works in the icon and small icon views, not in list -or report views (this is a limitation of the native Win32 control). +Note that this function only works in the icon and small icon views, not in list or +report views (this is a limitation of the native Win32 control). """. -spec getViewRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxListCtrl(). @@ -764,22 +799,37 @@ getViewRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListCtrl_GetViewRect), wxe_util:rec(?wxListCtrl_GetViewRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlhittest">external documentation</a>. -doc """ -Determines which item (if any) is at the specified point, giving details in -`flags`. +Determines which item (if any) is at the specified point, giving details in `flags`. Returns index of the item or `wxNOT_FOUND` if no item is at the specified point. `flags` will be a combination of the following flags: -If `ptrSubItem` is not NULL and the `m:wxListCtrl` is in the report mode the -subitem (or column) number will also be provided. This feature is only available -in version 2.7.0 or higher and is currently only implemented under wxMSW and -requires at least comctl32.dll of version 4.70 on the host system or the value -stored in `ptrSubItem` will be always -1. To compile this feature into wxWidgets -library you need to have access to commctrl.h of version 4.70 that is provided -by Microsoft. +* wxLIST_HITTEST_ABOVE: Above the control's client area. + +* wxLIST_HITTEST_BELOW: Below the control's client area. + +* wxLIST_HITTEST_TOLEFT: To the left of the control's client area. + +* wxLIST_HITTEST_TORIGHT: To the right of the control's client area. + +* wxLIST_HITTEST_NOWHERE: Inside the control's client area but not over an item. + +* wxLIST_HITTEST_ONITEMICON: Over an item's icon. + +* wxLIST_HITTEST_ONITEMLABEL: Over an item's text. + +* wxLIST_HITTEST_ONITEMSTATEICON: Over the checkbox of an item. + +* wxLIST_HITTEST_ONITEM: Combination of `wxLIST_HITTEST_ONITEMICON`, `wxLIST_HITTEST_ONITEMLABEL`, `wxLIST_HITTEST_ONITEMSTATEICON`. + +If `ptrSubItem` is not NULL and the `m:wxListCtrl` is in the report mode the subitem (or +column) number will also be provided. This feature is only available in version 2.7.0 or +higher and is currently only implemented under wxMSW and requires at least comctl32.dll of +version 4.70 on the host system or the value stored in `ptrSubItem` will be always -1. To +compile this feature into wxWidgets library you need to have access to commctrl.h of +version 4.70 that is provided by Microsoft. """. -spec hitTest(This, Point) -> Result when Result ::{Res ::integer(), Flags::integer(), PtrSubItem::integer()}, @@ -790,17 +840,11 @@ hitTest(#wx_ref{type=ThisT}=This,{PointX,PointY} = Point) wxe_util:queue_cmd(This,Point,?get_env(),?wxListCtrl_HitTest), wxe_util:rec(?wxListCtrl_HitTest). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlinsertcolumn">external documentation</a>. -%% <br /> Also:<br /> -%% insertColumn(This, Col, Info) -> integer() when<br /> -%% This::wxListCtrl(), Col::integer(), Info::wxListItem:wxListItem().<br /> -%% -doc """ For report view mode (only), inserts a column. -For more details, see `setItem/5`. Also see `insertColumn/4` overload for a -usually more convenient alternative to this method and the description of how -the item width is interpreted by this method. +For more details, see `setItem/5`. Also see `insertColumn/4` overload for a usually more convenient alternative to +this method and the description of how the item width is interpreted by this method. """. -spec insertColumn(This, Col, Heading) -> integer() when This::wxListCtrl(), Col::integer(), Heading::unicode:chardata(); @@ -817,15 +861,14 @@ insertColumn(#wx_ref{type=ThisT}=This,Col,#wx_ref{type=InfoT}=Info) wxe_util:queue_cmd(This,Col,Info,?get_env(),?wxListCtrl_InsertColumn_2), wxe_util:rec(?wxListCtrl_InsertColumn_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlinsertcolumn">external documentation</a>. -doc """ For report view mode (only), inserts a column. -Insert a new column in the list control in report view mode at the given -position specifying its most common attributes. +Insert a new column in the list control in report view mode at the given position +specifying its most common attributes. -Notice that to set the image for the column you need to use `insertColumn/4` -overload and specify ?wxLIST_MASK_IMAGE in the item mask. +Notice that to set the image for the column you need to use `insertColumn/4` overload and specify +?wxLIST\_MASK\_IMAGE in the item mask. Return: The index of the inserted column or -1 if adding it failed. """. @@ -844,11 +887,7 @@ insertColumn(#wx_ref{type=ThisT}=This,Col,Heading, Options) wxe_util:queue_cmd(This,Col,Heading_UC, Opts,?get_env(),?wxListCtrl_InsertColumn_3), wxe_util:rec(?wxListCtrl_InsertColumn_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlinsertitem">external documentation</a>. --doc """ -Inserts an item, returning the index of the new item if successful, -1 -otherwise. -""". +-doc "Inserts an item, returning the index of the new item if successful, -1 otherwise.". -spec insertItem(This, Info) -> integer() when This::wxListCtrl(), Info::wxListItem:wxListItem(). insertItem(#wx_ref{type=ThisT}=This,#wx_ref{type=InfoT}=Info) -> @@ -857,11 +896,6 @@ insertItem(#wx_ref{type=ThisT}=This,#wx_ref{type=InfoT}=Info) -> wxe_util:queue_cmd(This,Info,?get_env(),?wxListCtrl_InsertItem_1), wxe_util:rec(?wxListCtrl_InsertItem_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlinsertitem">external documentation</a>. -%% <br /> Also:<br /> -%% insertItem(This, Index, Label) -> integer() when<br /> -%% This::wxListCtrl(), Index::integer(), Label::unicode:chardata().<br /> -%% -doc "Insert a string item.". -spec insertItem(This, Index, ImageIndex) -> integer() when This::wxListCtrl(), Index::integer(), ImageIndex::integer(); @@ -879,7 +913,6 @@ insertItem(#wx_ref{type=ThisT}=This,Index,Label) wxe_util:queue_cmd(This,Index,Label_UC,?get_env(),?wxListCtrl_InsertItem_2_1), wxe_util:rec(?wxListCtrl_InsertItem_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlinsertitem">external documentation</a>. -doc "Insert an image/string item.". -spec insertItem(This, Index, Label, ImageIndex) -> integer() when This::wxListCtrl(), Index::integer(), Label::unicode:chardata(), ImageIndex::integer(). @@ -890,13 +923,11 @@ insertItem(#wx_ref{type=ThisT}=This,Index,Label,ImageIndex) wxe_util:queue_cmd(This,Index,Label_UC,ImageIndex,?get_env(),?wxListCtrl_InsertItem_3), wxe_util:rec(?wxListCtrl_InsertItem_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlrefreshitem">external documentation</a>. -doc """ Redraws the given `item`. -This is only useful for the virtual list controls as without calling this -function the displayed value of the item doesn't change even when the underlying -data does change. +This is only useful for the virtual list controls as without calling this function the +displayed value of the item doesn't change even when the underlying data does change. See: `refreshItems/3` """. @@ -907,7 +938,6 @@ refreshItem(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxListCtrl_RefreshItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlrefreshitems">external documentation</a>. -doc """ Redraws the items between `itemFrom` and `itemTo`. @@ -922,13 +952,12 @@ refreshItems(#wx_ref{type=ThisT}=This,ItemFrom,ItemTo) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,ItemFrom,ItemTo,?get_env(),?wxListCtrl_RefreshItems). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlscrolllist">external documentation</a>. -doc """ Scrolls the list control. -If in icon, small icon or report view mode, `dx` specifies the number of pixels -to scroll. If in list view mode, `dx` specifies the number of columns to scroll. -`dy` always specifies the number of pixels to scroll vertically. +If in icon, small icon or report view mode, `dx` specifies the number of pixels to +scroll. If in list view mode, `dx` specifies the number of columns to scroll. `dy` always +specifies the number of pixels to scroll vertically. Note: This method is currently only implemented in the Windows version. """. @@ -940,12 +969,11 @@ scrollList(#wx_ref{type=ThisT}=This,Dx,Dy) wxe_util:queue_cmd(This,Dx,Dy,?get_env(),?wxListCtrl_ScrollList), wxe_util:rec(?wxListCtrl_ScrollList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetbackgroundcolour">external documentation</a>. -doc """ Sets the background colour. -Note that the `wxWindow:getBackgroundColour/1` function of `m:wxWindow` base -class can be used to retrieve the current background colour. +Note that the `wxWindow:getBackgroundColour/1` function of `m:wxWindow` base class can be used to retrieve the current +background colour. """. -spec setBackgroundColour(This, Col) -> boolean() when This::wxListCtrl(), Col::wx:wx_colour(). @@ -955,7 +983,6 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,Col) wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxListCtrl_SetBackgroundColour), wxe_util:rec(?wxListCtrl_SetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetcolumn">external documentation</a>. -doc """ Sets information about this column. @@ -970,20 +997,18 @@ setColumn(#wx_ref{type=ThisT}=This,Col,#wx_ref{type=ItemT}=Item) wxe_util:queue_cmd(This,Col,Item,?get_env(),?wxListCtrl_SetColumn), wxe_util:rec(?wxListCtrl_SetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetcolumnwidth">external documentation</a>. -doc """ Sets the column width. -`width` can be a width in pixels or `wxLIST_AUTOSIZE` (-1) or -`wxLIST_AUTOSIZE_USEHEADER` (-2). +`width` can be a width in pixels or `wxLIST_AUTOSIZE` (-1) or `wxLIST_AUTOSIZE_USEHEADER` (-2). `wxLIST_AUTOSIZE` will resize the column to the length of its longest item. -`wxLIST_AUTOSIZE_USEHEADER` will resize the column to the length of the header -(Win32) or 80 pixels (other platforms). +`wxLIST_AUTOSIZE_USEHEADER` will resize the column to the length of the header (Win32) or +80 pixels (other platforms). -In small or normal icon view, `col` must be -1, and the column width is set for -all columns. +In small or normal icon view, `col` must be -1, and the column width is set for all +columns. """. -spec setColumnWidth(This, Col, Width) -> boolean() when This::wxListCtrl(), Col::integer(), Width::integer(). @@ -993,15 +1018,13 @@ setColumnWidth(#wx_ref{type=ThisT}=This,Col,Width) wxe_util:queue_cmd(This,Col,Width,?get_env(),?wxListCtrl_SetColumnWidth), wxe_util:rec(?wxListCtrl_SetColumnWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetimagelist">external documentation</a>. -doc """ Sets the image list associated with the control. -`which` is one of `wxIMAGE_LIST_NORMAL`, `wxIMAGE_LIST_SMALL`, -`wxIMAGE_LIST_STATE` (the last is unimplemented). +`which` is one of `wxIMAGE_LIST_NORMAL`, `wxIMAGE_LIST_SMALL`, `wxIMAGE_LIST_STATE` (the +last is unimplemented). -This method does not take ownership of the image list, you have to delete it -yourself. +This method does not take ownership of the image list, you have to delete it yourself. See: `assignImageList/3` """. @@ -1013,15 +1036,14 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList,Which) ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,Which,?get_env(),?wxListCtrl_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitem">external documentation</a>. -doc """ Sets the data of an item. -Using the `m:wxListItem`'s mask and state mask, you can change only selected -attributes of a `m:wxListCtrl` item. +Using the `m:wxListItem`'s mask and state mask, you can change only selected attributes +of a `m:wxListCtrl` item. -Return: true if the item was successfully updated or false if the update failed -for some reason (e.g. an invalid item index). +Return: true if the item was successfully updated or false if the update failed for some +reason (e.g. an invalid item index). """. -spec setItem(This, Info) -> boolean() when This::wxListCtrl(), Info::wxListItem:wxListItem(). @@ -1031,7 +1053,7 @@ setItem(#wx_ref{type=ThisT}=This,#wx_ref{type=InfoT}=Info) -> wxe_util:queue_cmd(This,Info,?get_env(),?wxListCtrl_SetItem_1), wxe_util:rec(?wxListCtrl_SetItem_1). -%% @equiv setItem(This,Index,Column,Label, []) +-doc(#{equiv => setItem(This,Index,Column,Label, [])}). -spec setItem(This, Index, Column, Label) -> boolean() when This::wxListCtrl(), Index::integer(), Column::integer(), Label::unicode:chardata(). @@ -1039,12 +1061,11 @@ setItem(This,Index,Column,Label) when is_record(This, wx_ref),is_integer(Index),is_integer(Column),?is_chardata(Label) -> setItem(This,Index,Column,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitem">external documentation</a>. -doc """ Sets an item string field at a particular column. -Return: true if the item was successfully updated or false if the update failed -for some reason (e.g. an invalid item index). +Return: true if the item was successfully updated or false if the update failed for some +reason (e.g. an invalid item index). """. -spec setItem(This, Index, Column, Label, [Option]) -> boolean() when This::wxListCtrl(), Index::integer(), Column::integer(), Label::unicode:chardata(), @@ -1059,12 +1080,10 @@ setItem(#wx_ref{type=ThisT}=This,Index,Column,Label, Options) wxe_util:queue_cmd(This,Index,Column,Label_UC, Opts,?get_env(),?wxListCtrl_SetItem_4), wxe_util:rec(?wxListCtrl_SetItem_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitembackgroundcolour">external documentation</a>. -doc """ Sets the background colour for this item. -This function only works in report view mode. The colour can be retrieved using -`getItemBackgroundColour/2`. +This function only works in report view mode. The colour can be retrieved using `getItemBackgroundColour/2`. """. -spec setItemBackgroundColour(This, Item, Col) -> 'ok' when This::wxListCtrl(), Item::integer(), Col::wx:wx_colour(). @@ -1073,19 +1092,17 @@ setItemBackgroundColour(#wx_ref{type=ThisT}=This,Item,Col) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,Item,wxe_util:color(Col),?get_env(),?wxListCtrl_SetItemBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemcount">external documentation</a>. -doc """ This method can only be used with virtual list controls. -It is used to indicate to the control the number of items it contains. After -calling it, the main program should be ready to handle calls to various item -callbacks (such as `wxListCtrl::OnGetItemText` (not implemented in wx)) for all -items in the range from 0 to `count`. +It is used to indicate to the control the number of items it contains. After calling it, +the main program should be ready to handle calls to various item callbacks (such as `wxListCtrl::OnGetItemText` +(not implemented in wx)) for all items in the range from 0 to `count`. Notice that the control is not necessarily redrawn after this call as it may be -undesirable if an item which is not visible on the screen anyhow was added to or -removed from a control displaying many items, if you do need to refresh the -display you can just call `wxWindow:refresh/2` manually. +undesirable if an item which is not visible on the screen anyhow was added to or removed +from a control displaying many items, if you do need to refresh the display you can just +call `wxWindow:refresh/2` manually. """. -spec setItemCount(This, Count) -> 'ok' when This::wxListCtrl(), Count::integer(). @@ -1094,12 +1111,11 @@ setItemCount(#wx_ref{type=ThisT}=This,Count) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,Count,?get_env(),?wxListCtrl_SetItemCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemdata">external documentation</a>. -doc """ Associates application-defined data with this item. -Notice that this function cannot be used to associate pointers with the control -items, use `SetItemPtrData()` (not implemented in wx) instead. +Notice that this function cannot be used to associate pointers with the control items, +use `SetItemPtrData()` (not implemented in wx) instead. """. -spec setItemData(This, Item, Data) -> boolean() when This::wxListCtrl(), Item::integer(), Data::integer(). @@ -1109,7 +1125,6 @@ setItemData(#wx_ref{type=ThisT}=This,Item,Data) wxe_util:queue_cmd(This,Item,Data,?get_env(),?wxListCtrl_SetItemData), wxe_util:rec(?wxListCtrl_SetItemData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemfont">external documentation</a>. -doc "Sets the item's font.". -spec setItemFont(This, Item, Font) -> 'ok' when This::wxListCtrl(), Item::integer(), Font::wxFont:wxFont(). @@ -1119,7 +1134,7 @@ setItemFont(#wx_ref{type=ThisT}=This,Item,#wx_ref{type=FontT}=Font) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Item,Font,?get_env(),?wxListCtrl_SetItemFont). -%% @equiv setItemImage(This,Item,Image, []) +-doc(#{equiv => setItemImage(This,Item,Image, [])}). -spec setItemImage(This, Item, Image) -> boolean() when This::wxListCtrl(), Item::integer(), Image::integer(). @@ -1127,7 +1142,6 @@ setItemImage(This,Item,Image) when is_record(This, wx_ref),is_integer(Item),is_integer(Image) -> setItemImage(This,Item,Image, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemimage">external documentation</a>. -doc """ Sets the unselected and selected images associated with the item. @@ -1145,12 +1159,11 @@ setItemImage(#wx_ref{type=ThisT}=This,Item,Image, Options) wxe_util:queue_cmd(This,Item,Image, Opts,?get_env(),?wxListCtrl_SetItemImage), wxe_util:rec(?wxListCtrl_SetItemImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemcolumnimage">external documentation</a>. -doc """ Sets the image associated with the item. -In report view, you can specify the column. The image is an index into the image -list associated with the list control. +In report view, you can specify the column. The image is an index into the image list +associated with the list control. """. -spec setItemColumnImage(This, Item, Column, Image) -> boolean() when This::wxListCtrl(), Item::integer(), Column::integer(), Image::integer(). @@ -1160,7 +1173,6 @@ setItemColumnImage(#wx_ref{type=ThisT}=This,Item,Column,Image) wxe_util:queue_cmd(This,Item,Column,Image,?get_env(),?wxListCtrl_SetItemColumnImage), wxe_util:rec(?wxListCtrl_SetItemColumnImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemposition">external documentation</a>. -doc """ Sets the position of the item, in icon or small icon view. @@ -1174,23 +1186,20 @@ setItemPosition(#wx_ref{type=ThisT}=This,Item,{PosX,PosY} = Pos) wxe_util:queue_cmd(This,Item,Pos,?get_env(),?wxListCtrl_SetItemPosition), wxe_util:rec(?wxListCtrl_SetItemPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemstate">external documentation</a>. -doc """ Sets the item state. -The `stateMask` is a combination of `wxLIST_STATE_XXX` constants described in -`m:wxListItem` documentation. For each of the bits specified in `stateMask`, the -corresponding state is set or cleared depending on whether `state` argument -contains the same bit or not. +The `stateMask` is a combination of `wxLIST_STATE_XXX` constants described in `m:wxListItem` +documentation. For each of the bits specified in `stateMask`, the corresponding state is +set or cleared depending on whether `state` argument contains the same bit or not. So to select an item you can use while to deselect it you should use -Consider using `m:wxListView` if possible to avoid dealing with this error-prone -and confusing method. +Consider using `m:wxListView` if possible to avoid dealing with this error-prone and +confusing method. -Also notice that contrary to the usual rule that only user actions generate -events, this method does generate wxEVT_LIST_ITEM_SELECTED event when it is used -to select an item. +Also notice that contrary to the usual rule that only user actions generate events, this +method does generate wxEVT_LIST_ITEM_SELECTED event when it is used to select an item. """. -spec setItemState(This, Item, State, StateMask) -> boolean() when This::wxListCtrl(), Item::integer(), State::integer(), StateMask::integer(). @@ -1200,7 +1209,6 @@ setItemState(#wx_ref{type=ThisT}=This,Item,State,StateMask) wxe_util:queue_cmd(This,Item,State,StateMask,?get_env(),?wxListCtrl_SetItemState), wxe_util:rec(?wxListCtrl_SetItemState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemtext">external documentation</a>. -doc "Sets the item text for this item.". -spec setItemText(This, Item, Text) -> 'ok' when This::wxListCtrl(), Item::integer(), Text::unicode:chardata(). @@ -1210,12 +1218,10 @@ setItemText(#wx_ref{type=ThisT}=This,Item,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Item,Text_UC,?get_env(),?wxListCtrl_SetItemText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetitemtextcolour">external documentation</a>. -doc """ Sets the colour for this item. -This function only works in report view. The colour can be retrieved using -`getItemTextColour/2`. +This function only works in report view. The colour can be retrieved using `getItemTextColour/2`. """. -spec setItemTextColour(This, Item, Col) -> 'ok' when This::wxListCtrl(), Item::integer(), Col::wx:wx_colour(). @@ -1224,7 +1230,7 @@ setItemTextColour(#wx_ref{type=ThisT}=This,Item,Col) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,Item,wxe_util:color(Col),?get_env(),?wxListCtrl_SetItemTextColour). -%% @equiv setSingleStyle(This,Style, []) +-doc(#{equiv => setSingleStyle(This,Style, [])}). -spec setSingleStyle(This, Style) -> 'ok' when This::wxListCtrl(), Style::integer(). @@ -1232,7 +1238,6 @@ setSingleStyle(This,Style) when is_record(This, wx_ref),is_integer(Style) -> setSingleStyle(This,Style, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetsinglestyle">external documentation</a>. -doc "Adds or removes a single window style.". -spec setSingleStyle(This, Style, [Option]) -> 'ok' when This::wxListCtrl(), Style::integer(), @@ -1245,7 +1250,6 @@ setSingleStyle(#wx_ref{type=ThisT}=This,Style, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Style, Opts,?get_env(),?wxListCtrl_SetSingleStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsettextcolour">external documentation</a>. -doc "Sets the text colour of the list control.". -spec setTextColour(This, Col) -> 'ok' when This::wxListCtrl(), Col::wx:wx_colour(). @@ -1254,7 +1258,6 @@ setTextColour(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxListCtrl), wxe_util:queue_cmd(This,wxe_util:color(Col),?get_env(),?wxListCtrl_SetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistctrl.html#wxlistctrlsetwindowstyleflag">external documentation</a>. -doc "Sets the whole window style, deleting all items.". -spec setWindowStyleFlag(This, Style) -> 'ok' when This::wxListCtrl(), Style::integer(). @@ -1264,22 +1267,6 @@ setWindowStyleFlag(#wx_ref{type=ThisT}=This,Style) wxe_util:queue_cmd(This,Style,?get_env(),?wxListCtrl_SetWindowStyleFlag). --doc """ -Sort the items in the list control. - -Sorts the items with supplied `SortCallBack` fun. - -SortCallBack receives the client data associated with two items to compare -(`NOT` the the index), and should return 0 if the items are equal, a negative -value if the first item is less than the second one and a positive value if the -first item is greater than the second one. - -Remark: Notice that the control may only be sorted on client data associated -with the items, so you must use SetItemData if you want to be able to sort the -items in the control. - -The callback may not call other (wx) processes. -""". -spec sortItems(This::wxListCtrl(), SortCallBack) -> boolean() when SortCallBack :: fun((integer(), integer()) -> integer()). sortItems(#wx_ref{type=ThisT}=This, SortCallBack) @@ -1290,556 +1277,374 @@ sortItems(#wx_ref{type=ThisT}=This, SortCallBack) wxe_util:queue_cmd(This, SortId, ?get_env(), Op), wxe_util:rec(Op). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the list control.". +-doc "Destroys the object". -spec destroy(This::wxListCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxListCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxListEvent.erl b/lib/wx/src/gen/wxListEvent.erl index b047b689385b..334f8ae35c6d 100644 --- a/lib/wx/src/gen/wxListEvent.erl +++ b/lib/wx/src/gen/wxListEvent.erl @@ -20,23 +20,23 @@ -module(wxListEvent). -moduledoc """ -Functions for wxListEvent class - -A list event holds information about events associated with `m:wxListCtrl` -objects. +A list event holds information about events associated with `m:wxListCtrl` objects. See: `m:wxListCtrl` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` -wxWidgets docs: -[wxListEvent](https://docs.wxwidgets.org/3.1/classwx_list_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxListEvent](https://docs.wxwidgets.org/3.2/classwx_list_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxListEventType`](`t:wxListEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxListEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getCacheFrom/1,getCacheTo/1,getColumn/1,getData/1,getImage/1,getIndex/1, @@ -52,17 +52,15 @@ subscribe to events of this type. -include("wx.hrl"). -type wxListEventType() :: 'command_list_begin_drag' | 'command_list_begin_rdrag' | 'command_list_begin_label_edit' | 'command_list_end_label_edit' | 'command_list_delete_item' | 'command_list_delete_all_items' | 'command_list_key_down' | 'command_list_insert_item' | 'command_list_col_click' | 'command_list_col_right_click' | 'command_list_col_begin_drag' | 'command_list_col_dragging' | 'command_list_col_end_drag' | 'command_list_item_selected' | 'command_list_item_deselected' | 'command_list_item_right_click' | 'command_list_item_middle_click' | 'command_list_item_activated' | 'command_list_item_focused' | 'command_list_cache_hint'. -export_type([wxListEvent/0, wxList/0, wxListEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetcachefrom">external documentation</a>. -doc """ -For `EVT_LIST_CACHE_HINT` event only: return the first item which the list -control advises us to cache. +For `EVT\_LIST\_CACHE\_HINT` event only: return the first item which the list control +advises us to cache. """. -spec getCacheFrom(This) -> integer() when This::wxListEvent(). @@ -71,10 +69,9 @@ getCacheFrom(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetCacheFrom), wxe_util:rec(?wxListEvent_GetCacheFrom). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetcacheto">external documentation</a>. -doc """ -For `EVT_LIST_CACHE_HINT` event only: return the last item (inclusive) which the -list control advises us to cache. +For `EVT\_LIST\_CACHE\_HINT` event only: return the last item (inclusive) which the list +control advises us to cache. """. -spec getCacheTo(This) -> integer() when This::wxListEvent(). @@ -83,7 +80,6 @@ getCacheTo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetCacheTo), wxe_util:rec(?wxListEvent_GetCacheTo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetkeycode">external documentation</a>. -doc "Key code if the event is a keypress event.". -spec getKeyCode(This) -> integer() when This::wxListEvent(). @@ -92,7 +88,6 @@ getKeyCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetKeyCode), wxe_util:rec(?wxListEvent_GetKeyCode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetindex">external documentation</a>. -doc "The item index.". -spec getIndex(This) -> integer() when This::wxListEvent(). @@ -101,13 +96,12 @@ getIndex(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetIndex), wxe_util:rec(?wxListEvent_GetIndex). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetcolumn">external documentation</a>. -doc """ The column position: it is only used with `COL` events. -For the column dragging events, it is the column to the left of the divider -being dragged, for the column click events it may be -1 if the user clicked in -the list control header outside any column. +For the column dragging events, it is the column to the left of the divider being +dragged, for the column click events it may be -1 if the user clicked in the list control +header outside any column. """. -spec getColumn(This) -> integer() when This::wxListEvent(). @@ -116,7 +110,6 @@ getColumn(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetColumn), wxe_util:rec(?wxListEvent_GetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetpoint">external documentation</a>. -doc "The position of the mouse pointer if the event is a drag event.". -spec getPoint(This) -> {X::integer(), Y::integer()} when This::wxListEvent(). @@ -125,8 +118,7 @@ getPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetPoint), wxe_util:rec(?wxListEvent_GetPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetlabel">external documentation</a>. --doc "The (new) item label for `EVT_LIST_END_LABEL_EDIT` event.". +-doc "The (new) item label for `EVT\_LIST\_END\_LABEL\_EDIT` event.". -spec getLabel(This) -> unicode:charlist() when This::wxListEvent(). getLabel(#wx_ref{type=ThisT}=This) -> @@ -134,7 +126,6 @@ getLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetLabel), wxe_util:rec(?wxListEvent_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgettext">external documentation</a>. -doc "The text.". -spec getText(This) -> unicode:charlist() when This::wxListEvent(). @@ -143,7 +134,6 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetText), wxe_util:rec(?wxListEvent_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetimage">external documentation</a>. -doc "The image.". -spec getImage(This) -> integer() when This::wxListEvent(). @@ -152,7 +142,6 @@ getImage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetImage), wxe_util:rec(?wxListEvent_GetImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetdata">external documentation</a>. -doc "The data.". -spec getData(This) -> integer() when This::wxListEvent(). @@ -161,7 +150,6 @@ getData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetData), wxe_util:rec(?wxListEvent_GetData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetmask">external documentation</a>. -doc "The mask.". -spec getMask(This) -> integer() when This::wxListEvent(). @@ -170,7 +158,6 @@ getMask(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetMask), wxe_util:rec(?wxListEvent_GetMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventgetitem">external documentation</a>. -doc """ An item object, used by some events. @@ -183,13 +170,12 @@ getItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListEvent_GetItem), wxe_util:rec(?wxListEvent_GetItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistevent.html#wxlisteventiseditcancelled">external documentation</a>. -doc """ -This method only makes sense for `EVT_LIST_END_LABEL_EDIT` message and returns -true if it the label editing has been cancelled by the user (`getLabel/1` -returns an empty string in this case but it doesn't allow the application to -distinguish between really cancelling the edit and the admittedly rare case when -the user wants to rename it to an empty string). +This method only makes sense for `EVT\_LIST\_END\_LABEL\_EDIT` message and returns true +if it the label editing has been cancelled by the user (`getLabel/1` returns an empty +string in this case but it doesn't allow the application to distinguish between really +cancelling the edit and the admittedly rare case when the user wants to rename it to an +empty string). """. -spec isEditCancelled(This) -> boolean() when This::wxListEvent(). @@ -199,68 +185,47 @@ isEditCancelled(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxListEvent_IsEditCancelled). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxListItem.erl b/lib/wx/src/gen/wxListItem.erl index ae4f82231f69..6ed78d66d0e0 100644 --- a/lib/wx/src/gen/wxListItem.erl +++ b/lib/wx/src/gen/wxListItem.erl @@ -20,22 +20,63 @@ -module(wxListItem). -moduledoc """ -Functions for wxListItem class - This class stores information about a `m:wxListCtrl` item or column. `m:wxListItem` is a class which contains information about: -The `m:wxListItem` object can also contain item-specific colour and font -information: for this you need to call one of `setTextColour/2`, -`setBackgroundColour/2` or `setFont/2` functions on it passing it the -colour/font to use. If the colour/font is not specified, the default list -control colour/font is used. +* Zero based item position; see `setId/2` and `getId/1`. + +* Zero based column index; see `setColumn/2` and `getColumn/1`. + +* The label (or header for columns); see `setText/2` and `getText/1`. + +* The zero based index into an image list; see `getImage/1` and `setImage/2`. + +* Application defined data; see `SetData()` (not implemented in wx) and `GetData()` (not +implemented in wx). + +* For columns only: the width of the column; see `setWidth/2` and `getWidth/1`. + +* For columns only: the format of the column; one of `wxLIST_FORMAT_LEFT`, `wxLIST_FORMAT_RIGHT`, `wxLIST_FORMAT_CENTRE`. +See `setAlign/2` and `getAlign/1`. + +* The state of the item; see `setState/2` and `getState/1`. This is a bitlist of the following flags: + +* `wxLIST_STATE_FOCUSED:` The item has the focus. + +* `wxLIST_STATE_SELECTED:` The item is selected. + +* `wxLIST_STATE_DONTCARE:` No special flags (the value of this constant is 0). + +* `wxLIST_STATE_DROPHILITED:` The item is highlighted to receive a drop event. Win32 only. + +* `wxLIST_STATE_CUT:` The item is in the cut state. Win32 only. + +* A mask indicating which state flags are valid; this is a bitlist of the flags reported +above for the item state. See `setStateMask/2` and GetStateMask(). + +* A mask indicating which fields of this class are valid; see `setMask/2` and `getMask/1`. This is a bitlist of +the following flags: + +* `wxLIST_MASK_STATE:` The state field is valid. + +* `wxLIST_MASK_TEXT:` The label field is valid. + +* `wxLIST_MASK_IMAGE:` The image field is valid. + +* `wxLIST_MASK_DATA:` The application-defined data field is valid. + +* `wxLIST_MASK_WIDTH:` The column width field is valid. + +* `wxLIST_MASK_FORMAT:` The column format field is valid. + +The `m:wxListItem` object can also contain item-specific colour and font information: for +this you need to call one of `setTextColour/2`, `setBackgroundColour/2` or `setFont/2` functions on it passing it the colour/font to use. If +the colour/font is not specified, the default list control colour/font is used. See: `m:wxListCtrl` -wxWidgets docs: -[wxListItem](https://docs.wxwidgets.org/3.1/classwx_list_item.html) +wxWidgets docs: [wxListItem](https://docs.wxwidgets.org/3.2/classwx_list_item.html) """. -include("wxe.hrl"). -export([clear/1,destroy/1,getAlign/1,getBackgroundColour/1,getColumn/1,getFont/1, @@ -49,18 +90,16 @@ wxWidgets docs: -type wxListItem() :: wx:wx_object(). -export_type([wxListItem/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemwxlistitem">external documentation</a>. -doc "Constructor.". -spec new() -> wxListItem(). new() -> wxe_util:queue_cmd(?get_env(), ?wxListItem_new_0), wxe_util:rec(?wxListItem_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemwxlistitem">external documentation</a>. +-doc "". -spec new(Item) -> wxListItem() when Item::wxListItem(). new(#wx_ref{type=ItemT}=Item) -> @@ -68,7 +107,6 @@ new(#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(Item,?get_env(),?wxListItem_new_1), wxe_util:rec(?wxListItem_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemclear">external documentation</a>. -doc "Resets the item state to the default.". -spec clear(This) -> 'ok' when This::wxListItem(). @@ -76,14 +114,12 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,?get_env(),?wxListItem_Clear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetalign">external documentation</a>. -%%<br /> Res = ?wxLIST_FORMAT_LEFT | ?wxLIST_FORMAT_RIGHT | ?wxLIST_FORMAT_CENTRE | ?wxLIST_FORMAT_CENTER -doc """ Returns the alignment for this item. -Can be one of `wxLIST_FORMAT_LEFT`, `wxLIST_FORMAT_RIGHT` or -`wxLIST_FORMAT_CENTRE`. +Can be one of `wxLIST_FORMAT_LEFT`, `wxLIST_FORMAT_RIGHT` or `wxLIST_FORMAT_CENTRE`. """. +%% Res = ?wxLIST_FORMAT_LEFT | ?wxLIST_FORMAT_RIGHT | ?wxLIST_FORMAT_CENTRE | ?wxLIST_FORMAT_CENTER -spec getAlign(This) -> wx:wx_enum() when This::wxListItem(). getAlign(#wx_ref{type=ThisT}=This) -> @@ -91,7 +127,6 @@ getAlign(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetAlign), wxe_util:rec(?wxListItem_GetAlign). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetbackgroundcolour">external documentation</a>. -doc "Returns the background colour for this item.". -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxListItem(). @@ -100,7 +135,6 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetBackgroundColour), wxe_util:rec(?wxListItem_GetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetcolumn">external documentation</a>. -doc "Returns the zero-based column; meaningful only in report mode.". -spec getColumn(This) -> integer() when This::wxListItem(). @@ -109,7 +143,6 @@ getColumn(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetColumn), wxe_util:rec(?wxListItem_GetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetfont">external documentation</a>. -doc "Returns the font used to display the item.". -spec getFont(This) -> wxFont:wxFont() when This::wxListItem(). @@ -118,7 +151,6 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetFont), wxe_util:rec(?wxListItem_GetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetid">external documentation</a>. -doc "Returns the zero-based item position.". -spec getId(This) -> integer() when This::wxListItem(). @@ -127,11 +159,7 @@ getId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetId), wxe_util:rec(?wxListItem_GetId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetimage">external documentation</a>. --doc """ -Returns the zero-based index of the image associated with the item into the -image list. -""". +-doc "Returns the zero-based index of the image associated with the item into the image list.". -spec getImage(This) -> integer() when This::wxListItem(). getImage(#wx_ref{type=ThisT}=This) -> @@ -139,11 +167,22 @@ getImage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetImage), wxe_util:rec(?wxListItem_GetImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetmask">external documentation</a>. -doc """ Returns a bit mask indicating which fields of the structure are valid. Can be any combination of the following values: + +* wxLIST_MASK_STATE: `GetState` is valid. + +* wxLIST_MASK_TEXT: `GetText` is valid. + +* wxLIST_MASK_IMAGE: `GetImage` is valid. + +* wxLIST_MASK_DATA: `GetData` is valid. + +* wxLIST_MASK_WIDTH: `GetWidth` is valid. + +* wxLIST_MASK_FORMAT: `GetFormat` is valid. """. -spec getMask(This) -> integer() when This::wxListItem(). @@ -152,11 +191,20 @@ getMask(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetMask), wxe_util:rec(?wxListItem_GetMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetstate">external documentation</a>. -doc """ Returns a bit field representing the state of the item. Can be any combination of: + +* wxLIST_STATE_DONTCARE: No special flags (the values of this constant is 0). + +* wxLIST_STATE_DROPHILITED: The item is highlighted to receive a drop event. Win32 only. + +* wxLIST_STATE_FOCUSED: The item has the focus. + +* wxLIST_STATE_SELECTED: The item is selected. + +* wxLIST_STATE_CUT: The item is in the cut state. Win32 only. """. -spec getState(This) -> integer() when This::wxListItem(). @@ -165,7 +213,6 @@ getState(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetState), wxe_util:rec(?wxListItem_GetState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgettext">external documentation</a>. -doc "Returns the label/header text.". -spec getText(This) -> unicode:charlist() when This::wxListItem(). @@ -174,7 +221,6 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetText), wxe_util:rec(?wxListItem_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgettextcolour">external documentation</a>. -doc "Returns the text colour.". -spec getTextColour(This) -> wx:wx_colour4() when This::wxListItem(). @@ -183,7 +229,6 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetTextColour), wxe_util:rec(?wxListItem_GetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemgetwidth">external documentation</a>. -doc """ Meaningful only for column headers in report mode. @@ -196,13 +241,12 @@ getWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItem_GetWidth), wxe_util:rec(?wxListItem_GetWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetalign">external documentation</a>. -%%<br /> Align = ?wxLIST_FORMAT_LEFT | ?wxLIST_FORMAT_RIGHT | ?wxLIST_FORMAT_CENTRE | ?wxLIST_FORMAT_CENTER -doc """ Sets the alignment for the item. See also `getAlign/1` """. +%% Align = ?wxLIST_FORMAT_LEFT | ?wxLIST_FORMAT_RIGHT | ?wxLIST_FORMAT_CENTRE | ?wxLIST_FORMAT_CENTER -spec setAlign(This, Align) -> 'ok' when This::wxListItem(), Align::wx:wx_enum(). setAlign(#wx_ref{type=ThisT}=This,Align) @@ -210,7 +254,6 @@ setAlign(#wx_ref{type=ThisT}=This,Align) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Align,?get_env(),?wxListItem_SetAlign). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetbackgroundcolour">external documentation</a>. -doc "Sets the background colour for the item.". -spec setBackgroundColour(This, ColBack) -> 'ok' when This::wxListItem(), ColBack::wx:wx_colour(). @@ -219,7 +262,6 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,wxe_util:color(ColBack),?get_env(),?wxListItem_SetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetcolumn">external documentation</a>. -doc """ Sets the zero-based column. @@ -232,7 +274,6 @@ setColumn(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Col,?get_env(),?wxListItem_SetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetfont">external documentation</a>. -doc "Sets the font for the item.". -spec setFont(This, Font) -> 'ok' when This::wxListItem(), Font::wxFont:wxFont(). @@ -241,7 +282,6 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxListItem_SetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetid">external documentation</a>. -doc "Sets the zero-based item position.". -spec setId(This, Id) -> 'ok' when This::wxListItem(), Id::integer(). @@ -250,11 +290,7 @@ setId(#wx_ref{type=ThisT}=This,Id) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Id,?get_env(),?wxListItem_SetId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetimage">external documentation</a>. --doc """ -Sets the zero-based index of the image associated with the item into the image -list. -""". +-doc "Sets the zero-based index of the image associated with the item into the image list.". -spec setImage(This, Image) -> 'ok' when This::wxListItem(), Image::integer(). setImage(#wx_ref{type=ThisT}=This,Image) @@ -262,7 +298,6 @@ setImage(#wx_ref{type=ThisT}=This,Image) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Image,?get_env(),?wxListItem_SetImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetmask">external documentation</a>. -doc """ Sets the mask of valid fields. @@ -275,10 +310,9 @@ setMask(#wx_ref{type=ThisT}=This,Mask) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Mask,?get_env(),?wxListItem_SetMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetstate">external documentation</a>. -doc """ -Sets the item state flags (note that the valid state flags are influenced by the -value of the state mask, see `setStateMask/2`). +Sets the item state flags (note that the valid state flags are influenced by the value of +the state mask, see `setStateMask/2`). See `getState/1` for valid flag values. """. @@ -289,10 +323,8 @@ setState(#wx_ref{type=ThisT}=This,State) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,State,?get_env(),?wxListItem_SetState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetstatemask">external documentation</a>. -doc """ -Sets the bitmask that is used to determine which of the state flags are to be -set. +Sets the bitmask that is used to determine which of the state flags are to be set. See also `setState/2`. """. @@ -303,7 +335,6 @@ setStateMask(#wx_ref{type=ThisT}=This,StateMask) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,StateMask,?get_env(),?wxListItem_SetStateMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsettext">external documentation</a>. -doc "Sets the text label for the item.". -spec setText(This, Text) -> 'ok' when This::wxListItem(), Text::unicode:chardata(). @@ -313,7 +344,6 @@ setText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxListItem_SetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsettextcolour">external documentation</a>. -doc "Sets the text colour for the item.". -spec setTextColour(This, ColText) -> 'ok' when This::wxListItem(), ColText::wx:wx_colour(). @@ -322,7 +352,6 @@ setTextColour(#wx_ref{type=ThisT}=This,ColText) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,wxe_util:color(ColText),?get_env(),?wxListItem_SetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitem.html#wxlistitemsetwidth">external documentation</a>. -doc """ Meaningful only for column headers in report mode. @@ -335,8 +364,7 @@ setWidth(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxListItem), wxe_util:queue_cmd(This,Width,?get_env(),?wxListItem_SetWidth). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxListItem()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxListItem), diff --git a/lib/wx/src/gen/wxListItemAttr.erl b/lib/wx/src/gen/wxListItemAttr.erl index 29769f1b7935..42c6bce73779 100644 --- a/lib/wx/src/gen/wxListItemAttr.erl +++ b/lib/wx/src/gen/wxListItemAttr.erl @@ -22,8 +22,7 @@ -moduledoc """ Functions for wxListItemAttr class -wxWidgets docs: -[wxListItemAttr](https://docs.wxwidgets.org/3.1/classwx_list_item_attr.html) +wxWidgets docs: [wxListItemAttr](https://docs.wxwidgets.org/3.2/classwx_list_item_attr.html) """. -include("wxe.hrl"). -export([destroy/1,getBackgroundColour/1,getFont/1,getTextColour/1,hasBackgroundColour/1, @@ -35,17 +34,16 @@ wxWidgets docs: -type wxListItemAttr() :: wx:wx_object(). -export_type([wxListItemAttr/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrwxlistitemattr">external documentation</a>. +-doc "". -spec new() -> wxListItemAttr(). new() -> wxe_util:queue_cmd(?get_env(), ?wxListItemAttr_new_0), wxe_util:rec(?wxListItemAttr_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrwxlistitemattr">external documentation</a>. +-doc "". -spec new(ColText, ColBack, Font) -> wxListItemAttr() when ColText::wx:wx_colour(), ColBack::wx:wx_colour(), Font::wxFont:wxFont(). new(ColText,ColBack,#wx_ref{type=FontT}=Font) @@ -54,7 +52,7 @@ new(ColText,ColBack,#wx_ref{type=FontT}=Font) wxe_util:queue_cmd(wxe_util:color(ColText),wxe_util:color(ColBack),Font,?get_env(),?wxListItemAttr_new_3), wxe_util:rec(?wxListItemAttr_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrgetbackgroundcolour">external documentation</a>. +-doc "". -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxListItemAttr(). getBackgroundColour(#wx_ref{type=ThisT}=This) -> @@ -62,7 +60,7 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_GetBackgroundColour), wxe_util:rec(?wxListItemAttr_GetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrgetfont">external documentation</a>. +-doc "". -spec getFont(This) -> wxFont:wxFont() when This::wxListItemAttr(). getFont(#wx_ref{type=ThisT}=This) -> @@ -70,7 +68,7 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_GetFont), wxe_util:rec(?wxListItemAttr_GetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrgettextcolour">external documentation</a>. +-doc "". -spec getTextColour(This) -> wx:wx_colour4() when This::wxListItemAttr(). getTextColour(#wx_ref{type=ThisT}=This) -> @@ -78,7 +76,7 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_GetTextColour), wxe_util:rec(?wxListItemAttr_GetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrhasbackgroundcolour">external documentation</a>. +-doc "". -spec hasBackgroundColour(This) -> boolean() when This::wxListItemAttr(). hasBackgroundColour(#wx_ref{type=ThisT}=This) -> @@ -86,7 +84,7 @@ hasBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_HasBackgroundColour), wxe_util:rec(?wxListItemAttr_HasBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrhasfont">external documentation</a>. +-doc "". -spec hasFont(This) -> boolean() when This::wxListItemAttr(). hasFont(#wx_ref{type=ThisT}=This) -> @@ -94,7 +92,7 @@ hasFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_HasFont), wxe_util:rec(?wxListItemAttr_HasFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrhastextcolour">external documentation</a>. +-doc "". -spec hasTextColour(This) -> boolean() when This::wxListItemAttr(). hasTextColour(#wx_ref{type=ThisT}=This) -> @@ -102,7 +100,7 @@ hasTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListItemAttr_HasTextColour), wxe_util:rec(?wxListItemAttr_HasTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrsetbackgroundcolour">external documentation</a>. +-doc "". -spec setBackgroundColour(This, ColBack) -> 'ok' when This::wxListItemAttr(), ColBack::wx:wx_colour(). setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) @@ -110,7 +108,7 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) ?CLASS(ThisT,wxListItemAttr), wxe_util:queue_cmd(This,wxe_util:color(ColBack),?get_env(),?wxListItemAttr_SetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrsetfont">external documentation</a>. +-doc "". -spec setFont(This, Font) -> 'ok' when This::wxListItemAttr(), Font::wxFont:wxFont(). setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> @@ -118,7 +116,7 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxListItemAttr_SetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistitemattr.html#wxlistitemattrsettextcolour">external documentation</a>. +-doc "". -spec setTextColour(This, ColText) -> 'ok' when This::wxListItemAttr(), ColText::wx:wx_colour(). setTextColour(#wx_ref{type=ThisT}=This,ColText) @@ -126,8 +124,7 @@ setTextColour(#wx_ref{type=ThisT}=This,ColText) ?CLASS(ThisT,wxListItemAttr), wxe_util:queue_cmd(This,wxe_util:color(ColText),?get_env(),?wxListItemAttr_SetTextColour). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxListItemAttr()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxListItemAttr), diff --git a/lib/wx/src/gen/wxListView.erl b/lib/wx/src/gen/wxListView.erl index 55511cdc7e7c..e54df9c2a524 100644 --- a/lib/wx/src/gen/wxListView.erl +++ b/lib/wx/src/gen/wxListView.erl @@ -20,25 +20,26 @@ -module(wxListView). -moduledoc """ -Functions for wxListView class +This class currently simply presents a simpler to use interface for the `m:wxListCtrl` -- +it can be thought of as a `façade` for that complicated class. -This class currently simply presents a simpler to use interface for the -`m:wxListCtrl` \- it can be thought of as a `façade` for that complicated class. +Using it is preferable to using `m:wxListCtrl` directly whenever possible because in the +future some ports might implement `m:wxListView` but not the full set of `m:wxListCtrl` features. -Using it is preferable to using `m:wxListCtrl` directly whenever possible -because in the future some ports might implement `m:wxListView` but not the full -set of `m:wxListCtrl` features. - -Other than different interface, this class is identical to `m:wxListCtrl`. In -particular, it uses the same events, same window styles and so on. +Other than different interface, this class is identical to `m:wxListCtrl`. In particular, +it uses the same events, same window styles and so on. See: `setColumnImage/3` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -wxWidgets docs: -[wxListView](https://docs.wxwidgets.org/3.1/classwx_list_view.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxListView](https://docs.wxwidgets.org/3.2/classwx_list_view.html) """. -include("wxe.hrl"). -export([clearColumnImage/2,focus/2,getFirstSelected/1,getFocusedItem/1,getNextSelected/2, @@ -86,16 +87,14 @@ wxWidgets docs: -type wxListView() :: wx:wx_object(). -export_type([wxListView/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewclearcolumnimage">external documentation</a>. -doc """ -Resets the column image - after calling this function, no image will be shown. +Resets the column image -- after calling this function, no image will be shown. See: `setColumnImage/3` """. @@ -106,7 +105,6 @@ clearColumnImage(#wx_ref{type=ThisT}=This,Col) ?CLASS(ThisT,wxListView), wxe_util:queue_cmd(This,Col,?get_env(),?wxListView_ClearColumnImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewfocus">external documentation</a>. -doc "Sets focus to the item with the given `index`.". -spec focus(This, Index) -> 'ok' when This::wxListView(), Index::integer(). @@ -115,12 +113,10 @@ focus(#wx_ref{type=ThisT}=This,Index) ?CLASS(ThisT,wxListView), wxe_util:queue_cmd(This,Index,?get_env(),?wxListView_Focus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewgetfirstselected">external documentation</a>. -doc """ Returns the first selected item in a (presumably) multiple selection control. -Together with `getNextSelected/2` it can be used to iterate over all selected -items in the control. +Together with `getNextSelected/2` it can be used to iterate over all selected items in the control. Return: The first selected item, if any, -1 otherwise. """. @@ -131,11 +127,13 @@ getFirstSelected(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListView_GetFirstSelected), wxe_util:rec(?wxListView_GetFirstSelected). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewgetfocuseditem">external documentation</a>. -doc """ Returns the currently focused item or -1 if none. -See: `isSelected/2`, `focus/2` +See: +* `isSelected/2` + +* `focus/2` """. -spec getFocusedItem(This) -> integer() when This::wxListView(). @@ -144,10 +142,9 @@ getFocusedItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListView_GetFocusedItem), wxe_util:rec(?wxListView_GetFocusedItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewgetnextselected">external documentation</a>. -doc """ -Used together with `getFirstSelected/1` to iterate over all selected items in -the control. +Used together with `getFirstSelected/1` to iterate over all selected items in the +control. Return: Returns the next selected item or -1 if there are no more of them. """. @@ -159,11 +156,13 @@ getNextSelected(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxListView_GetNextSelected), wxe_util:rec(?wxListView_GetNextSelected). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewisselected">external documentation</a>. -doc """ Returns true if the item with the given `index` is selected, false otherwise. -See: `getFirstSelected/1`, `getNextSelected/2` +See: +* `getFirstSelected/1` + +* `getNextSelected/2` """. -spec isSelected(This, Index) -> boolean() when This::wxListView(), Index::integer(). @@ -173,7 +172,7 @@ isSelected(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxListView_IsSelected), wxe_util:rec(?wxListView_IsSelected). -%% @equiv select(This,N, []) +-doc(#{equiv => select(This,N, [])}). -spec select(This, N) -> 'ok' when This::wxListView(), N::integer(). @@ -181,14 +180,12 @@ select(This,N) when is_record(This, wx_ref),is_integer(N) -> select(This,N, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewselect">external documentation</a>. -doc """ Selects or unselects the given item. -Notice that this method inherits the unusual behaviour of -`wxListCtrl:setItemState/4` which sends a wxEVT_LIST_ITEM_SELECTED event when it -is used to select an item, contrary to the usual rule that only the user actions -result in selection. +Notice that this method inherits the unusual behaviour of `wxListCtrl:setItemState/4` which sends a +wxEVT_LIST_ITEM_SELECTED event when it is used to select an item, contrary to the usual +rule that only the user actions result in selection. """. -spec select(This, N, [Option]) -> 'ok' when This::wxListView(), N::integer(), @@ -201,12 +198,10 @@ select(#wx_ref{type=ThisT}=This,N, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,N, Opts,?get_env(),?wxListView_Select). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistview.html#wxlistviewsetcolumnimage">external documentation</a>. -doc """ Sets the column image for the specified column. -To use the column images, the control must have a valid image list with at least -one image. +To use the column images, the control must have a valid image list with at least one image. """. -spec setColumnImage(This, Col, Image) -> 'ok' when This::wxListView(), Col::integer(), Image::integer(). @@ -216,554 +211,371 @@ setColumnImage(#wx_ref{type=ThisT}=This,Col,Image) wxe_util:queue_cmd(This,Col,Image,?get_env(),?wxListView_SetColumnImage). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxListbook.erl b/lib/wx/src/gen/wxListbook.erl index 0045a9e446ce..22117e346aff 100644 --- a/lib/wx/src/gen/wxListbook.erl +++ b/lib/wx/src/gen/wxListbook.erl @@ -20,37 +20,57 @@ -module(wxListbook). -moduledoc """ -Functions for wxListbook class +`m:wxListbook` is a class similar to `m:wxNotebook` but which uses a `m:wxListCtrl` to +show the labels instead of the tabs. -`m:wxListbook` is a class similar to `m:wxNotebook` but which uses a -`m:wxListCtrl` to show the labels instead of the tabs. - -The underlying `m:wxListCtrl` displays page labels in a one-column report view -by default. Calling wxBookCtrl::SetImageList will implicitly switch the control -to use an icon view. +The underlying `m:wxListCtrl` displays page labels in a one-column report view by +default. Calling wxBookCtrl::SetImageList will implicitly switch the control to use an +icon view. For usage documentation of this class, please refer to the base abstract class -wxBookCtrl. You can also use the page_samples_notebook to see `m:wxListbook` in -action. +wxBookCtrl. You can also use the page_samples_notebook to see `m:wxListbook` in action. -Styles +## Styles This class supports the following styles: -See: ?wxBookCtrl, `m:wxNotebook`, -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_notebook) +* wxLB_DEFAULT: Choose the default location for the labels depending on the current +platform (left everywhere except Mac where it is top). + +* wxLB_TOP: Place labels above the page area. + +* wxLB_LEFT: Place labels on the left side. + +* wxLB_RIGHT: Place labels on the right side. + +* wxLB_BOTTOM: Place labels below the page area. + +See: +* ?wxBookCtrl + +* `m:wxNotebook` + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_notebook) + +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxBookCtrlBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxBookCtrlBase` -wxWidgets docs: -[wxListbook](https://docs.wxwidgets.org/3.1/classwx_listbook.html) +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxListbook](https://docs.wxwidgets.org/3.2/classwx_listbook.html) ## Events Event types emitted from this class: -[`listbook_page_changed`](`m:wxBookCtrlEvent`), -[`listbook_page_changing`](`m:wxBookCtrlEvent`) + +* [`listbook_page_changed`](`m:wxBookCtrlEvent`) + +* [`listbook_page_changing`](`m:wxBookCtrlEvent`) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,advanceSelection/1,advanceSelection/2,assignImageList/2, @@ -101,7 +121,6 @@ Event types emitted from this class: -type wxListbook() :: wx:wx_object(). -export_type([wxListbook/0]). -%% @hidden -doc false. parent_class(wxBookCtrlBase) -> true; parent_class(wxControl) -> true; @@ -109,14 +128,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookwxlistbook">external documentation</a>. -doc "Default ctor.". -spec new() -> wxListbook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxListbook_new_0), wxe_util:rec(?wxListbook_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxListbook() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -124,7 +142,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookwxlistbook">external documentation</a>. -doc "Constructs a listbook control.". -spec new(Parent, Id, [Option]) -> wxListbook() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -142,7 +159,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxListbook_new_3), wxe_util:rec(?wxListbook_new_3). -%% @equiv addPage(This,Page,Text, []) +-doc(#{equiv => addPage(This,Page,Text, [])}). -spec addPage(This, Page, Text) -> boolean() when This::wxListbook(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -150,17 +167,15 @@ addPage(This,Page,Text) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Text) -> addPage(This,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookaddpage">external documentation</a>. -doc """ Adds a new page. -The page must have the book control itself as the parent and must not have been -added to this control previously. +The page must have the book control itself as the parent and must not have been added to +this control previously. -The call to this function will generate the page changing and page changed -events if `select` is true, but not when inserting the very first page (as there -is no previous page selection to switch from in this case and so it wouldn't -make sense to e.g. veto such event). +The call to this function will generate the page changing and page changed events if `select` +is true, but not when inserting the very first page (as there is no previous page +selection to switch from in this case and so it wouldn't make sense to e.g. veto such event). Return: true if successful, false otherwise. @@ -184,7 +199,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text, Options) wxe_util:queue_cmd(This,Page,Text_UC, Opts,?get_env(),?wxListbook_AddPage), wxe_util:rec(?wxListbook_AddPage). -%% @equiv advanceSelection(This, []) +-doc(#{equiv => advanceSelection(This, [])}). -spec advanceSelection(This) -> 'ok' when This::wxListbook(). @@ -192,7 +207,6 @@ advanceSelection(This) when is_record(This, wx_ref) -> advanceSelection(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookadvanceselection">external documentation</a>. -doc """ Cycles through the tabs. @@ -209,11 +223,13 @@ advanceSelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxListbook_AdvanceSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookassignimagelist">external documentation</a>. -doc """ Sets the image list for the page control and takes ownership of the list. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec assignImageList(This, ImageList) -> 'ok' when This::wxListbook(), ImageList::wxImageList:wxImageList(). @@ -222,7 +238,7 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxListbook_AssignImageList). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxListbook(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -230,7 +246,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookcreate">external documentation</a>. -doc """ Create the list book control that has already been constructed with the default constructor. @@ -252,7 +267,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxListbook_Create), wxe_util:rec(?wxListbook_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookdeleteallpages">external documentation</a>. -doc "Deletes all pages.". -spec deleteAllPages(This) -> boolean() when This::wxListbook(). @@ -261,7 +275,6 @@ deleteAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListbook_DeleteAllPages), wxe_util:rec(?wxListbook_DeleteAllPages). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetcurrentpage">external documentation</a>. -doc "Returns the currently selected page or NULL.". -spec getCurrentPage(This) -> wxWindow:wxWindow() when This::wxListbook(). @@ -270,11 +283,13 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListbook_GetCurrentPage), wxe_util:rec(?wxListbook_GetCurrentPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetimagelist">external documentation</a>. -doc """ Returns the associated image list, may be NULL. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec getImageList(This) -> wxImageList:wxImageList() when This::wxListbook(). @@ -283,7 +298,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListbook_GetImageList), wxe_util:rec(?wxListbook_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetpage">external documentation</a>. -doc "Returns the window at the given page position.". -spec getPage(This, Page) -> wxWindow:wxWindow() when This::wxListbook(), Page::integer(). @@ -293,7 +307,6 @@ getPage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxListbook_GetPage), wxe_util:rec(?wxListbook_GetPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetpagecount">external documentation</a>. -doc "Returns the number of pages in the control.". -spec getPageCount(This) -> integer() when This::wxListbook(). @@ -302,7 +315,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListbook_GetPageCount), wxe_util:rec(?wxListbook_GetPageCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetpageimage">external documentation</a>. -doc "Returns the image index for the given page.". -spec getPageImage(This, NPage) -> integer() when This::wxListbook(), NPage::integer(). @@ -312,7 +324,6 @@ getPageImage(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxListbook_GetPageImage), wxe_util:rec(?wxListbook_GetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetpagetext">external documentation</a>. -doc "Returns the string for the given page.". -spec getPageText(This, NPage) -> unicode:charlist() when This::wxListbook(), NPage::integer(). @@ -322,14 +333,12 @@ getPageText(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxListbook_GetPageText), wxe_util:rec(?wxListbook_GetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookgetselection">external documentation</a>. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note that this method may return either the previously or newly selected page -when called from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the -platform and so `wxBookCtrlEvent:getSelection/1` should be used instead in this -case. +Note that this method may return either the previously or newly selected page when called +from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the platform and so `wxBookCtrlEvent:getSelection/1` should be +used instead in this case. """. -spec getSelection(This) -> integer() when This::wxListbook(). @@ -338,15 +347,13 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxListbook_GetSelection), wxe_util:rec(?wxListbook_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookhittest">external documentation</a>. -doc """ -Returns the index of the tab at the specified position or `wxNOT_FOUND` if none. +Returns the index of the tab at the specified position or `wxNOT\_FOUND` if none. -If `flags` parameter is non-NULL, the position of the point inside the tab is -returned as well. +If `flags` parameter is non-NULL, the position of the point inside the tab is returned as well. -Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at -the specified position. +Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at the +specified position. """. -spec hitTest(This, Pt) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -357,7 +364,7 @@ hitTest(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxListbook_HitTest), wxe_util:rec(?wxListbook_HitTest). -%% @equiv insertPage(This,Index,Page,Text, []) +-doc(#{equiv => insertPage(This,Index,Page,Text, [])}). -spec insertPage(This, Index, Page, Text) -> boolean() when This::wxListbook(), Index::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -365,7 +372,6 @@ insertPage(This,Index,Page,Text) when is_record(This, wx_ref),is_integer(Index),is_record(Page, wx_ref),?is_chardata(Text) -> insertPage(This,Index,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookinsertpage">external documentation</a>. -doc """ Inserts a new page at the specified position. @@ -391,13 +397,15 @@ insertPage(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=PageT}=Page,Text, Options wxe_util:queue_cmd(This,Index,Page,Text_UC, Opts,?get_env(),?wxListbook_InsertPage), wxe_util:rec(?wxListbook_InsertPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbooksetimagelist">external documentation</a>. -doc """ Sets the image list to use. It does not take ownership of the image list, you must delete it yourself. -See: `m:wxImageList`, `assignImageList/2` +See: +* `m:wxImageList` + +* `assignImageList/2` """. -spec setImageList(This, ImageList) -> 'ok' when This::wxListbook(), ImageList::wxImageList:wxImageList(). @@ -406,7 +414,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxListbook_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbooksetpagesize">external documentation</a>. -doc """ Sets the width and height of the pages. @@ -419,7 +426,6 @@ setPageSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxListbook), wxe_util:queue_cmd(This,Size,?get_env(),?wxListbook_SetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbooksetpageimage">external documentation</a>. -doc """ Sets the image index for the given page. @@ -433,7 +439,6 @@ setPageImage(#wx_ref{type=ThisT}=This,Page,Image) wxe_util:queue_cmd(This,Page,Image,?get_env(),?wxListbook_SetPageImage), wxe_util:rec(?wxListbook_SetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbooksetpagetext">external documentation</a>. -doc "Sets the text for the given page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxListbook(), Page::integer(), Text::unicode:chardata(). @@ -444,12 +449,11 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:queue_cmd(This,Page,Text_UC,?get_env(),?wxListbook_SetPageText), wxe_util:rec(?wxListbook_SetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbooksetselection">external documentation</a>. -doc """ Sets the selection to the given page, returning the previous selection. -Notice that the call to this function generates the page changing events, use -the `changeSelection/2` function if you don't want these events to be generated. +Notice that the call to this function generates the page changing events, use the `changeSelection/2` +function if you don't want these events to be generated. See: `getSelection/1` """. @@ -461,12 +465,10 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxListbook_SetSelection), wxe_util:rec(?wxListbook_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlistbook.html#wxlistbookchangeselection">external documentation</a>. -doc """ Changes the selection to the given page, returning the previous selection. -This function behaves as `setSelection/2` but does `not` generate the page -changing events. +This function behaves as `setSelection/2` but does `not` generate the page changing events. See overview_events_prog for more information. """. @@ -478,569 +480,383 @@ changeSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxListbook_ChangeSelection), wxe_util:rec(?wxListbook_ChangeSelection). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxListbook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxListbook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBookCtrlBase -%% @hidden -doc false. removePage(This,Page) -> wxBookCtrlBase:removePage(This,Page). -%% @hidden -doc false. deletePage(This,Page) -> wxBookCtrlBase:deletePage(This,Page). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxLocale.erl b/lib/wx/src/gen/wxLocale.erl index fa0c9fa95dc8..b73057d0b4fd 100644 --- a/lib/wx/src/gen/wxLocale.erl +++ b/lib/wx/src/gen/wxLocale.erl @@ -20,25 +20,21 @@ -module(wxLocale). -moduledoc """ -Functions for wxLocale class +`m:wxLocale` class encapsulates all language-dependent settings and is a generalization +of the C locale concept. -`m:wxLocale` class encapsulates all language-dependent settings and is a -generalization of the C locale concept. - -In wxWidgets this class manages current locale. It also initializes and -activates `wxTranslations` (not implemented in wx) object that manages message -catalogs. +In wxWidgets this class manages current locale. It also initializes and activates `wxTranslations` +(not implemented in wx) object that manages message catalogs. For a list of the supported languages, please see ?wxLanguage enum values. These -constants may be used to specify the language in `init/3` and are returned by -`getSystemLanguage/0`. +constants may be used to specify the language in `init/3` and are returned by `getSystemLanguage/0`. See: -[Overview i18n](https://docs.wxwidgets.org/3.1/overview_i18n.html#overview_i18n), -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_internat), -`wxXLocale` (not implemented in wx), `wxTranslations` (not implemented in wx) +* [Overview i18n](https://docs.wxwidgets.org/3.2/overview_i18n.html#overview_i18n) + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_internat) -wxWidgets docs: [wxLocale](https://docs.wxwidgets.org/3.1/classwx_locale.html) +wxWidgets docs: [wxLocale](https://docs.wxwidgets.org/3.2/classwx_locale.html) """. -include("wxe.hrl"). -export([addCatalog/2,addCatalog/3,addCatalog/4,addCatalogLookupPathPrefix/1, @@ -53,25 +49,19 @@ wxWidgets docs: [wxLocale](https://docs.wxwidgets.org/3.1/classwx_locale.html) -type wxLocale() :: wx:wx_object(). -export_type([wxLocale/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalewxlocale">external documentation</a>. -doc """ -This is the default constructor and it does nothing to initialize the object: -`init/3` must be used to do that. +This is the default constructor and it does nothing to initialize the object: `init/3` +must be used to do that. """. -spec new() -> wxLocale(). new() -> wxe_util:queue_cmd(?get_env(), ?wxLocale_new_0), wxe_util:rec(?wxLocale_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalewxlocale">external documentation</a>. -%% <br /> Also:<br /> -%% new(Name) -> wxLocale() when<br /> -%% Name::unicode:chardata().<br /> -%% +-doc "Equivalent to: `new/2`". -spec new(Language) -> wxLocale() when Language::integer(); (Name) -> wxLocale() when @@ -85,23 +75,15 @@ new(Name) when ?is_chardata(Name) -> new(Name, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalewxlocale">external documentation</a>. -%% <br /> Also:<br /> -%% new(Name, [Option]) -> wxLocale() when<br /> -%% Name::unicode:chardata(),<br /> -%% Option :: {'shortName', unicode:chardata()}<br /> -%% | {'locale', unicode:chardata()}<br /> -%% | {'bLoadDefault', boolean()}.<br /> -%% -doc """ See `init/3` for parameters description. -The call of this function has several global side effects which you should -understand: first of all, the application locale is changed - note that this -will affect many of standard C library functions such as printf() or strftime(). -Second, this `m:wxLocale` object becomes the new current global locale for the -application and so all subsequent calls to ?wxGetTranslation() will try to -translate the messages using the message catalogs for this locale. +The call of this function has several global side effects which you should understand: +first of all, the application locale is changed - note that this will affect many of +standard C library functions such as printf() or strftime(). Second, this `m:wxLocale` +object becomes the new current global locale for the application and so all subsequent +calls to ?wxGetTranslation() will try to translate the messages using the message catalogs +for this locale. """. -spec new(Language, [Option]) -> wxLocale() when Language::integer(), @@ -129,7 +111,7 @@ new(Name, Options) wxe_util:queue_cmd(Name_UC, Opts,?get_env(),?wxLocale_new_2_1), wxe_util:rec(?wxLocale_new_2_1). -%% @equiv init(This, []) +-doc(#{equiv => init(This, [])}). -spec init(This) -> boolean() when This::wxLocale(). @@ -137,16 +119,15 @@ init(This) when is_record(This, wx_ref) -> init(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleinit">external documentation</a>. -doc """ Initializes the `m:wxLocale` instance. -The call of this function has several global side effects which you should -understand: first of all, the application locale is changed - note that this -will affect many of standard C library functions such as printf() or strftime(). -Second, this `m:wxLocale` object becomes the new current global locale for the -application and so all subsequent calls to ?wxGetTranslation() will try to -translate the messages using the message catalogs for this locale. +The call of this function has several global side effects which you should understand: +first of all, the application locale is changed - note that this will affect many of +standard C library functions such as printf() or strftime(). Second, this `m:wxLocale` +object becomes the new current global locale for the application and so all subsequent +calls to ?wxGetTranslation() will try to translate the messages using the message catalogs +for this locale. Return: true on success or false if the given locale couldn't be set. """. @@ -164,10 +145,10 @@ init(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxLocale_Init_1), wxe_util:rec(?wxLocale_Init_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleinit">external documentation</a>. -doc """ -Deprecated: This form is deprecated, use the other one unless you know what you -are doing. +Deprecated: + +This form is deprecated, use the other one unless you know what you are doing. """. -spec init(This, Name, [Option]) -> boolean() when This::wxLocale(), Name::unicode:chardata(), @@ -186,7 +167,6 @@ init(#wx_ref{type=ThisT}=This,Name, Options) wxe_util:queue_cmd(This,Name_UC, Opts,?get_env(),?wxLocale_Init_2), wxe_util:rec(?wxLocale_Init_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleaddcatalog">external documentation</a>. -doc "Calls wxTranslations::AddCatalog(const wxString&).". -spec addCatalog(This, Domain) -> boolean() when This::wxLocale(), Domain::unicode:chardata(). @@ -197,12 +177,8 @@ addCatalog(#wx_ref{type=ThisT}=This,Domain) wxe_util:queue_cmd(This,Domain_UC,?get_env(),?wxLocale_AddCatalog_1), wxe_util:rec(?wxLocale_AddCatalog_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleaddcatalog">external documentation</a>. -%%<br /> MsgIdLanguage = integer --doc """ -Calls `wxTranslations::AddCatalog(const wxString&, wxLanguage)` (not implemented -in wx). -""". +-doc "Calls `wxTranslations::AddCatalog(const wxString&, wxLanguage)` (not implemented in wx).". +%% MsgIdLanguage = integer -spec addCatalog(This, Domain, MsgIdLanguage) -> boolean() when This::wxLocale(), Domain::unicode:chardata(), MsgIdLanguage::wx:wx_enum(). addCatalog(#wx_ref{type=ThisT}=This,Domain,MsgIdLanguage) @@ -212,12 +188,11 @@ addCatalog(#wx_ref{type=ThisT}=This,Domain,MsgIdLanguage) wxe_util:queue_cmd(This,Domain_UC,MsgIdLanguage,?get_env(),?wxLocale_AddCatalog_2), wxe_util:rec(?wxLocale_AddCatalog_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleaddcatalog">external documentation</a>. -%%<br /> MsgIdLanguage = integer -doc """ -Calls `wxTranslations::AddCatalog(const wxString&, wxLanguage, const wxString&)` -(not implemented in wx). +Calls `wxTranslations::AddCatalog(const wxString&, wxLanguage, const wxString&)` (not +implemented in wx). """. +%% MsgIdLanguage = integer -spec addCatalog(This, Domain, MsgIdLanguage, MsgIdCharset) -> boolean() when This::wxLocale(), Domain::unicode:chardata(), MsgIdLanguage::wx:wx_enum(), MsgIdCharset::unicode:chardata(). addCatalog(#wx_ref{type=ThisT}=This,Domain,MsgIdLanguage,MsgIdCharset) @@ -228,11 +203,7 @@ addCatalog(#wx_ref{type=ThisT}=This,Domain,MsgIdLanguage,MsgIdCharset) wxe_util:queue_cmd(This,Domain_UC,MsgIdLanguage,MsgIdCharset_UC,?get_env(),?wxLocale_AddCatalog_3), wxe_util:rec(?wxLocale_AddCatalog_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleaddcataloglookuppathprefix">external documentation</a>. --doc """ -Calls `wxFileTranslationsLoader::AddCatalogLookupPathPrefix()` (not implemented -in wx). -""". +-doc "Calls `wxFileTranslationsLoader::AddCatalogLookupPathPrefix()` (not implemented in wx).". -spec addCatalogLookupPathPrefix(Prefix) -> 'ok' when Prefix::unicode:chardata(). addCatalogLookupPathPrefix(Prefix) @@ -240,15 +211,13 @@ addCatalogLookupPathPrefix(Prefix) Prefix_UC = unicode:characters_to_binary(Prefix), wxe_util:queue_cmd(Prefix_UC,?get_env(),?wxLocale_AddCatalogLookupPathPrefix). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetcanonicalname">external documentation</a>. -doc """ Returns the canonical form of current locale name. -Canonical form is the one that is used on UNIX systems: it is a two- or -five-letter string in xx or xx_YY format, where xx is ISO 639 code of language -and YY is ISO 3166 code of the country. Examples are "en", "en_GB", "en_US" or -"fr_FR". This form is internally used when looking up message catalogs. Compare -`getSysName/1`. +Canonical form is the one that is used on UNIX systems: it is a two- or five-letter +string in xx or xx_YY format, where xx is ISO 639 code of language and YY is ISO 3166 code +of the country. Examples are "en", "en_GB", "en_US" or "fr_FR". This form is internally +used when looking up message catalogs. Compare `getSysName/1`. """. -spec getCanonicalName(This) -> unicode:charlist() when This::wxLocale(). @@ -257,12 +226,11 @@ getCanonicalName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_GetCanonicalName), wxe_util:rec(?wxLocale_GetCanonicalName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetlanguage">external documentation</a>. -doc """ Returns the ?wxLanguage constant of current language. -Note that you can call this function only if you used the form of `init/3` that -takes ?wxLanguage argument. +Note that you can call this function only if you used the form of `init/3` that takes ?wxLanguage +argument. """. -spec getLanguage(This) -> integer() when This::wxLocale(). @@ -271,13 +239,10 @@ getLanguage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_GetLanguage), wxe_util:rec(?wxLocale_GetLanguage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetlanguagename">external documentation</a>. -doc """ -Returns English name of the given language or empty string if this language is -unknown. +Returns English name of the given language or empty string if this language is unknown. -See `GetLanguageInfo()` (not implemented in wx) for a remark about special -meaning of `wxLANGUAGE_DEFAULT`. +See `GetLanguageInfo()` (not implemented in wx) for a remark about special meaning of `wxLANGUAGE_DEFAULT`. """. -spec getLanguageName(Lang) -> unicode:charlist() when Lang::integer(). @@ -286,7 +251,6 @@ getLanguageName(Lang) wxe_util:queue_cmd(Lang,?get_env(),?wxLocale_GetLanguageName), wxe_util:rec(?wxLocale_GetLanguageName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetlocale">external documentation</a>. -doc """ Returns the locale name as passed to the constructor or `init/3`. @@ -299,10 +263,9 @@ getLocale(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_GetLocale), wxe_util:rec(?wxLocale_GetLocale). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetname">external documentation</a>. -doc """ -Returns the current short name for the locale (as given to the constructor or -the `init/3` function). +Returns the current short name for the locale (as given to the constructor or the `init/3` +function). """. -spec getName(This) -> unicode:charlist() when This::wxLocale(). @@ -311,7 +274,7 @@ getName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_GetName), wxe_util:rec(?wxLocale_GetName). -%% @equiv getString(This,OrigString, []) +-doc(#{equiv => getString(This,OrigString, [])}). -spec getString(This, OrigString) -> unicode:charlist() when This::wxLocale(), OrigString::unicode:chardata(). @@ -319,7 +282,6 @@ getString(This,OrigString) when is_record(This, wx_ref),?is_chardata(OrigString) -> getString(This,OrigString, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetstring">external documentation</a>. -doc "Calls wxGetTranslation(const wxString&, const wxString&).". -spec getString(This, OrigString, [Option]) -> unicode:charlist() when This::wxLocale(), OrigString::unicode:chardata(), @@ -334,7 +296,7 @@ getString(#wx_ref{type=ThisT}=This,OrigString, Options) wxe_util:queue_cmd(This,OrigString_UC, Opts,?get_env(),?wxLocale_GetString_2), wxe_util:rec(?wxLocale_GetString_2). -%% @equiv getString(This,OrigString,OrigString2,N, []) +-doc(#{equiv => getString(This,OrigString,OrigString2,N, [])}). -spec getString(This, OrigString, OrigString2, N) -> unicode:charlist() when This::wxLocale(), OrigString::unicode:chardata(), OrigString2::unicode:chardata(), N::integer(). @@ -342,11 +304,7 @@ getString(This,OrigString,OrigString2,N) when is_record(This, wx_ref),?is_chardata(OrigString),?is_chardata(OrigString2),is_integer(N) -> getString(This,OrigString,OrigString2,N, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetstring">external documentation</a>. --doc """ -Calls wxGetTranslation(const wxString&, const wxString&, unsigned, const -wxString&). -""". +-doc "Calls wxGetTranslation(const wxString&, const wxString&, unsigned, const wxString&).". -spec getString(This, OrigString, OrigString2, N, [Option]) -> unicode:charlist() when This::wxLocale(), OrigString::unicode:chardata(), OrigString2::unicode:chardata(), N::integer(), Option :: {'szDomain', unicode:chardata()}. @@ -361,7 +319,7 @@ getString(#wx_ref{type=ThisT}=This,OrigString,OrigString2,N, Options) wxe_util:queue_cmd(This,OrigString_UC,OrigString2_UC,N, Opts,?get_env(),?wxLocale_GetString_4), wxe_util:rec(?wxLocale_GetString_4). -%% @equiv getHeaderValue(This,Header, []) +-doc(#{equiv => getHeaderValue(This,Header, [])}). -spec getHeaderValue(This, Header) -> unicode:charlist() when This::wxLocale(), Header::unicode:chardata(). @@ -369,7 +327,6 @@ getHeaderValue(This,Header) when is_record(This, wx_ref),?is_chardata(Header) -> getHeaderValue(This,Header, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetheadervalue">external documentation</a>. -doc "Calls `wxTranslations::GetHeaderValue()` (not implemented in wx).". -spec getHeaderValue(This, Header, [Option]) -> unicode:charlist() when This::wxLocale(), Header::unicode:chardata(), @@ -384,7 +341,6 @@ getHeaderValue(#wx_ref{type=ThisT}=This,Header, Options) wxe_util:queue_cmd(This,Header_UC, Opts,?get_env(),?wxLocale_GetHeaderValue), wxe_util:rec(?wxLocale_GetHeaderValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetsysname">external documentation</a>. -doc """ Returns current platform-specific locale name as passed to setlocale(). @@ -397,53 +353,44 @@ getSysName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_GetSysName), wxe_util:rec(?wxLocale_GetSysName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetsystemencoding">external documentation</a>. -%%<br /> Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc """ Tries to detect the user's default font encoding. -Returns ?wxFontEncoding() value or `wxFONTENCODING_SYSTEM` if it couldn't be -determined. +Returns ?wxFontEncoding() value or `wxFONTENCODING_SYSTEM` if it couldn't be determined. """. +%% Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec getSystemEncoding() -> wx:wx_enum(). getSystemEncoding() -> wxe_util:queue_cmd(?get_env(), ?wxLocale_GetSystemEncoding), wxe_util:rec(?wxLocale_GetSystemEncoding). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetsystemencodingname">external documentation</a>. -doc """ Tries to detect the name of the user's default font encoding. This string isn't particularly useful for the application as its form is platform-dependent and so you should probably use `getSystemEncoding/0` instead. -Returns a user-readable string value or an empty string if it couldn't be -determined. +Returns a user-readable string value or an empty string if it couldn't be determined. """. -spec getSystemEncodingName() -> unicode:charlist(). getSystemEncodingName() -> wxe_util:queue_cmd(?get_env(), ?wxLocale_GetSystemEncodingName), wxe_util:rec(?wxLocale_GetSystemEncodingName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocalegetsystemlanguage">external documentation</a>. -doc """ Tries to detect the user's default locale setting. -Returns the ?wxLanguage value or `wxLANGUAGE_UNKNOWN` if the language-guessing -algorithm failed. +Returns the ?wxLanguage value or `wxLANGUAGE_UNKNOWN` if the language-guessing algorithm failed. -Note: This function works with `locales` and returns the user's default locale. -This may be, and usually is, the same as their preferred UI language, but it's -not the same thing. Use wxTranslation to obtain `language` information. - -See: `wxTranslations::GetBestTranslation()` (not implemented in wx) +Note: This function works with `locales` and returns the user's default locale. This may +be, and usually is, the same as their preferred UI language, but it's not the same thing. +Use wxTranslation to obtain `language` information. """. -spec getSystemLanguage() -> integer(). getSystemLanguage() -> wxe_util:queue_cmd(?get_env(), ?wxLocale_GetSystemLanguage), wxe_util:rec(?wxLocale_GetSystemLanguage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleisloaded">external documentation</a>. -doc "Calls `wxTranslations::IsLoaded()` (not implemented in wx).". -spec isLoaded(This, Domain) -> boolean() when This::wxLocale(), Domain::unicode:chardata(). @@ -454,7 +401,6 @@ isLoaded(#wx_ref{type=ThisT}=This,Domain) wxe_util:queue_cmd(This,Domain_UC,?get_env(),?wxLocale_IsLoaded), wxe_util:rec(?wxLocale_IsLoaded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlocale.html#wxlocaleisok">external documentation</a>. -doc "Returns true if the locale could be set successfully.". -spec isOk(This) -> boolean() when This::wxLocale(). @@ -463,12 +409,7 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxLocale_IsOk), wxe_util:rec(?wxLocale_IsOk). -%% @doc Destroys this object, do not use object again --doc """ -The destructor, like the constructor, also has global side effects: the -previously set locale is restored and so the changes described in `init/3` -documentation are rolled back. -""". +-doc "Destroys the object". -spec destroy(This::wxLocale()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxLocale), diff --git a/lib/wx/src/gen/wxLogNull.erl b/lib/wx/src/gen/wxLogNull.erl index 8f46c820bea1..a0ffcabae548 100644 --- a/lib/wx/src/gen/wxLogNull.erl +++ b/lib/wx/src/gen/wxLogNull.erl @@ -20,22 +20,20 @@ -module(wxLogNull). -moduledoc """ -Functions for wxLogNull class +This class allows you to temporarily suspend logging. -This class allows you to temporarily suspend logging. All calls to the log -functions during the life time of an object of this class are just ignored. +All calls to the log functions during the life time of an object of this class are just ignored. -In particular, it can be used to suppress the log messages given by wxWidgets -itself but it should be noted that it is rarely the best way to cope with this -problem as `all` log messages are suppressed, even if they indicate a completely -different error than the one the programmer wanted to suppress. +In particular, it can be used to suppress the log messages given by wxWidgets itself but +it should be noted that it is rarely the best way to cope with this problem as `all` log +messages are suppressed, even if they indicate a completely different error than the one +the programmer wanted to suppress. For instance, the example of the overview: would be better written as: -wxWidgets docs: -[wxLogNull](https://docs.wxwidgets.org/3.1/classwx_log_null.html) +wxWidgets docs: [wxLogNull](https://docs.wxwidgets.org/3.2/classwx_log_null.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -45,19 +43,16 @@ wxWidgets docs: -type wxLogNull() :: wx:wx_object(). -export_type([wxLogNull/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxlognull.html#wxlognullwxlognull">external documentation</a>. -doc "Suspends logging.". -spec new() -> wxLogNull(). new() -> wxe_util:queue_cmd(?get_env(), ?wxLogNull_new), wxe_util:rec(?wxLogNull_new). -%% @doc Destroys this object, do not use object again --doc "Resumes logging.". +-doc "Destroys the object". -spec destroy(This::wxLogNull()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxLogNull), diff --git a/lib/wx/src/gen/wxMDIChildFrame.erl b/lib/wx/src/gen/wxMDIChildFrame.erl index 34c4ab3e3c40..91ba20f48852 100644 --- a/lib/wx/src/gen/wxMDIChildFrame.erl +++ b/lib/wx/src/gen/wxMDIChildFrame.erl @@ -20,35 +20,42 @@ -module(wxMDIChildFrame). -moduledoc """ -Functions for wxMDIChildFrame class +An MDI child frame is a frame that can only exist inside a `m:wxMDIClientWindow`, which +is itself a child of `m:wxMDIParentFrame`. -An MDI child frame is a frame that can only exist inside a -`m:wxMDIClientWindow`, which is itself a child of `m:wxMDIParentFrame`. - -Styles +## Styles This class supports the following styles: -All of the standard `m:wxFrame` styles can be used but most of them are ignored -by TDI-based MDI implementations. +All of the standard `m:wxFrame` styles can be used but most of them are ignored by +TDI-based MDI implementations. + +Remark: Although internally an MDI child frame is a child of the MDI client window, in +wxWidgets you create it as a child of `m:wxMDIParentFrame`. In fact, you can usually +forget that the client window exists. MDI child frames are clipped to the area of the MDI +client window, and may be iconized on the client window. You can associate a menubar with +a child frame as usual, although an MDI child doesn't display its menubar under its own +title bar. The MDI parent frame's menubar will be changed to reflect the currently active +child frame. If there are currently no children, the parent frame's own menubar will be displayed. + +See: +* `m:wxMDIClientWindow` + +* `m:wxMDIParentFrame` + +* `m:wxFrame` + +This class is derived, and can use functions, from: + +* `m:wxFrame` -Remark: Although internally an MDI child frame is a child of the MDI client -window, in wxWidgets you create it as a child of `m:wxMDIParentFrame`. In fact, -you can usually forget that the client window exists. MDI child frames are -clipped to the area of the MDI client window, and may be iconized on the client -window. You can associate a menubar with a child frame as usual, although an MDI -child doesn't display its menubar under its own title bar. The MDI parent -frame's menubar will be changed to reflect the currently active child frame. If -there are currently no children, the parent frame's own menubar will be -displayed. +* `m:wxTopLevelWindow` -See: `m:wxMDIClientWindow`, `m:wxMDIParentFrame`, `m:wxFrame` +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxFrame` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxMDIChildFrame](https://docs.wxwidgets.org/3.1/classwx_m_d_i_child_frame.html) +wxWidgets docs: [wxMDIChildFrame](https://docs.wxwidgets.org/3.2/classwx_m_d_i_child_frame.html) """. -include("wxe.hrl"). -export([activate/1,create/4,create/5,destroy/1,maximize/1,maximize/2,new/0,new/3, @@ -104,7 +111,6 @@ wxWidgets docs: -type wxMDIChildFrame() :: wx:wx_object(). -export_type([wxMDIChildFrame/0]). -%% @hidden -doc false. parent_class(wxFrame) -> true; parent_class(wxTopLevelWindow) -> true; @@ -112,14 +118,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframewxmdichildframe">external documentation</a>. -doc "Default constructor.". -spec new() -> wxMDIChildFrame(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMDIChildFrame_new_0), wxe_util:rec(?wxMDIChildFrame_new_0). -%% @equiv new(Parent,Id,Title, []) +-doc(#{equiv => new(Parent,Id,Title, [])}). -spec new(Parent, Id, Title) -> wxMDIChildFrame() when Parent::wxMDIParentFrame:wxMDIParentFrame(), Id::integer(), Title::unicode:chardata(). @@ -127,7 +132,6 @@ new(Parent,Id,Title) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> new(Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframewxmdichildframe">external documentation</a>. -doc """ Constructor, creating the window. @@ -150,11 +154,13 @@ new(#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(Parent,Id,Title_UC, Opts,?get_env(),?wxMDIChildFrame_new_4), wxe_util:rec(?wxMDIChildFrame_new_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframeactivate">external documentation</a>. -doc """ Activates this MDI child frame. -See: `maximize/2`, `restore/1` +See: +* `maximize/2` + +* `restore/1` """. -spec activate(This) -> 'ok' when This::wxMDIChildFrame(). @@ -162,7 +168,7 @@ activate(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIChildFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIChildFrame_Activate). -%% @equiv create(This,Parent,Id,Title, []) +-doc(#{equiv => create(This,Parent,Id,Title, [])}). -spec create(This, Parent, Id, Title) -> boolean() when This::wxMDIChildFrame(), Parent::wxMDIParentFrame:wxMDIParentFrame(), Id::integer(), Title::unicode:chardata(). @@ -170,7 +176,6 @@ create(This,Parent,Id,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> create(This,Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframecreate">external documentation</a>. -doc """ Used in two-step frame construction. @@ -194,7 +199,7 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(This,Parent,Id,Title_UC, Opts,?get_env(),?wxMDIChildFrame_Create), wxe_util:rec(?wxMDIChildFrame_Create). -%% @equiv maximize(This, []) +-doc(#{equiv => maximize(This, [])}). -spec maximize(This) -> 'ok' when This::wxMDIChildFrame(). @@ -202,14 +207,16 @@ maximize(This) when is_record(This, wx_ref) -> maximize(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframemaximize">external documentation</a>. -doc """ Maximizes this MDI child frame. -This function doesn't do anything if `IsAlwaysMaximized()` (not implemented in -wx) returns true. +This function doesn't do anything if `IsAlwaysMaximized()` (not implemented in wx) +returns true. + +See: +* `activate/1` -See: `activate/1`, `restore/1` +* `restore/1` """. -spec maximize(This, [Option]) -> 'ok' when This::wxMDIChildFrame(), @@ -222,14 +229,16 @@ maximize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxMDIChildFrame_Maximize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdichildframe.html#wxmdichildframerestore">external documentation</a>. -doc """ Restores this MDI child frame (unmaximizes). -This function doesn't do anything if `IsAlwaysMaximized()` (not implemented in -wx) returns true. +This function doesn't do anything if `IsAlwaysMaximized()` (not implemented in wx) +returns true. + +See: +* `activate/1` -See: `activate/1`, `maximize/2` +* `maximize/2` """. -spec restore(This) -> 'ok' when This::wxMDIChildFrame(). @@ -237,687 +246,459 @@ restore(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIChildFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIChildFrame_Restore). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Destroys all child windows and menu bar if present. -""". +-doc "Destroys the object". -spec destroy(This::wxMDIChildFrame()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMDIChildFrame), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFrame -%% @hidden -doc false. setToolBar(This,ToolBar) -> wxFrame:setToolBar(This,ToolBar). -%% @hidden -doc false. setStatusWidths(This,Widths_field) -> wxFrame:setStatusWidths(This,Widths_field). -%% @hidden -doc false. setStatusText(This,Text, Options) -> wxFrame:setStatusText(This,Text, Options). -%% @hidden -doc false. setStatusText(This,Text) -> wxFrame:setStatusText(This,Text). -%% @hidden -doc false. setStatusBarPane(This,N) -> wxFrame:setStatusBarPane(This,N). -%% @hidden -doc false. setStatusBar(This,StatusBar) -> wxFrame:setStatusBar(This,StatusBar). -%% @hidden -doc false. setMenuBar(This,MenuBar) -> wxFrame:setMenuBar(This,MenuBar). -%% @hidden -doc false. sendSizeEvent(This, Options) -> wxFrame:sendSizeEvent(This, Options). -%% @hidden -doc false. sendSizeEvent(This) -> wxFrame:sendSizeEvent(This). -%% @hidden -doc false. processCommand(This,Id) -> wxFrame:processCommand(This,Id). -%% @hidden -doc false. getToolBar(This) -> wxFrame:getToolBar(This). -%% @hidden -doc false. getStatusBarPane(This) -> wxFrame:getStatusBarPane(This). -%% @hidden -doc false. getStatusBar(This) -> wxFrame:getStatusBar(This). -%% @hidden -doc false. getMenuBar(This) -> wxFrame:getMenuBar(This). -%% @hidden -doc false. getClientAreaOrigin(This) -> wxFrame:getClientAreaOrigin(This). -%% @hidden -doc false. createToolBar(This, Options) -> wxFrame:createToolBar(This, Options). -%% @hidden -doc false. createToolBar(This) -> wxFrame:createToolBar(This). -%% @hidden -doc false. createStatusBar(This, Options) -> wxFrame:createStatusBar(This, Options). -%% @hidden -doc false. createStatusBar(This) -> wxFrame:createStatusBar(This). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMDIClientWindow.erl b/lib/wx/src/gen/wxMDIClientWindow.erl index bc0d579e3013..4c9c53ce3138 100644 --- a/lib/wx/src/gen/wxMDIClientWindow.erl +++ b/lib/wx/src/gen/wxMDIClientWindow.erl @@ -20,33 +20,36 @@ -module(wxMDIClientWindow). -moduledoc """ -Functions for wxMDIClientWindow class +An MDI client window is a child of `m:wxMDIParentFrame`, and manages zero or more `m:wxMDIChildFrame` +objects. -An MDI client window is a child of `m:wxMDIParentFrame`, and manages zero or -more `m:wxMDIChildFrame` objects. +The client window is the area where MDI child windows exist. It doesn't have to cover +the whole parent frame; other windows such as toolbars and a help window might coexist +with it. There can be scrollbars on a client window, which are controlled by the parent +window style. -The client window is the area where MDI child windows exist. It doesn't have to -cover the whole parent frame; other windows such as toolbars and a help window -might coexist with it. There can be scrollbars on a client window, which are -controlled by the parent window style. +The `m:wxMDIClientWindow` class is usually adequate without further derivation, and it is +created automatically when the MDI parent frame is created. If the application needs to +derive a new class, the function `wxMDIParentFrame::OnCreateClient()` (not implemented in +wx) must be overridden in order to give an opportunity to use a different class of client window. -The `m:wxMDIClientWindow` class is usually adequate without further derivation, -and it is created automatically when the MDI parent frame is created. If the -application needs to derive a new class, the function -`wxMDIParentFrame::OnCreateClient()` (not implemented in wx) must be overridden -in order to give an opportunity to use a different class of client window. +Under wxMSW, the client window will automatically have a sunken border style when the +active child is not maximized, and no border style when a child is maximized. -Under wxMSW, the client window will automatically have a sunken border style -when the active child is not maximized, and no border style when a child is -maximized. +See: +* `m:wxMDIChildFrame` -See: `m:wxMDIChildFrame`, `m:wxMDIParentFrame`, `m:wxFrame` +* `m:wxMDIParentFrame` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* `m:wxFrame` -wxWidgets docs: -[wxMDIClientWindow](https://docs.wxwidgets.org/3.1/classwx_m_d_i_client_window.html) +This class is derived, and can use functions, from: + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxMDIClientWindow](https://docs.wxwidgets.org/3.2/classwx_m_d_i_client_window.html) """. -include("wxe.hrl"). -export([createClient/2,createClient/3,destroy/1,new/0]). @@ -93,25 +96,23 @@ wxWidgets docs: -type wxMDIClientWindow() :: wx:wx_object(). -export_type([wxMDIClientWindow/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiclientwindow.html#wxmdiclientwindowwxmdiclientwindow">external documentation</a>. -doc """ Default constructor. -Objects of this class are only created by `m:wxMDIParentFrame` which uses the -default constructor and calls `createClient/3` immediately afterwards. +Objects of this class are only created by `m:wxMDIParentFrame` which uses the default +constructor and calls `createClient/3` immediately afterwards. """. -spec new() -> wxMDIClientWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMDIClientWindow_new), wxe_util:rec(?wxMDIClientWindow_new). -%% @equiv createClient(This,Parent, []) +-doc(#{equiv => createClient(This,Parent, [])}). -spec createClient(This, Parent) -> boolean() when This::wxMDIClientWindow(), Parent::wxMDIParentFrame:wxMDIParentFrame(). @@ -119,12 +120,11 @@ createClient(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> createClient(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiclientwindow.html#wxmdiclientwindowcreateclient">external documentation</a>. -doc """ Called by `m:wxMDIParentFrame` immediately after creating the client window. -This function may be overridden in the derived class but the base class version -must usually be called first to really create the window. +This function may be overridden in the derived class but the base class version must +usually be called first to really create the window. """. -spec createClient(This, Parent, [Option]) -> boolean() when This::wxMDIClientWindow(), Parent::wxMDIParentFrame:wxMDIParentFrame(), @@ -139,561 +139,377 @@ createClient(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxMDIClientWindow_CreateClient), wxe_util:rec(?wxMDIClientWindow_CreateClient). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxMDIClientWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMDIClientWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMDIParentFrame.erl b/lib/wx/src/gen/wxMDIParentFrame.erl index 7698c95c7efb..c4e74802f83f 100644 --- a/lib/wx/src/gen/wxMDIParentFrame.erl +++ b/lib/wx/src/gen/wxMDIParentFrame.erl @@ -20,51 +20,60 @@ -module(wxMDIParentFrame). -moduledoc """ -Functions for wxMDIParentFrame class +An MDI (Multiple Document Interface) parent frame is a window which can contain MDI child +frames in its client area which emulates the full desktop. -An MDI (Multiple Document Interface) parent frame is a window which can contain -MDI child frames in its client area which emulates the full desktop. +MDI is a user-interface model in which all the window reside inside the single parent +window as opposed to being separate from each other. It remains popular despite dire +warnings from Microsoft itself (which popularized this model in the first model) that MDI +is obsolete. -MDI is a user-interface model in which all the window reside inside the single -parent window as opposed to being separate from each other. It remains popular -despite dire warnings from Microsoft itself (which popularized this model in the -first model) that MDI is obsolete. +An MDI parent frame always has a `m:wxMDIClientWindow` associated with it, which is the +parent for MDI child frames. In the simplest case, the client window takes up the entire +parent frame area but it is also possible to resize it to be smaller in order to have +other windows in the frame, a typical example is using a sidebar along one of the window edges. -An MDI parent frame always has a `m:wxMDIClientWindow` associated with it, which -is the parent for MDI child frames. In the simplest case, the client window -takes up the entire parent frame area but it is also possible to resize it to be -smaller in order to have other windows in the frame, a typical example is using -a sidebar along one of the window edges. +The appearance of MDI applications differs between different ports. The classic MDI +model, with child windows which can be independently moved, resized etc, is only available +under MSW, which provides native support for it. In Mac ports, multiple top level windows +are used for the MDI children too and the MDI parent frame itself is invisible, to +accommodate the native look and feel requirements. In all the other ports, a tab-based MDI +implementation (sometimes called TDI) is used and so at most one MDI child is visible at +any moment (child frames are always maximized). -The appearance of MDI applications differs between different ports. The classic -MDI model, with child windows which can be independently moved, resized etc, is -only available under MSW, which provides native support for it. In Mac ports, -multiple top level windows are used for the MDI children too and the MDI parent -frame itself is invisible, to accommodate the native look and feel requirements. -In all the other ports, a tab-based MDI implementation (sometimes called TDI) is -used and so at most one MDI child is visible at any moment (child frames are -always maximized). +Although it is possible to have multiple MDI parent frames, a typical MDI application +has a single MDI parent frame window inside which multiple MDI child frames, i.e. objects +of class `m:wxMDIChildFrame`, can be created. -Although it is possible to have multiple MDI parent frames, a typical MDI -application has a single MDI parent frame window inside which multiple MDI child -frames, i.e. objects of class `m:wxMDIChildFrame`, can be created. - -Styles +## Styles This class supports the following styles: -There are no special styles for this class, all `m:wxFrame` styles apply to it -in the usual way. The only exception is that wxHSCROLL and wxVSCROLL styles -apply not to the frame itself but to the client window, so that using them -enables horizontal and vertical scrollbars for this window and not the frame. +There are no special styles for this class, all `m:wxFrame` styles apply to it in the +usual way. The only exception is that wxHSCROLL and wxVSCROLL styles apply not to the +frame itself but to the client window, so that using them enables horizontal and vertical +scrollbars for this window and not the frame. + +See: +* `m:wxMDIChildFrame` + +* `m:wxMDIClientWindow` + +* `m:wxFrame` + +* `m:wxDialog` + +This class is derived, and can use functions, from: + +* `m:wxFrame` + +* `m:wxTopLevelWindow` -See: `m:wxMDIChildFrame`, `m:wxMDIClientWindow`, `m:wxFrame`, `m:wxDialog` +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxFrame` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxMDIParentFrame](https://docs.wxwidgets.org/3.1/classwx_m_d_i_parent_frame.html) +wxWidgets docs: [wxMDIParentFrame](https://docs.wxwidgets.org/3.2/classwx_m_d_i_parent_frame.html) """. -include("wxe.hrl"). -export([activateNext/1,activatePrevious/1,arrangeIcons/1,cascade/1,create/4, @@ -121,7 +130,6 @@ wxWidgets docs: -type wxMDIParentFrame() :: wx:wx_object(). -export_type([wxMDIParentFrame/0]). -%% @hidden -doc false. parent_class(wxFrame) -> true; parent_class(wxTopLevelWindow) -> true; @@ -129,7 +137,6 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframewxmdiparentframe">external documentation</a>. -doc """ Default constructor. @@ -140,7 +147,7 @@ new() -> wxe_util:queue_cmd(?get_env(), ?wxMDIParentFrame_new_0), wxe_util:rec(?wxMDIParentFrame_new_0). -%% @equiv new(Parent,Id,Title, []) +-doc(#{equiv => new(Parent,Id,Title, [])}). -spec new(Parent, Id, Title) -> wxMDIParentFrame() when Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -148,20 +155,18 @@ new(Parent,Id,Title) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> new(Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframewxmdiparentframe">external documentation</a>. -doc """ Constructor, creating the window. -Notice that if you override virtual `OnCreateClient()` (not implemented in wx) -method you shouldn't be using this constructor but the default constructor and -`create/5` as otherwise your overridden method is never going to be called -because of the usual C++ virtual call resolution rules. +Notice that if you override virtual `OnCreateClient()` (not implemented in wx) method you +shouldn't be using this constructor but the default constructor and `create/5` as otherwise your +overridden method is never going to be called because of the usual C++ virtual call +resolution rules. -Under wxMSW, the client window will automatically have a sunken border style -when the active child is not maximized, and no border style when a child is -maximized. +Under wxMSW, the client window will automatically have a sunken border style when the +active child is not maximized, and no border style when a child is maximized. -See: `create/5`, `OnCreateClient()` (not implemented in wx) +See: `create/5` """. -spec new(Parent, Id, Title, [Option]) -> wxMDIParentFrame() when Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(), @@ -180,13 +185,12 @@ new(#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(Parent,Id,Title_UC, Opts,?get_env(),?wxMDIParentFrame_new_4), wxe_util:rec(?wxMDIParentFrame_new_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframeactivatenext">external documentation</a>. -doc """ Activates the MDI child following the currently active one. -The MDI children are maintained in an ordered list and this function switches to -the next element in this list, wrapping around the end of it if the currently -active child is the last one. +The MDI children are maintained in an ordered list and this function switches to the next +element in this list, wrapping around the end of it if the currently active child is the +last one. See: `activatePrevious/1` """. @@ -196,7 +200,6 @@ activateNext(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIParentFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_ActivateNext). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframeactivateprevious">external documentation</a>. -doc """ Activates the MDI child preceding the currently active one. @@ -208,14 +211,16 @@ activatePrevious(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIParentFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_ActivatePrevious). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframearrangeicons">external documentation</a>. -doc """ Arranges any iconized (minimized) MDI child windows. -This method is only implemented in MSW MDI implementation and does nothing under -the other platforms. +This method is only implemented in MSW MDI implementation and does nothing under the +other platforms. -See: `cascade/1`, `tile/2` +See: +* `cascade/1` + +* `tile/2` """. -spec arrangeIcons(This) -> 'ok' when This::wxMDIParentFrame(). @@ -223,14 +228,16 @@ arrangeIcons(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIParentFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_ArrangeIcons). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframecascade">external documentation</a>. -doc """ Arranges the MDI child windows in a cascade. -This method is only implemented in MSW MDI implementation and does nothing under -the other platforms. +This method is only implemented in MSW MDI implementation and does nothing under the +other platforms. + +See: +* `tile/2` -See: `tile/2`, `arrangeIcons/1` +* `arrangeIcons/1` """. -spec cascade(This) -> 'ok' when This::wxMDIParentFrame(). @@ -238,7 +245,7 @@ cascade(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMDIParentFrame), wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_Cascade). -%% @equiv create(This,Parent,Id,Title, []) +-doc(#{equiv => create(This,Parent,Id,Title, [])}). -spec create(This, Parent, Id, Title) -> boolean() when This::wxMDIParentFrame(), Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -246,7 +253,6 @@ create(This,Parent,Id,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> create(This,Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframecreate">external documentation</a>. -doc """ Used in two-step frame construction. @@ -270,7 +276,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(This,Parent,Id,Title_UC, Opts,?get_env(),?wxMDIParentFrame_Create), wxe_util:rec(?wxMDIParentFrame_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframegetactivechild">external documentation</a>. -doc """ Returns a pointer to the active MDI child, if there is one. @@ -283,12 +288,7 @@ getActiveChild(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_GetActiveChild), wxe_util:rec(?wxMDIParentFrame_GetActiveChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframegetclientwindow">external documentation</a>. --doc """ -Returns a pointer to the client window. - -See: `OnCreateClient()` (not implemented in wx) -""". +-doc "Returns a pointer to the client window.". -spec getClientWindow(This) -> wxMDIClientWindow:wxMDIClientWindow() when This::wxMDIParentFrame(). getClientWindow(#wx_ref{type=ThisT}=This) -> @@ -296,7 +296,7 @@ getClientWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMDIParentFrame_GetClientWindow), wxe_util:rec(?wxMDIParentFrame_GetClientWindow). -%% @equiv tile(This, []) +-doc(#{equiv => tile(This, [])}). -spec tile(This) -> 'ok' when This::wxMDIParentFrame(). @@ -304,15 +304,14 @@ tile(This) when is_record(This, wx_ref) -> tile(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmdiparentframe.html#wxmdiparentframetile">external documentation</a>. -%%<br /> Orient = ?wxHORIZONTAL | ?wxVERTICAL | ?wxBOTH | ?wxORIENTATION_MASK -doc """ -Tiles the MDI child windows either horizontally or vertically depending on -whether `orient` is `wxHORIZONTAL` or `wxVERTICAL`. +Tiles the MDI child windows either horizontally or vertically depending on whether `orient` +is `wxHORIZONTAL` or `wxVERTICAL`. -This method is only implemented in MSW MDI implementation and does nothing under -the other platforms. +This method is only implemented in MSW MDI implementation and does nothing under the +other platforms. """. +%% Orient = ?wxHORIZONTAL | ?wxVERTICAL | ?wxBOTH | ?wxORIENTATION_MASK -spec tile(This, [Option]) -> 'ok' when This::wxMDIParentFrame(), Option :: {'orient', wx:wx_enum()}. @@ -324,693 +323,463 @@ tile(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxMDIParentFrame_Tile). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Destroys all child windows and menu bar if present. -""". +-doc "Destroys the object". -spec destroy(This::wxMDIParentFrame()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMDIParentFrame), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFrame -%% @hidden -doc false. setToolBar(This,ToolBar) -> wxFrame:setToolBar(This,ToolBar). -%% @hidden -doc false. setStatusWidths(This,Widths_field) -> wxFrame:setStatusWidths(This,Widths_field). -%% @hidden -doc false. setStatusText(This,Text, Options) -> wxFrame:setStatusText(This,Text, Options). -%% @hidden -doc false. setStatusText(This,Text) -> wxFrame:setStatusText(This,Text). -%% @hidden -doc false. setStatusBarPane(This,N) -> wxFrame:setStatusBarPane(This,N). -%% @hidden -doc false. setStatusBar(This,StatusBar) -> wxFrame:setStatusBar(This,StatusBar). -%% @hidden -doc false. setMenuBar(This,MenuBar) -> wxFrame:setMenuBar(This,MenuBar). -%% @hidden -doc false. sendSizeEvent(This, Options) -> wxFrame:sendSizeEvent(This, Options). -%% @hidden -doc false. sendSizeEvent(This) -> wxFrame:sendSizeEvent(This). -%% @hidden -doc false. processCommand(This,Id) -> wxFrame:processCommand(This,Id). -%% @hidden -doc false. getToolBar(This) -> wxFrame:getToolBar(This). -%% @hidden -doc false. getStatusBarPane(This) -> wxFrame:getStatusBarPane(This). -%% @hidden -doc false. getStatusBar(This) -> wxFrame:getStatusBar(This). -%% @hidden -doc false. getMenuBar(This) -> wxFrame:getMenuBar(This). -%% @hidden -doc false. getClientAreaOrigin(This) -> wxFrame:getClientAreaOrigin(This). -%% @hidden -doc false. createToolBar(This, Options) -> wxFrame:createToolBar(This, Options). -%% @hidden -doc false. createToolBar(This) -> wxFrame:createToolBar(This). -%% @hidden -doc false. createStatusBar(This, Options) -> wxFrame:createStatusBar(This, Options). -%% @hidden -doc false. createStatusBar(This) -> wxFrame:createStatusBar(This). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMask.erl b/lib/wx/src/gen/wxMask.erl index f11d7c106df8..bfdd57db6f59 100644 --- a/lib/wx/src/gen/wxMask.erl +++ b/lib/wx/src/gen/wxMask.erl @@ -20,21 +20,24 @@ -module(wxMask). -moduledoc """ -Functions for wxMask class +This class encapsulates a monochrome mask bitmap, where the masked area is black and the +unmasked area is white. -This class encapsulates a monochrome mask bitmap, where the masked area is black -and the unmasked area is white. +When associated with a bitmap and drawn in a device context, the unmasked area of the +bitmap will be drawn, and the masked area will not be drawn. -When associated with a bitmap and drawn in a device context, the unmasked area -of the bitmap will be drawn, and the masked area will not be drawn. +Note: A mask can be associated also with a bitmap with an alpha channel but drawing such +bitmaps under wxMSW may be slow so using them should be avoided if drawing performance is +an important factor. -Note: A mask can be associated also with a bitmap with an alpha channel but -drawing such bitmaps under wxMSW may be slow so using them should be avoided if -drawing performance is an important factor. +See: +* `m:wxBitmap` -See: `m:wxBitmap`, `wxDC:blit/6`, `m:wxMemoryDC` +* `wxDC:blit/6` -wxWidgets docs: [wxMask](https://docs.wxwidgets.org/3.1/classwx_mask.html) +* `m:wxMemoryDC` + +wxWidgets docs: [wxMask](https://docs.wxwidgets.org/3.2/classwx_mask.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,new/0,new/1,new/2]). @@ -44,18 +47,15 @@ wxWidgets docs: [wxMask](https://docs.wxwidgets.org/3.1/classwx_mask.html) -type wxMask() :: wx:wx_object(). -export_type([wxMask/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmask.html#wxmaskwxmask">external documentation</a>. -doc "Default constructor.". -spec new() -> wxMask(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMask_new_0), wxe_util:rec(?wxMask_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmask.html#wxmaskwxmask">external documentation</a>. -doc "Constructs a mask from a monochrome bitmap.". -spec new(Bitmap) -> wxMask() when Bitmap::wxBitmap:wxBitmap(). @@ -64,11 +64,6 @@ new(#wx_ref{type=BitmapT}=Bitmap) -> wxe_util:queue_cmd(Bitmap,?get_env(),?wxMask_new_1), wxe_util:rec(?wxMask_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmask.html#wxmaskwxmask">external documentation</a>. -%% <br /> Also:<br /> -%% new(Bitmap, Colour) -> wxMask() when<br /> -%% Bitmap::wxBitmap:wxBitmap(), Colour::wx:wx_colour().<br /> -%% -doc "Constructs a mask from a bitmap and a colour that indicates the background.". -spec new(Bitmap, Index) -> wxMask() when Bitmap::wxBitmap:wxBitmap(), Index::integer(); @@ -85,7 +80,6 @@ new(#wx_ref{type=BitmapT}=Bitmap,Colour) wxe_util:queue_cmd(Bitmap,wxe_util:color(Colour),?get_env(),?wxMask_new_2_1), wxe_util:rec(?wxMask_new_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmask.html#wxmaskcreate">external documentation</a>. -doc "Constructs a mask from a monochrome bitmap.". -spec create(This, Bitmap) -> boolean() when This::wxMask(), Bitmap::wxBitmap:wxBitmap(). @@ -95,11 +89,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxMask_Create_1), wxe_util:rec(?wxMask_Create_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmask.html#wxmaskcreate">external documentation</a>. -%% <br /> Also:<br /> -%% create(This, Bitmap, Colour) -> boolean() when<br /> -%% This::wxMask(), Bitmap::wxBitmap:wxBitmap(), Colour::wx:wx_colour().<br /> -%% -doc "Constructs a mask from a bitmap and a colour that indicates the background.". -spec create(This, Bitmap, Index) -> boolean() when This::wxMask(), Bitmap::wxBitmap:wxBitmap(), Index::integer(); @@ -118,8 +107,7 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap,Colour) wxe_util:queue_cmd(This,Bitmap,wxe_util:color(Colour),?get_env(),?wxMask_Create_2_1), wxe_util:rec(?wxMask_Create_2_1). -%% @doc Destroys this object, do not use object again --doc "Destroys the `m:wxMask` object and the underlying bitmap data.". +-doc "Destroys the object". -spec destroy(This::wxMask()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMask), diff --git a/lib/wx/src/gen/wxMaximizeEvent.erl b/lib/wx/src/gen/wxMaximizeEvent.erl index f5adaec62e1b..e07f8e001e35 100644 --- a/lib/wx/src/gen/wxMaximizeEvent.erl +++ b/lib/wx/src/gen/wxMaximizeEvent.erl @@ -20,30 +20,31 @@ -module(wxMaximizeEvent). -moduledoc """ -Functions for wxMaximizeEvent class +An event being sent when a top level window is maximized. -An event being sent when a top level window is maximized. Notice that it is not -sent when the window is restored to its original size after it had been -maximized, only a normal `m:wxSizeEvent` is generated in this case. +Notice that it is not sent when the window is restored to its original size after it had +been maximized, only a normal `m:wxSizeEvent` is generated in this case. -Currently this event is only generated in wxMSW, wxGTK and wxOSX/Cocoa ports so -portable programs should only rely on receiving `wxEVT_SIZE` and not necessarily -this event when the window is maximized. +Currently this event is only generated in wxMSW, wxGTK and wxOSX/Cocoa ports so portable +programs should only rely on receiving `wxEVT_SIZE` and not necessarily this event when +the window is maximized. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxTopLevelWindow:maximize/2`, `wxTopLevelWindow:isMaximized/1` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvent` +* `wxTopLevelWindow:maximize/2` -wxWidgets docs: -[wxMaximizeEvent](https://docs.wxwidgets.org/3.1/classwx_maximize_event.html) +* `wxTopLevelWindow:isMaximized/1` + +This class is derived, and can use functions, from: + +* `m:wxEvent` + +wxWidgets docs: [wxMaximizeEvent](https://docs.wxwidgets.org/3.2/classwx_maximize_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxMaximizeEventType`](`t:wxMaximizeEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxMaximizeEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -56,36 +57,26 @@ this type. -include("wx.hrl"). -type wxMaximizeEventType() :: 'maximize'. -export_type([wxMaximizeEvent/0, wxMaximize/0, wxMaximizeEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMemoryDC.erl b/lib/wx/src/gen/wxMemoryDC.erl index 31972f28639d..60d5951bab0a 100644 --- a/lib/wx/src/gen/wxMemoryDC.erl +++ b/lib/wx/src/gen/wxMemoryDC.erl @@ -20,30 +20,33 @@ -module(wxMemoryDC). -moduledoc """ -Functions for wxMemoryDC class +A memory device context provides a means to draw graphics onto a bitmap. -A memory device context provides a means to draw graphics onto a bitmap. When -drawing in to a mono-bitmap, using `wxWHITE`, `wxWHITE_PEN` and `wxWHITE_BRUSH` -will draw the background colour (i.e. 0) whereas all other colours will draw the -foreground colour (i.e. 1). +When drawing in to a mono-bitmap, using `wxWHITE`, `wxWHITE_PEN` and `wxWHITE_BRUSH` will +draw the background colour (i.e. 0) whereas all other colours will draw the foreground +colour (i.e. 1). -A bitmap must be selected into the new memory DC before it may be used for -anything. Typical usage is as follows: +A bitmap must be selected into the new memory DC before it may be used for anything. +Typical usage is as follows: -Note that the memory DC must be deleted (or the bitmap selected out of it) -before a bitmap can be reselected into another memory DC. +Note that the memory DC must be deleted (or the bitmap selected out of it) before a +bitmap can be reselected into another memory DC. -And, before performing any other operations on the bitmap data, the bitmap must -be selected out of the memory DC: +And, before performing any other operations on the bitmap data, the bitmap must be +selected out of the memory DC: This happens automatically when `m:wxMemoryDC` object goes out of scope. -See: `m:wxBitmap`, `m:wxDC` +See: +* `m:wxBitmap` -This class is derived (and can use functions) from: `m:wxDC` +* `m:wxDC` -wxWidgets docs: -[wxMemoryDC](https://docs.wxwidgets.org/3.1/classwx_memory_d_c.html) +This class is derived, and can use functions, from: + +* `m:wxDC` + +wxWidgets docs: [wxMemoryDC](https://docs.wxwidgets.org/3.2/classwx_memory_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/0,new/1,selectObject/2,selectObjectAsSource/2]). @@ -72,33 +75,28 @@ wxWidgets docs: -type wxMemoryDC() :: wx:wx_object(). -export_type([wxMemoryDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmemorydc.html#wxmemorydcwxmemorydc">external documentation</a>. -doc """ Constructs a new memory device context. -Use the `wxDC:isOk/1` member to test whether the constructor was successful in -creating a usable device context. Don't forget to select a bitmap into the DC -before drawing on it. +Use the `wxDC:isOk/1` member to test whether the constructor was successful in creating a usable +device context. Don't forget to select a bitmap into the DC before drawing on it. """. -spec new() -> wxMemoryDC(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMemoryDC_new_0), wxe_util:rec(?wxMemoryDC_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmemorydc.html#wxmemorydcwxmemorydc">external documentation</a>. -doc """ -Constructs a new memory device context having the same characteristics as the -given existing device context. +Constructs a new memory device context having the same characteristics as the given +existing device context. -This constructor creates a memory device context `compatible` with `dc` in -wxMSW, the argument is ignored in the other ports. If `dc` is NULL, a device -context compatible with the screen is created, just as with the default -constructor. +This constructor creates a memory device context `compatible` with `dc` in wxMSW, the +argument is ignored in the other ports. If `dc` is NULL, a device context compatible with +the screen is created, just as with the default constructor. """. -spec new(Dc) -> wxMemoryDC() when Dc::wxDC:wxDC() | wxBitmap:wxBitmap(). @@ -113,24 +111,20 @@ new(#wx_ref{type=DcT}=Dc) -> wxe_util:queue_cmd(wx:typeCast(Dc, DcType),?get_env(),?wxMemoryDC_new_1), wxe_util:rec(?wxMemoryDC_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmemorydc.html#wxmemorydcselectobject">external documentation</a>. -doc """ -Works exactly like `selectObjectAsSource/2` but this is the function you should -use when you select a bitmap because you want to modify it, e.g. +Works exactly like `selectObjectAsSource/2` but this is the function you should use when +you select a bitmap because you want to modify it, e.g. drawing on this DC. -Using `selectObjectAsSource/2` when modifying the bitmap may incur some problems -related to `m:wxBitmap` being a reference counted object (see -overview_refcount). +Using `selectObjectAsSource/2` when modifying the bitmap may incur some problems related to `m:wxBitmap` being a +reference counted object (see overview_refcount). -Before using the updated bitmap data, make sure to select it out of context -first either by selecting ?wxNullBitmap into the device context or destroying -the device context entirely. +Before using the updated bitmap data, make sure to select it out of context first either +by selecting ?wxNullBitmap into the device context or destroying the device context entirely. -If the bitmap is already selected in this device context, nothing is done. If it -is selected in another context, the function asserts and drawing on the bitmap -won't work correctly. +If the bitmap is already selected in this device context, nothing is done. If it is +selected in another context, the function asserts and drawing on the bitmap won't work correctly. See: `wxDC:drawBitmap/4` """. @@ -141,17 +135,16 @@ selectObject(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxMemoryDC_SelectObject). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmemorydc.html#wxmemorydcselectobjectassource">external documentation</a>. -doc """ Selects the given bitmap into the device context, to use as the memory bitmap. -Selecting the bitmap into a memory DC allows you to draw into the DC (and -therefore the bitmap) and also to use `wxDC:blit/6` to copy the bitmap to a -window. For this purpose, you may find `wxDC:drawIcon/3` easier to use instead. +Selecting the bitmap into a memory DC allows you to draw into the DC (and therefore the +bitmap) and also to use `wxDC:blit/6` to copy the bitmap to a window. For this purpose, you may find `wxDC:drawIcon/3` +easier to use instead. -If the argument is ?wxNullBitmap (or some other uninitialised `m:wxBitmap`) the -current bitmap is selected out of the device context, and the original bitmap -restored, allowing the current bitmap to be destroyed safely. +If the argument is ?wxNullBitmap (or some other uninitialised `m:wxBitmap`) the current +bitmap is selected out of the device context, and the original bitmap restored, allowing +the current bitmap to be destroyed safely. """. -spec selectObjectAsSource(This, Bitmap) -> 'ok' when This::wxMemoryDC(), Bitmap::wxBitmap:wxBitmap(). @@ -160,287 +153,194 @@ selectObjectAsSource(#wx_ref{type=ThisT}=This,#wx_ref{type=BitmapT}=Bitmap) -> ?CLASS(BitmapT,wxBitmap), wxe_util:queue_cmd(This,Bitmap,?get_env(),?wxMemoryDC_SelectObjectAsSource). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxMemoryDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMemoryDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxMenu.erl b/lib/wx/src/gen/wxMenu.erl index 072cde596cc2..4f15932e1e81 100644 --- a/lib/wx/src/gen/wxMenu.erl +++ b/lib/wx/src/gen/wxMenu.erl @@ -20,74 +20,74 @@ -module(wxMenu). -moduledoc """ -Functions for wxMenu class - -A menu is a popup (or pull down) list of items, one of which may be selected -before the menu goes away (clicking elsewhere dismisses the menu). Menus may be -used to construct either menu bars or popup menus. - -A menu item has an integer ID associated with it which can be used to identify -the selection, or to change the menu item in some way. A menu item with a -special identifier `wxID_SEPARATOR` is a separator item and doesn't have an -associated command but just makes a separator line appear in the menu. - -Note: Please note that `wxID_ABOUT` and `wxID_EXIT` are predefined by wxWidgets -and have a special meaning since entries using these IDs will be taken out of -the normal menus under macOS and will be inserted into the system menu -(following the appropriate macOS interface guideline). - -Menu items may be either `normal` items, `check` items or `radio` items. Normal -items don't have any special properties while the check items have a boolean -flag associated to them and they show a checkmark in the menu when the flag is -set. wxWidgets automatically toggles the flag value when the item is clicked and -its value may be retrieved using either `isChecked/2` method of `m:wxMenu` or -`m:wxMenuBar` itself or by using wxEvent::IsChecked when you get the menu -notification for the item in question. - -The radio items are similar to the check items except that all the other items -in the same radio group are unchecked when a radio item is checked. The radio -group is formed by a contiguous range of radio items, i.e. it starts at the -first item of this kind and ends with the first item of a different kind (or the -end of the menu). Notice that because the radio groups are defined in terms of -the item positions inserting or removing the items in the menu containing the -radio items risks to not work correctly. +A menu is a popup (or pull down) list of items, one of which may be selected before the +menu goes away (clicking elsewhere dismisses the menu). + +Menus may be used to construct either menu bars or popup menus. + +A menu item has an integer ID associated with it which can be used to identify the +selection, or to change the menu item in some way. A menu item with a special identifier `wxID_SEPARATOR` +is a separator item and doesn't have an associated command but just makes a separator +line appear in the menu. + +Note: Please note that `wxID_ABOUT` and `wxID_EXIT` are predefined by wxWidgets and have +a special meaning since entries using these IDs will be taken out of the normal menus +under macOS and will be inserted into the system menu (following the appropriate macOS +interface guideline). + +Menu items may be either `normal` items, `check` items or `radio` items. Normal items +don't have any special properties while the check items have a boolean flag associated to +them and they show a checkmark in the menu when the flag is set. wxWidgets automatically +toggles the flag value when the item is clicked and its value may be retrieved using +either `isChecked/2` method of `m:wxMenu` or `m:wxMenuBar` itself or by using wxEvent::IsChecked when +you get the menu notification for the item in question. + +The radio items are similar to the check items except that all the other items in the +same radio group are unchecked when a radio item is checked. The radio group is formed by +a contiguous range of radio items, i.e. it starts at the first item of this kind and ends +with the first item of a different kind (or the end of the menu). Notice that because the +radio groups are defined in terms of the item positions inserting or removing the items in +the menu containing the radio items risks to not work correctly. Allocation strategy -All menus must be created on the `heap` because all menus attached to a menubar -or to another menu will be deleted by their parent when it is deleted. The only -exception to this rule are the popup menus (i.e. menus used with -`wxWindow:popupMenu/4`) as wxWidgets does not destroy them to allow reusing the -same menu more than once. But the exception applies only to the menus themselves -and not to any submenus of popup menus which are still destroyed by wxWidgets as -usual and so must be heap-allocated. +All menus must be created on the `heap` because all menus attached to a menubar or to +another menu will be deleted by their parent when it is deleted. The only exception to +this rule are the popup menus (i.e. menus used with `wxWindow:popupMenu/4`) as wxWidgets does not destroy them +to allow reusing the same menu more than once. But the exception applies only to the menus +themselves and not to any submenus of popup menus which are still destroyed by wxWidgets +as usual and so must be heap-allocated. -As the frame menubar is deleted by the frame itself, it means that normally all -menus used are deleted automatically. +As the frame menubar is deleted by the frame itself, it means that normally all menus +used are deleted automatically. Event handling -Event handlers for the commands generated by the menu items can be connected -directly to the menu object itself using `wxEvtHandler::Bind()` (not implemented -in wx). If this menu is a submenu of another one, the events from its items can -also be processed in the parent menu and so on, recursively. +Event handlers for the commands generated by the menu items can be connected directly to +the menu object itself using `wxEvtHandler::Bind()` (not implemented in wx). If this menu +is a submenu of another one, the events from its items can also be processed in the parent +menu and so on, recursively. -If the menu is part of a menu bar, then events can also be handled in -`m:wxMenuBar` object. +If the menu is part of a menu bar, then events can also be handled in `m:wxMenuBar` object. -Finally, menu events can also be handled in the associated window, which is -either the `m:wxFrame` associated with the menu bar this menu belongs to or the -window for which `wxWindow:popupMenu/4` was called for the popup menus. +Finally, menu events can also be handled in the associated window, which is either the `m:wxFrame` +associated with the menu bar this menu belongs to or the window for which `wxWindow:popupMenu/4` was called for +the popup menus. See overview_events_bind for how to bind event handlers to the various objects. -See: `m:wxMenuBar`, `wxWindow:popupMenu/4`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxFileHistory` (not implemented in wx) +See: +* `m:wxMenuBar` -This class is derived (and can use functions) from: `m:wxEvtHandler` +* `wxWindow:popupMenu/4` -wxWidgets docs: [wxMenu](https://docs.wxwidgets.org/3.1/classwx_menu.html) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: + +* `m:wxEvtHandler` + +wxWidgets docs: [wxMenu](https://docs.wxwidgets.org/3.2/classwx_menu.html) """. -include("wxe.hrl"). -export(['Destroy'/2,append/2,append/3,append/4,append/5,appendCheckItem/3,appendCheckItem/4, @@ -105,19 +105,16 @@ wxWidgets docs: [wxMenu](https://docs.wxwidgets.org/3.1/classwx_menu.html) -type wxMenu() :: wx:wx_object(). -export_type([wxMenu/0]). -%% @hidden -doc false. parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuwxmenu">external documentation</a>. -doc "Constructs a `m:wxMenu` object.". -spec new() -> wxMenu(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMenu_new_0), wxe_util:rec(?wxMenu_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuwxmenu">external documentation</a>. -doc "Constructs a `m:wxMenu` object.". -spec new([Option]) -> wxMenu() when Option :: {'style', integer()}. @@ -129,7 +126,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxMenu_new_1), wxe_util:rec(?wxMenu_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuwxmenu">external documentation</a>. -doc "Constructs a `m:wxMenu` object with a title.". -spec new(Title, [Option]) -> wxMenu() when Title::unicode:chardata(), @@ -143,19 +139,31 @@ new(Title, Options) wxe_util:queue_cmd(Title_UC, Opts,?get_env(),?wxMenu_new_2), wxe_util:rec(?wxMenu_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappend">external documentation</a>. -doc """ Adds a menu item object. -This is the most generic variant of `append/5` method because it may be used for -both items (including separators) and submenus and because you can also specify -various extra properties of a menu item this way, such as bitmaps and fonts. +This is the most generic variant of `append/5` method because it may be used for both items +(including separators) and submenus and because you can also specify various extra +properties of a menu item this way, such as bitmaps and fonts. Remark: See the remarks for the other `append/5` overloads. -See: `appendSeparator/1`, `appendCheckItem/4`, `appendRadioItem/4`, -`AppendSubMenu()` (not implemented in wx), `insert/6`, `setLabel/3`, -`getHelpString/2`, `setHelpString/3`, `m:wxMenuItem` +See: +* `appendSeparator/1` + +* `appendCheckItem/4` + +* `appendRadioItem/4` + +* `insert/6` + +* `setLabel/3` + +* `getHelpString/2` + +* `setHelpString/3` + +* `m:wxMenuItem` """. -spec append(This, MenuItem) -> wxMenuItem:wxMenuItem() when This::wxMenu(), MenuItem::wxMenuItem:wxMenuItem(). @@ -165,7 +173,7 @@ append(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuItemT}=MenuItem) -> wxe_util:queue_cmd(This,MenuItem,?get_env(),?wxMenu_Append_1), wxe_util:rec(?wxMenu_Append_1). -%% @equiv append(This,Id,Item, []) +-doc(#{equiv => append(This,Id,Item, [])}). -spec append(This, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(). @@ -173,28 +181,32 @@ append(This,Id,Item) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Item) -> append(This,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappend">external documentation</a>. -%% <br /> Also:<br /> -%% append(This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when<br /> -%% This::wxMenu(), Id::integer(), Item::unicode:chardata(),<br /> -%% Option :: {'help', unicode:chardata()}<br /> -%% | {'kind', wx:wx_enum()}.<br /> -%% -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Adds a menu item. -Example: +Example: or even better for stock menu items (see `wxMenuItem:new/1`): + +Remark: This command can be used after the menu has been shown, as well as on initial +creation of a menu or menubar. + +See: +* `appendSeparator/1` -or even better for stock menu items (see `wxMenuItem:new/1`): +* `appendCheckItem/4` -Remark: This command can be used after the menu has been shown, as well as on -initial creation of a menu or menubar. +* `appendRadioItem/4` -See: `appendSeparator/1`, `appendCheckItem/4`, `appendRadioItem/4`, -`AppendSubMenu()` (not implemented in wx), `insert/6`, `setLabel/3`, -`getHelpString/2`, `setHelpString/3`, `m:wxMenuItem` +* `insert/6` + +* `setLabel/3` + +* `getHelpString/2` + +* `setHelpString/3` + +* `m:wxMenuItem` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec append(This, Id, Item, SubMenu) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), SubMenu::wxMenu(); (This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when @@ -216,16 +228,29 @@ append(#wx_ref{type=ThisT}=This,Id,Item, Options) wxe_util:queue_cmd(This,Id,Item_UC, Opts,?get_env(),?wxMenu_Append_3), wxe_util:rec(?wxMenu_Append_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappend">external documentation</a>. -doc """ Adds a submenu. -Deprecated: This function is deprecated, use `AppendSubMenu()` (not implemented -in wx) instead. +Deprecated: + +This function is deprecated, use `AppendSubMenu()` (not implemented in wx) instead. + +See: +* `appendSeparator/1` + +* `appendCheckItem/4` + +* `appendRadioItem/4` + +* `insert/6` + +* `setLabel/3` + +* `getHelpString/2` -See: `appendSeparator/1`, `appendCheckItem/4`, `appendRadioItem/4`, -`AppendSubMenu()` (not implemented in wx), `insert/6`, `setLabel/3`, -`getHelpString/2`, `setHelpString/3`, `m:wxMenuItem` +* `setHelpString/3` + +* `m:wxMenuItem` """. -spec append(This, Id, Item, SubMenu, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), SubMenu::wxMenu(), @@ -241,7 +266,7 @@ append(#wx_ref{type=ThisT}=This,Id,Item,#wx_ref{type=SubMenuT}=SubMenu, Options) wxe_util:queue_cmd(This,Id,Item_UC,SubMenu, Opts,?get_env(),?wxMenu_Append_4), wxe_util:rec(?wxMenu_Append_4). -%% @equiv appendCheckItem(This,Id,Item, []) +-doc(#{equiv => appendCheckItem(This,Id,Item, [])}). -spec appendCheckItem(This, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(). @@ -249,11 +274,13 @@ appendCheckItem(This,Id,Item) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Item) -> appendCheckItem(This,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappendcheckitem">external documentation</a>. -doc """ Adds a checkable item to the end of the menu. -See: `append/5`, `insertCheckItem/5` +See: +* `append/5` + +* `insertCheckItem/5` """. -spec appendCheckItem(This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), @@ -268,7 +295,7 @@ appendCheckItem(#wx_ref{type=ThisT}=This,Id,Item, Options) wxe_util:queue_cmd(This,Id,Item_UC, Opts,?get_env(),?wxMenu_AppendCheckItem), wxe_util:rec(?wxMenu_AppendCheckItem). -%% @equiv appendRadioItem(This,Id,Item, []) +-doc(#{equiv => appendRadioItem(This,Id,Item, [])}). -spec appendRadioItem(This, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(). @@ -276,16 +303,18 @@ appendRadioItem(This,Id,Item) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Item) -> appendRadioItem(This,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappendradioitem">external documentation</a>. -doc """ Adds a radio item to the end of the menu. -All consequent radio items form a group and when an item in the group is -checked, all the others are automatically unchecked. +All consequent radio items form a group and when an item in the group is checked, all the +others are automatically unchecked. Note: Radio items are not supported under wxMotif. -See: `append/5`, `insertRadioItem/5` +See: +* `append/5` + +* `insertRadioItem/5` """. -spec appendRadioItem(This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), @@ -300,11 +329,13 @@ appendRadioItem(#wx_ref{type=ThisT}=This,Id,Item, Options) wxe_util:queue_cmd(This,Id,Item_UC, Opts,?get_env(),?wxMenu_AppendRadioItem), wxe_util:rec(?wxMenu_AppendRadioItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuappendseparator">external documentation</a>. -doc """ Adds a separator to the end of the menu. -See: `append/5`, `insertSeparator/2` +See: +* `append/5` + +* `insertSeparator/2` """. -spec appendSeparator(This) -> wxMenuItem:wxMenuItem() when This::wxMenu(). @@ -313,13 +344,11 @@ appendSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenu_AppendSeparator), wxe_util:rec(?wxMenu_AppendSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenubreak">external documentation</a>. -doc """ -Inserts a break in a menu, causing the next appended item to appear in a new -column. +Inserts a break in a menu, causing the next appended item to appear in a new column. -This function only actually inserts a break in wxMSW and does nothing under the -other platforms. +This function only actually inserts a break in wxMSW and does nothing under the other +platforms. """. -spec break(This) -> 'ok' when This::wxMenu(). @@ -327,7 +356,6 @@ break(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxMenu), wxe_util:queue_cmd(This,?get_env(),?wxMenu_Break). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenucheck">external documentation</a>. -doc """ Checks or unchecks the menu item. @@ -340,18 +368,17 @@ check(#wx_ref{type=ThisT}=This,Id,Check) ?CLASS(ThisT,wxMenu), wxe_util:queue_cmd(This,Id,Check,?get_env(),?wxMenu_Check). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenudelete">external documentation</a>. -%% <br /> Also:<br /> -%% delete(This, Item) -> boolean() when<br /> -%% This::wxMenu(), Item::wxMenuItem:wxMenuItem().<br /> -%% -doc """ Deletes the menu item from the menu. -If the item is a submenu, it will `not` be deleted. Use `'Destroy'/2` if you -want to delete a submenu. +If the item is a submenu, it will `not` be deleted. Use `'Destroy'/2` if you want to delete a submenu. + +See: +* `findItem/2` + +* `'Destroy'/2` -See: `findItem/2`, `'Destroy'/2`, `remove/2` +* `remove/2` """. -spec delete(This, Id) -> boolean() when This::wxMenu(), Id::integer(); @@ -368,18 +395,18 @@ delete(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(This,Item,?get_env(),?wxMenu_Delete_1_1), wxe_util:rec(?wxMenu_Delete_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenudestroy">external documentation</a>. -%% <br /> Also:<br /> -%% 'Destroy'(This, Item) -> boolean() when<br /> -%% This::wxMenu(), Item::wxMenuItem:wxMenuItem().<br /> -%% -doc """ Deletes the menu item from the menu. -If the item is a submenu, it will be deleted. Use `remove/2` if you want to keep -the submenu (for example, to reuse it later). +If the item is a submenu, it will be deleted. Use `remove/2` if you want to keep the submenu (for +example, to reuse it later). -See: `findItem/2`, `delete/2`, `remove/2` +See: +* `findItem/2` + +* `delete/2` + +* `remove/2` """. -spec 'Destroy'(This, Id) -> boolean() when This::wxMenu(), Id::integer(); @@ -396,7 +423,6 @@ See: `findItem/2`, `delete/2`, `remove/2` wxe_util:queue_cmd(This,Item,?get_env(),?wxMenu_Destroy_1_1), wxe_util:rec(?wxMenu_Destroy_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuenable">external documentation</a>. -doc """ Enables or disables (greys out) a menu item. @@ -409,18 +435,13 @@ enable(#wx_ref{type=ThisT}=This,Id,Enable) ?CLASS(ThisT,wxMenu), wxe_util:queue_cmd(This,Id,Enable,?get_env(),?wxMenu_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenufinditem">external documentation</a>. -%% <br /> Also:<br /> -%% findItem(This, ItemString) -> integer() when<br /> -%% This::wxMenu(), ItemString::unicode:chardata().<br /> -%% -doc """ Finds the menu id for a menu item string. Return: Menu item identifier, or wxNOT_FOUND if none is found. -Remark: Any special menu codes are stripped out of source and target strings -before matching. +Remark: Any special menu codes are stripped out of source and target strings before +matching. """. -spec findItem(This, Id) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(); @@ -438,7 +459,6 @@ findItem(#wx_ref{type=ThisT}=This,ItemString) wxe_util:queue_cmd(This,ItemString_UC,?get_env(),?wxMenu_FindItem_1), wxe_util:rec(?wxMenu_FindItem_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenufinditembyposition">external documentation</a>. -doc "Returns the `m:wxMenuItem` given a position in the menu.". -spec findItemByPosition(This, Position) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Position::integer(). @@ -448,14 +468,16 @@ findItemByPosition(#wx_ref{type=ThisT}=This,Position) wxe_util:queue_cmd(This,Position,?get_env(),?wxMenu_FindItemByPosition), wxe_util:rec(?wxMenu_FindItemByPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenugethelpstring">external documentation</a>. -doc """ Returns the help string associated with a menu item. -Return: The help string, or the empty string if there is no help string or the -item was not found. +Return: The help string, or the empty string if there is no help string or the item was +not found. + +See: +* `setHelpString/3` -See: `setHelpString/3`, `append/5` +* `append/5` """. -spec getHelpString(This, Id) -> unicode:charlist() when This::wxMenu(), Id::integer(). @@ -465,13 +487,12 @@ getHelpString(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenu_GetHelpString), wxe_util:rec(?wxMenu_GetHelpString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenugetlabel">external documentation</a>. -doc """ Returns a menu item label. Return: The item label, or the empty string if the item was not found. -See: `GetLabelText()` (not implemented in wx), `setLabel/3` +See: `setLabel/3` """. -spec getLabel(This, Id) -> unicode:charlist() when This::wxMenu(), Id::integer(). @@ -481,7 +502,6 @@ getLabel(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenu_GetLabel), wxe_util:rec(?wxMenu_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenugetmenuitemcount">external documentation</a>. -doc "Returns the number of items in the menu.". -spec getMenuItemCount(This) -> integer() when This::wxMenu(). @@ -490,7 +510,7 @@ getMenuItemCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenu_GetMenuItemCount), wxe_util:rec(?wxMenu_GetMenuItemCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenugetmenuitems">external documentation</a>. +-doc "". -spec getMenuItems(This) -> [wxMenuItem:wxMenuItem()] when This::wxMenu(). getMenuItems(#wx_ref{type=ThisT}=This) -> @@ -498,7 +518,6 @@ getMenuItems(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenu_GetMenuItems), wxe_util:rec(?wxMenu_GetMenuItems). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenugettitle">external documentation</a>. -doc """ Returns the title of the menu. @@ -511,19 +530,17 @@ getTitle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenu_GetTitle), wxe_util:rec(?wxMenu_GetTitle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsert">external documentation</a>. -%% <br /> Also:<br /> -%% insert(This, Pos, MenuItem) -> wxMenuItem:wxMenuItem() when<br /> -%% This::wxMenu(), Pos::integer(), MenuItem::wxMenuItem:wxMenuItem().<br /> -%% -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Inserts the given `item` before the position `pos`. Inserting the item at position `getMenuItemCount/1` is the same as appending it. -See: `append/5`, `prepend/5` +See: +* `append/5` + +* `prepend/5` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec insert(This, Pos, Id) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(); (This, Pos, MenuItem) -> wxMenuItem:wxMenuItem() when @@ -539,15 +556,17 @@ insert(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=MenuItemT}=MenuItem) wxe_util:queue_cmd(This,Pos,MenuItem,?get_env(),?wxMenu_Insert_2), wxe_util:rec(?wxMenu_Insert_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsert">external documentation</a>. -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Inserts the given `item` before the position `pos`. Inserting the item at position `getMenuItemCount/1` is the same as appending it. -See: `append/5`, `prepend/5` +See: +* `append/5` + +* `prepend/5` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec insert(This, Pos, Id, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Option :: {'text', unicode:chardata()} @@ -564,7 +583,7 @@ insert(#wx_ref{type=ThisT}=This,Pos,Id, Options) wxe_util:queue_cmd(This,Pos,Id, Opts,?get_env(),?wxMenu_Insert_3), wxe_util:rec(?wxMenu_Insert_3). -%% @equiv insert(This,Pos,Id,Text,Submenu, []) +-doc(#{equiv => insert(This,Pos,Id,Text,Submenu, [])}). -spec insert(This, Pos, Id, Text, Submenu) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Text::unicode:chardata(), Submenu::wxMenu(). @@ -572,14 +591,13 @@ insert(This,Pos,Id,Text,Submenu) when is_record(This, wx_ref),is_integer(Pos),is_integer(Id),?is_chardata(Text),is_record(Submenu, wx_ref) -> insert(This,Pos,Id,Text,Submenu, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsert">external documentation</a>. -doc """ Inserts the given `submenu` before the position `pos`. -`text` is the text shown in the menu for it and `help` is the help string shown -in the status bar when the submenu item is selected. +`text` is the text shown in the menu for it and `help` is the help string shown in the +status bar when the submenu item is selected. -See: `AppendSubMenu()` (not implemented in wx), `prepend/5` +See: `prepend/5` """. -spec insert(This, Pos, Id, Text, Submenu, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Text::unicode:chardata(), Submenu::wxMenu(), @@ -595,7 +613,7 @@ insert(#wx_ref{type=ThisT}=This,Pos,Id,Text,#wx_ref{type=SubmenuT}=Submenu, Opti wxe_util:queue_cmd(This,Pos,Id,Text_UC,Submenu, Opts,?get_env(),?wxMenu_Insert_5), wxe_util:rec(?wxMenu_Insert_5). -%% @equiv insertCheckItem(This,Pos,Id,Item, []) +-doc(#{equiv => insertCheckItem(This,Pos,Id,Item, [])}). -spec insertCheckItem(This, Pos, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Item::unicode:chardata(). @@ -603,11 +621,13 @@ insertCheckItem(This,Pos,Id,Item) when is_record(This, wx_ref),is_integer(Pos),is_integer(Id),?is_chardata(Item) -> insertCheckItem(This,Pos,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsertcheckitem">external documentation</a>. -doc """ Inserts a checkable item at the given position. -See: `insert/6`, `appendCheckItem/4` +See: +* `insert/6` + +* `appendCheckItem/4` """. -spec insertCheckItem(This, Pos, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Item::unicode:chardata(), @@ -622,7 +642,7 @@ insertCheckItem(#wx_ref{type=ThisT}=This,Pos,Id,Item, Options) wxe_util:queue_cmd(This,Pos,Id,Item_UC, Opts,?get_env(),?wxMenu_InsertCheckItem), wxe_util:rec(?wxMenu_InsertCheckItem). -%% @equiv insertRadioItem(This,Pos,Id,Item, []) +-doc(#{equiv => insertRadioItem(This,Pos,Id,Item, [])}). -spec insertRadioItem(This, Pos, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Item::unicode:chardata(). @@ -630,11 +650,13 @@ insertRadioItem(This,Pos,Id,Item) when is_record(This, wx_ref),is_integer(Pos),is_integer(Id),?is_chardata(Item) -> insertRadioItem(This,Pos,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsertradioitem">external documentation</a>. -doc """ Inserts a radio item at the given position. -See: `insert/6`, `appendRadioItem/4` +See: +* `insert/6` + +* `appendRadioItem/4` """. -spec insertRadioItem(This, Pos, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(), Id::integer(), Item::unicode:chardata(), @@ -649,11 +671,13 @@ insertRadioItem(#wx_ref{type=ThisT}=This,Pos,Id,Item, Options) wxe_util:queue_cmd(This,Pos,Id,Item_UC, Opts,?get_env(),?wxMenu_InsertRadioItem), wxe_util:rec(?wxMenu_InsertRadioItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuinsertseparator">external documentation</a>. -doc """ Inserts a separator at the given position. -See: `insert/6`, `appendSeparator/1` +See: +* `insert/6` + +* `appendSeparator/1` """. -spec insertSeparator(This, Pos) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Pos::integer(). @@ -663,7 +687,6 @@ insertSeparator(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxMenu_InsertSeparator), wxe_util:rec(?wxMenu_InsertSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuischecked">external documentation</a>. -doc """ Determines whether a menu item is checked. @@ -679,7 +702,6 @@ isChecked(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenu_IsChecked), wxe_util:rec(?wxMenu_IsChecked). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuisenabled">external documentation</a>. -doc """ Determines whether a menu item is enabled. @@ -695,18 +717,15 @@ isEnabled(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenu_IsEnabled), wxe_util:rec(?wxMenu_IsEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprepend">external documentation</a>. -%% <br /> Also:<br /> -%% prepend(This, Item) -> wxMenuItem:wxMenuItem() when<br /> -%% This::wxMenu(), Item::wxMenuItem:wxMenuItem().<br /> -%% -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ -Inserts the given `item` at position 0, i.e. before all the other existing -items. +Inserts the given `item` at position 0, i.e. before all the other existing items. + +See: +* `append/5` -See: `append/5`, `insert/6` +* `insert/6` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec prepend(This, Id) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(); (This, Item) -> wxMenuItem:wxMenuItem() when @@ -721,14 +740,15 @@ prepend(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(This,Item,?get_env(),?wxMenu_Prepend_1), wxe_util:rec(?wxMenu_Prepend_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprepend">external documentation</a>. -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ -Inserts the given `item` at position 0, i.e. before all the other existing -items. +Inserts the given `item` at position 0, i.e. before all the other existing items. -See: `append/5`, `insert/6` +See: +* `append/5` + +* `insert/6` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec prepend(This, Id, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Option :: {'text', unicode:chardata()} @@ -745,7 +765,7 @@ prepend(#wx_ref{type=ThisT}=This,Id, Options) wxe_util:queue_cmd(This,Id, Opts,?get_env(),?wxMenu_Prepend_2), wxe_util:rec(?wxMenu_Prepend_2). -%% @equiv prepend(This,Id,Text,Submenu, []) +-doc(#{equiv => prepend(This,Id,Text,Submenu, [])}). -spec prepend(This, Id, Text, Submenu) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Text::unicode:chardata(), Submenu::wxMenu(). @@ -753,11 +773,10 @@ prepend(This,Id,Text,Submenu) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Text),is_record(Submenu, wx_ref) -> prepend(This,Id,Text,Submenu, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprepend">external documentation</a>. -doc """ Inserts the given `submenu` at position 0. -See: `AppendSubMenu()` (not implemented in wx), `insert/6` +See: `insert/6` """. -spec prepend(This, Id, Text, Submenu, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Text::unicode:chardata(), Submenu::wxMenu(), @@ -773,7 +792,7 @@ prepend(#wx_ref{type=ThisT}=This,Id,Text,#wx_ref{type=SubmenuT}=Submenu, Options wxe_util:queue_cmd(This,Id,Text_UC,Submenu, Opts,?get_env(),?wxMenu_Prepend_4), wxe_util:rec(?wxMenu_Prepend_4). -%% @equiv prependCheckItem(This,Id,Item, []) +-doc(#{equiv => prependCheckItem(This,Id,Item, [])}). -spec prependCheckItem(This, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(). @@ -781,11 +800,13 @@ prependCheckItem(This,Id,Item) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Item) -> prependCheckItem(This,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprependcheckitem">external documentation</a>. -doc """ Inserts a checkable item at position 0. -See: `prepend/5`, `appendCheckItem/4` +See: +* `prepend/5` + +* `appendCheckItem/4` """. -spec prependCheckItem(This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), @@ -800,7 +821,7 @@ prependCheckItem(#wx_ref{type=ThisT}=This,Id,Item, Options) wxe_util:queue_cmd(This,Id,Item_UC, Opts,?get_env(),?wxMenu_PrependCheckItem), wxe_util:rec(?wxMenu_PrependCheckItem). -%% @equiv prependRadioItem(This,Id,Item, []) +-doc(#{equiv => prependRadioItem(This,Id,Item, [])}). -spec prependRadioItem(This, Id, Item) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(). @@ -808,11 +829,13 @@ prependRadioItem(This,Id,Item) when is_record(This, wx_ref),is_integer(Id),?is_chardata(Item) -> prependRadioItem(This,Id,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprependradioitem">external documentation</a>. -doc """ Inserts a radio item at position 0. -See: `prepend/5`, `appendRadioItem/4` +See: +* `prepend/5` + +* `appendRadioItem/4` """. -spec prependRadioItem(This, Id, Item, [Option]) -> wxMenuItem:wxMenuItem() when This::wxMenu(), Id::integer(), Item::unicode:chardata(), @@ -827,11 +850,13 @@ prependRadioItem(#wx_ref{type=ThisT}=This,Id,Item, Options) wxe_util:queue_cmd(This,Id,Item_UC, Opts,?get_env(),?wxMenu_PrependRadioItem), wxe_util:rec(?wxMenu_PrependRadioItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuprependseparator">external documentation</a>. -doc """ Inserts a separator at position 0. -See: `prepend/5`, `appendSeparator/1` +See: +* `prepend/5` + +* `appendSeparator/1` """. -spec prependSeparator(This) -> wxMenuItem:wxMenuItem() when This::wxMenu(). @@ -840,17 +865,11 @@ prependSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenu_PrependSeparator), wxe_util:rec(?wxMenu_PrependSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenuremove">external documentation</a>. -%% <br /> Also:<br /> -%% remove(This, Item) -> wxMenuItem:wxMenuItem() when<br /> -%% This::wxMenu(), Item::wxMenuItem:wxMenuItem().<br /> -%% -doc """ -Removes the menu item from the menu but doesn't delete the associated C++ -object. +Removes the menu item from the menu but doesn't delete the associated C++ object. -This allows you to reuse the same item later by adding it back to the menu -(especially useful with submenus). +This allows you to reuse the same item later by adding it back to the menu (especially +useful with submenus). Return: A pointer to the item which was detached from the menu. """. @@ -869,7 +888,6 @@ remove(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(This,Item,?get_env(),?wxMenu_Remove_1_1), wxe_util:rec(?wxMenu_Remove_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenusethelpstring">external documentation</a>. -doc """ Sets an item's help string. @@ -883,11 +901,13 @@ setHelpString(#wx_ref{type=ThisT}=This,Id,HelpString) HelpString_UC = unicode:characters_to_binary(HelpString), wxe_util:queue_cmd(This,Id,HelpString_UC,?get_env(),?wxMenu_SetHelpString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenusetlabel">external documentation</a>. -doc """ Sets the label of a menu item. -See: `append/5`, `getLabel/2` +See: +* `append/5` + +* `getLabel/2` """. -spec setLabel(This, Id, Label) -> 'ok' when This::wxMenu(), Id::integer(), Label::unicode:chardata(). @@ -897,13 +917,11 @@ setLabel(#wx_ref{type=ThisT}=This,Id,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Id,Label_UC,?get_env(),?wxMenu_SetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenu.html#wxmenusettitle">external documentation</a>. -doc """ Sets the title of the menu. -Remark: Notice that you can only call this method directly for the popup menus, -to change the title of a menu that is part of a menu bar you need to use -`wxMenuBar:setLabelTop/3`. +Remark: Notice that you can only call this method directly for the popup menus, to change +the title of a menu that is part of a menu bar you need to use `wxMenuBar:setLabelTop/3`. See: `getTitle/1` """. @@ -915,34 +933,20 @@ setTitle(#wx_ref{type=ThisT}=This,Title) Title_UC = unicode:characters_to_binary(Title), wxe_util:queue_cmd(This,Title_UC,?get_env(),?wxMenu_SetTitle). -%% @doc Destroys this object, do not use object again --doc """ -Destructor, destroying the menu. - -Note: Under Motif, a popup menu must have a valid parent (the window it was last -popped up on) when being destroyed. Therefore, make sure you delete or re-use -the popup menu `before` destroying the parent window. Re-use in this context -means popping up the menu on a different window from last time, which causes an -implicit destruction and recreation of internal data structures. -""". +-doc "Destroys the object". -spec destroy(This::wxMenu()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMenu), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMenuBar.erl b/lib/wx/src/gen/wxMenuBar.erl index e90552268ac2..f42aee8ab4b5 100644 --- a/lib/wx/src/gen/wxMenuBar.erl +++ b/lib/wx/src/gen/wxMenuBar.erl @@ -20,29 +20,31 @@ -module(wxMenuBar). -moduledoc """ -Functions for wxMenuBar class - A menu bar is a series of menus accessible from the top of a frame. -Remark: To respond to a menu selection, provide a handler for EVT_MENU, in the -frame that contains the menu bar. +Remark: To respond to a menu selection, provide a handler for EVT_MENU, in the frame that +contains the menu bar. + +If you have a toolbar which uses the same identifiers as your EVT_MENU entries, events +from the toolbar will also be processed by your EVT_MENU event handlers. + +Tip: under Windows, if you discover that menu shortcuts (for example, Alt-F to show the +file menu) are not working, check any EVT_CHAR events you are handling in child windows. +If you are not calling event.Skip() for events that you don't process in these event +handlers, menu shortcuts may cease to work. -If you have a toolbar which uses the same identifiers as your EVT_MENU entries, -events from the toolbar will also be processed by your EVT_MENU event handlers. +See: +* `m:wxMenu` -Tip: under Windows, if you discover that menu shortcuts (for example, Alt-F to -show the file menu) are not working, check any EVT_CHAR events you are handling -in child windows. If you are not calling event.Skip() for events that you don't -process in these event handlers, menu shortcuts may cease to work. +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: `m:wxMenu`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* `m:wxWindow` -wxWidgets docs: -[wxMenuBar](https://docs.wxwidgets.org/3.1/classwx_menu_bar.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxMenuBar](https://docs.wxwidgets.org/3.2/classwx_menu_bar.html) """. -include("wxe.hrl"). -export([append/3,check/3,destroy/1,enable/3,enableTop/3,findItem/2,findMenu/2, @@ -93,20 +95,18 @@ wxWidgets docs: -type wxMenuBar() :: wx:wx_object(). -export_type([wxMenuBar/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarwxmenubar">external documentation</a>. -doc "Construct an empty menu bar.". -spec new() -> wxMenuBar(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMenuBar_new_0), wxe_util:rec(?wxMenuBar_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarwxmenubar">external documentation</a>. +-doc "". -spec new(Style) -> wxMenuBar() when Style::integer(). new(Style) @@ -114,7 +114,6 @@ new(Style) wxe_util:queue_cmd(Style,?get_env(),?wxMenuBar_new_1), wxe_util:rec(?wxMenuBar_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarappend">external documentation</a>. -doc """ Adds the item to the end of the menu bar. @@ -132,12 +131,11 @@ append(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu,Title) wxe_util:queue_cmd(This,Menu,Title_UC,?get_env(),?wxMenuBar_Append), wxe_util:rec(?wxMenuBar_Append). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarcheck">external documentation</a>. -doc """ Checks or unchecks a menu item. -Remark: Only use this when the menu bar has been associated with a frame; -otherwise, use the `m:wxMenu` equivalent call. +Remark: Only use this when the menu bar has been associated with a frame; otherwise, use +the `m:wxMenu` equivalent call. """. -spec check(This, Id, Check) -> 'ok' when This::wxMenuBar(), Id::integer(), Check::boolean(). @@ -146,12 +144,11 @@ check(#wx_ref{type=ThisT}=This,Id,Check) ?CLASS(ThisT,wxMenuBar), wxe_util:queue_cmd(This,Id,Check,?get_env(),?wxMenuBar_Check). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarenable">external documentation</a>. -doc """ Enables or disables (greys out) a menu item. -Remark: Only use this when the menu bar has been associated with a frame; -otherwise, use the `m:wxMenu` equivalent call. +Remark: Only use this when the menu bar has been associated with a frame; otherwise, use +the `m:wxMenu` equivalent call. """. -spec enable(This, Id, Enable) -> 'ok' when This::wxMenuBar(), Id::integer(), Enable::boolean(). @@ -160,7 +157,6 @@ enable(#wx_ref{type=ThisT}=This,Id,Enable) ?CLASS(ThisT,wxMenuBar), wxe_util:queue_cmd(This,Id,Enable,?get_env(),?wxMenuBar_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarenabletop">external documentation</a>. -doc """ Enables or disables a whole menu. @@ -173,13 +169,12 @@ enableTop(#wx_ref{type=ThisT}=This,Pos,Enable) ?CLASS(ThisT,wxMenuBar), wxe_util:queue_cmd(This,Pos,Enable,?get_env(),?wxMenuBar_EnableTop). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarfindmenu">external documentation</a>. -doc """ -Returns the index of the menu with the given `title` or `wxNOT_FOUND` if no such -menu exists in this menubar. +Returns the index of the menu with the given `title` or `wxNOT\_FOUND` if no such menu +exists in this menubar. -The `title` parameter may specify either the menu title (with accelerator -characters, i.e. `"&File"`) or just the menu label (`"File"`) indifferently. +The `title` parameter may specify either the menu title (with accelerator characters, +i.e. `"&File"`) or just the menu label (`"File"`) indifferently. """. -spec findMenu(This, Title) -> integer() when This::wxMenuBar(), Title::unicode:chardata(). @@ -190,14 +185,13 @@ findMenu(#wx_ref{type=ThisT}=This,Title) wxe_util:queue_cmd(This,Title_UC,?get_env(),?wxMenuBar_FindMenu), wxe_util:rec(?wxMenuBar_FindMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarfindmenuitem">external documentation</a>. -doc """ Finds the menu item id for a menu name/menu item string pair. Return: The menu item identifier, or wxNOT_FOUND if none was found. -Remark: Any special menu codes are stripped out of source and target strings -before matching. +Remark: Any special menu codes are stripped out of source and target strings before +matching. """. -spec findMenuItem(This, MenuString, ItemString) -> integer() when This::wxMenuBar(), MenuString::unicode:chardata(), ItemString::unicode:chardata(). @@ -209,7 +203,6 @@ findMenuItem(#wx_ref{type=ThisT}=This,MenuString,ItemString) wxe_util:queue_cmd(This,MenuString_UC,ItemString_UC,?get_env(),?wxMenuBar_FindMenuItem), wxe_util:rec(?wxMenuBar_FindMenuItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarfinditem">external documentation</a>. -doc """ Finds the menu item object associated with the given menu item identifier. @@ -223,12 +216,11 @@ findItem(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenuBar_FindItem), wxe_util:rec(?wxMenuBar_FindItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargethelpstring">external documentation</a>. -doc """ Gets the help string associated with the menu item identifier. -Return: The help string, or the empty string if there was no help string or the -menu item was not found. +Return: The help string, or the empty string if there was no help string or the menu item +was not found. See: `setHelpString/3` """. @@ -240,7 +232,6 @@ getHelpString(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenuBar_GetHelpString), wxe_util:rec(?wxMenuBar_GetHelpString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetlabel">external documentation</a>. -doc """ Gets the label associated with a menu item. @@ -256,8 +247,7 @@ getLabel(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenuBar_GetLabel), wxe_util:rec(?wxMenuBar_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetmenulabel">external documentation</a>. --doc "See: `getMenuLabel/2`.". +-doc "Equivalent to: `getMenuLabel/2`". -spec getLabelTop(This, Pos) -> unicode:charlist() when This::wxMenuBar(), Pos::integer(). @@ -265,7 +255,6 @@ getLabelTop(This,Pos) when is_record(This, wx_ref),is_integer(Pos) -> getMenuLabel(This,Pos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetmenulabel">external documentation</a>. -doc """ Returns the label of a top-level menu. @@ -276,7 +265,10 @@ Return: The menu label, or the empty string if the menu was not found. Remark: Use only after the menubar has been associated with a frame. -See: `getMenuLabelText/2`, `setMenuLabel/3` +See: +* `getMenuLabelText/2` + +* `setMenuLabel/3` """. -spec getMenuLabel(This, Pos) -> unicode:charlist() when This::wxMenuBar(), Pos::integer(). @@ -286,18 +278,20 @@ getMenuLabel(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxMenuBar_GetMenuLabel), wxe_util:rec(?wxMenuBar_GetMenuLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetmenulabeltext">external documentation</a>. -doc """ Returns the label of a top-level menu. -Note that the returned string does not include any accelerator characters that -may have been specified in the menu title string during its construction. +Note that the returned string does not include any accelerator characters that may have +been specified in the menu title string during its construction. Return: The menu label, or the empty string if the menu was not found. Remark: Use only after the menubar has been associated with a frame. -See: `getMenuLabel/2`, `setMenuLabel/3` +See: +* `getMenuLabel/2` + +* `setMenuLabel/3` """. -spec getMenuLabelText(This, Pos) -> unicode:charlist() when This::wxMenuBar(), Pos::integer(). @@ -307,7 +301,6 @@ getMenuLabelText(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxMenuBar_GetMenuLabelText), wxe_util:rec(?wxMenuBar_GetMenuLabelText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetmenu">external documentation</a>. -doc "Returns the menu at `menuIndex` (zero-based).". -spec getMenu(This, MenuIndex) -> wxMenu:wxMenu() when This::wxMenuBar(), MenuIndex::integer(). @@ -317,7 +310,6 @@ getMenu(#wx_ref{type=ThisT}=This,MenuIndex) wxe_util:queue_cmd(This,MenuIndex,?get_env(),?wxMenuBar_GetMenu), wxe_util:rec(?wxMenuBar_GetMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetmenucount">external documentation</a>. -doc "Returns the number of menus in this menubar.". -spec getMenuCount(This) -> integer() when This::wxMenuBar(). @@ -326,12 +318,11 @@ getMenuCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuBar_GetMenuCount), wxe_util:rec(?wxMenuBar_GetMenuCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarinsert">external documentation</a>. -doc """ Inserts the menu at the given position into the menu bar. -Inserting menu at position 0 will insert it in the very beginning of it, -inserting at position `getMenuCount/1` is the same as calling `append/3`. +Inserting menu at position 0 will insert it in the very beginning of it, inserting at +position `getMenuCount/1` is the same as calling `append/3`. Return: true on success, false if an error occurred. @@ -347,7 +338,6 @@ insert(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=MenuT}=Menu,Title) wxe_util:queue_cmd(This,Pos,Menu,Title_UC,?get_env(),?wxMenuBar_Insert), wxe_util:rec(?wxMenuBar_Insert). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarischecked">external documentation</a>. -doc """ Determines whether an item is checked. @@ -361,26 +351,24 @@ isChecked(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenuBar_IsChecked), wxe_util:rec(?wxMenuBar_IsChecked). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarsetautowindowmenu">external documentation</a>. +-doc "". -spec setAutoWindowMenu(Enable) -> 'ok' when Enable::boolean(). setAutoWindowMenu(Enable) when is_boolean(Enable) -> wxe_util:queue_cmd(Enable,?get_env(),?wxMenuBar_SetAutoWindowMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubargetautowindowmenu">external documentation</a>. +-doc "". -spec getAutoWindowMenu() -> boolean(). getAutoWindowMenu() -> wxe_util:queue_cmd(?get_env(), ?wxMenuBar_GetAutoWindowMenu), wxe_util:rec(?wxMenuBar_GetAutoWindowMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarosxgetapplemenu">external documentation</a>. -doc """ Returns the Apple menu. -This is the leftmost menu with application's name as its title. You shouldn't -remove any items from it, but it is safe to insert extra menu items or submenus -into it. +This is the leftmost menu with application's name as its title. You shouldn't remove any +items from it, but it is safe to insert extra menu items or submenus into it. Only for:wxosx @@ -393,10 +381,9 @@ oSXGetAppleMenu(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuBar_OSXGetAppleMenu), wxe_util:rec(?wxMenuBar_OSXGetAppleMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarmacgetcommonmenubar">external documentation</a>. -doc """ -Enables you to get the global menubar on Mac, that is, the menubar displayed -when the app is running without any frames open. +Enables you to get the global menubar on Mac, that is, the menubar displayed when the app +is running without any frames open. Return: The global menubar. @@ -409,10 +396,9 @@ macGetCommonMenuBar() -> wxe_util:queue_cmd(?get_env(), ?wxMenuBar_MacGetCommonMenuBar), wxe_util:rec(?wxMenuBar_MacGetCommonMenuBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarmacsetcommonmenubar">external documentation</a>. -doc """ -Enables you to set the global menubar on Mac, that is, the menubar displayed -when the app is running without any frames open. +Enables you to set the global menubar on Mac, that is, the menubar displayed when the app +is running without any frames open. Remark: Only exists on Mac, other platforms do not have this method. @@ -424,7 +410,6 @@ macSetCommonMenuBar(#wx_ref{type=MenubarT}=Menubar) -> ?CLASS(MenubarT,wxMenuBar), wxe_util:queue_cmd(Menubar,?get_env(),?wxMenuBar_MacSetCommonMenuBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarisenabled">external documentation</a>. -doc """ Determines whether an item is enabled. @@ -438,13 +423,11 @@ isEnabled(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxMenuBar_IsEnabled), wxe_util:rec(?wxMenuBar_IsEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarremove">external documentation</a>. -doc """ Removes the menu from the menu bar and returns the menu object - the caller is responsible for deleting it. -This function may be used together with `insert/4` to change the menubar -dynamically. +This function may be used together with `insert/4` to change the menubar dynamically. See: `replace/4` """. @@ -456,14 +439,16 @@ remove(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxMenuBar_Remove), wxe_util:rec(?wxMenuBar_Remove). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarreplace">external documentation</a>. -doc """ Replaces the menu at the given position with another one. -Return: The menu which was previously at position pos. The caller is responsible -for deleting it. +Return: The menu which was previously at position pos. The caller is responsible for +deleting it. + +See: +* `insert/4` -See: `insert/4`, `remove/2` +* `remove/2` """. -spec replace(This, Pos, Menu, Title) -> wxMenu:wxMenu() when This::wxMenuBar(), Pos::integer(), Menu::wxMenu:wxMenu(), Title::unicode:chardata(). @@ -475,7 +460,6 @@ replace(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=MenuT}=Menu,Title) wxe_util:queue_cmd(This,Pos,Menu,Title_UC,?get_env(),?wxMenuBar_Replace), wxe_util:rec(?wxMenuBar_Replace). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarsethelpstring">external documentation</a>. -doc """ Sets the help string associated with a menu item. @@ -489,7 +473,6 @@ setHelpString(#wx_ref{type=ThisT}=This,Id,HelpString) HelpString_UC = unicode:characters_to_binary(HelpString), wxe_util:queue_cmd(This,Id,HelpString_UC,?get_env(),?wxMenuBar_SetHelpString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarsetlabel">external documentation</a>. -doc """ Sets the label of a menu item. @@ -505,8 +488,7 @@ setLabel(#wx_ref{type=ThisT}=This,Id,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Id,Label_UC,?get_env(),?wxMenuBar_SetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarsetmenulabel">external documentation</a>. --doc "See: `setMenuLabel/3`.". +-doc "Equivalent to: `setMenuLabel/3`". -spec setLabelTop(This, Pos, Label) -> 'ok' when This::wxMenuBar(), Pos::integer(), Label::unicode:chardata(). @@ -514,7 +496,6 @@ setLabelTop(This,Pos,Label) when is_record(This, wx_ref),is_integer(Pos),?is_chardata(Label) -> setMenuLabel(This,Pos,Label). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenubar.html#wxmenubarsetmenulabel">external documentation</a>. -doc """ Sets the label of a top-level menu. @@ -528,549 +509,367 @@ setMenuLabel(#wx_ref{type=ThisT}=This,Pos,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Pos,Label_UC,?get_env(),?wxMenuBar_SetMenuLabel). -%% @doc Destroys this object, do not use object again --doc """ -Destructor, destroying the menu bar and removing it from the parent frame (if -any). -""". +-doc "Destroys the object". -spec destroy(This::wxMenuBar()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMenuBar), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMenuEvent.erl b/lib/wx/src/gen/wxMenuEvent.erl index 0b0f2e75084c..ec6d368a27e9 100644 --- a/lib/wx/src/gen/wxMenuEvent.erl +++ b/lib/wx/src/gen/wxMenuEvent.erl @@ -20,36 +20,38 @@ -module(wxMenuEvent). -moduledoc """ -Functions for wxMenuEvent class +This class is used for a variety of menu-related events. -This class is used for a variety of menu-related events. Note that these do not -include menu command events, which are handled using `m:wxCommandEvent` objects. +Note that these do not include menu command events, which are handled using `m:wxCommandEvent` +objects. -Events of this class are generated by both menus that are part of a -`m:wxMenuBar`, attached to `m:wxFrame`, and popup menus shown by -`wxWindow:popupMenu/4`. They are sent to the following objects until one of them -handles the event: -`-# The menu object itself, as returned by GetMenu(), if any. -# The wxMenuBar to which this menu is attached, if any. -# The window associated with the menu, e.g. the one calling PopupMenu() for the popup menus. -# The top level parent of that window if it's different from the window itself.` +Events of this class are generated by both menus that are part of a `m:wxMenuBar`, +attached to `m:wxFrame`, and popup menus shown by `wxWindow:popupMenu/4`. They are sent to the following objects +until one of them handles the event: `-# The menu object itself, as returned by GetMenu(), if any. -# The wxMenuBar to which +this menu is attached, if any. -# The window associated with the menu, e.g. the one +calling PopupMenu() for the popup menus. -# The top level parent of that window if it's +different from the window itself. ` +This is similar to command events generated by the menu items, but, unlike them, `m:wxMenuEvent` +are only sent to the window itself and its top level parent but not any intermediate +windows in the hierarchy. -This is similar to command events generated by the menu items, but, unlike them, -`m:wxMenuEvent` are only sent to the window itself and its top level parent but -not any intermediate windows in the hierarchy. +The default handler for `wxEVT_MENU_HIGHLIGHT` in `m:wxFrame` displays help text in the +status bar, see `wxFrame:setStatusBarPane/2`. -The default handler for `wxEVT_MENU_HIGHLIGHT` in `m:wxFrame` displays help text -in the status bar, see `wxFrame:setStatusBarPane/2`. +See: +* `m:wxCommandEvent` -See: `m:wxCommandEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxMenuEvent](https://docs.wxwidgets.org/3.1/classwx_menu_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxMenuEvent](https://docs.wxwidgets.org/3.2/classwx_menu_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxMenuEventType`](`t:wxMenuEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxMenuEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getMenu/1,getMenuId/1,isPopup/1]). @@ -62,23 +64,19 @@ subscribe to events of this type. -include("wx.hrl"). -type wxMenuEventType() :: 'menu_open' | 'menu_close' | 'menu_highlight'. -export_type([wxMenuEvent/0, wxMenu/0, wxMenuEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuevent.html#wxmenueventgetmenu">external documentation</a>. -doc """ -Returns the menu which is being opened or closed, or the menu containing the -highlighted item. +Returns the menu which is being opened or closed, or the menu containing the highlighted +item. Note that the returned value can be NULL if the menu being opened doesn't have a -corresponding `m:wxMenu`, e.g. this happens when opening the system menu in -wxMSW port. +corresponding `m:wxMenu`, e.g. this happens when opening the system menu in wxMSW port. -Remark: Since 3.1.3 this function can be used with `OPEN`, `CLOSE` and -`HIGHLIGHT` events. Before 3.1.3, this method can only be used with the `OPEN` -and `CLOSE` events. +Remark: Since 3.1.3 this function can be used with `OPEN`, `CLOSE` and `HIGHLIGHT` +events. Before 3.1.3, this method can only be used with the `OPEN` and `CLOSE` events. """. -spec getMenu(This) -> wxMenu:wxMenu() when This::wxMenuEvent(). @@ -87,7 +85,6 @@ getMenu(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuEvent_GetMenu), wxe_util:rec(?wxMenuEvent_GetMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuevent.html#wxmenueventgetmenuid">external documentation</a>. -doc """ Returns the menu identifier associated with the event. @@ -100,10 +97,9 @@ getMenuId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuEvent_GetMenuId), wxe_util:rec(?wxMenuEvent_GetMenuId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuevent.html#wxmenueventispopup">external documentation</a>. -doc """ -Returns true if the menu which is being opened or closed is a popup menu, false -if it is a normal one. +Returns true if the menu which is being opened or closed is a popup menu, false if it is +a normal one. This method should only be used with the `OPEN` and `CLOSE` events. """. @@ -115,30 +111,21 @@ isPopup(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxMenuEvent_IsPopup). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMenuItem.erl b/lib/wx/src/gen/wxMenuItem.erl index 339377128a7a..ac264f6f6735 100644 --- a/lib/wx/src/gen/wxMenuItem.erl +++ b/lib/wx/src/gen/wxMenuItem.erl @@ -20,25 +20,30 @@ -module(wxMenuItem). -moduledoc """ -Functions for wxMenuItem class - A menu item represents an item in a menu. -Note that you usually don't have to deal with it directly as `m:wxMenu` methods -usually construct an object of this class for you. +Note that you usually don't have to deal with it directly as `m:wxMenu` methods usually +construct an object of this class for you. + +Also please note that the methods related to fonts and bitmaps are currently only +implemented for Windows, Mac and GTK+. -Also please note that the methods related to fonts and bitmaps are currently -only implemented for Windows, Mac and GTK+. +See: +* `m:wxMenuBar` -See: `m:wxMenuBar`, `m:wxMenu` +* `m:wxMenu` -wxWidgets docs: -[wxMenuItem](https://docs.wxwidgets.org/3.1/classwx_menu_item.html) +wxWidgets docs: [wxMenuItem](https://docs.wxwidgets.org/3.2/classwx_menu_item.html) ## Events -Event types emitted from this class: [`menu_open`](`m:wxMenuEvent`), -[`menu_close`](`m:wxMenuEvent`), [`menu_highlight`](`m:wxMenuEvent`) +Event types emitted from this class: + +* [`menu_open`](`m:wxMenuEvent`) + +* [`menu_close`](`m:wxMenuEvent`) + +* [`menu_highlight`](`m:wxMenuEvent`) """. -include("wxe.hrl"). -export([check/1,check/2,destroy/1,enable/1,enable/2,getBitmap/1,getHelp/1,getId/1, @@ -52,42 +57,37 @@ Event types emitted from this class: [`menu_open`](`m:wxMenuEvent`), -type wxMenuItem() :: wx:wx_object(). -export_type([wxMenuItem/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxMenuItem(). new() -> new([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemwxmenuitem">external documentation</a>. -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Constructs a `m:wxMenuItem` object. -Menu items can be standard, or "stock menu items", or custom. For the standard -menu items (such as commands to open a file, exit the program and so on, see -page_stockitems for the full list) it is enough to specify just the stock ID and -leave `text` and `help` string empty. Some platforms (currently wxGTK only, and -see the remark in `setBitmap/2` documentation) will also show standard bitmaps -for stock menu items. +Menu items can be standard, or "stock menu items", or custom. For the standard menu items +(such as commands to open a file, exit the program and so on, see page_stockitems for the +full list) it is enough to specify just the stock ID and leave `text` and `help` string +empty. Some platforms (currently wxGTK only, and see the remark in `setBitmap/2` documentation) will +also show standard bitmaps for stock menu items. -Leaving at least `text` empty for the stock menu items is actually strongly -recommended as they will have appearance and keyboard interface (including -standard accelerators) familiar to the user. +Leaving at least `text` empty for the stock menu items is actually strongly recommended +as they will have appearance and keyboard interface (including standard accelerators) +familiar to the user. -For the custom (non-stock) menu items, `text` must be specified and while `help` -string may be left empty, it's recommended to pass the item description (which -is automatically shown by the library in the status bar when the menu item is -selected) in this parameter. +For the custom (non-stock) menu items, `text` must be specified and while `help` string +may be left empty, it's recommended to pass the item description (which is automatically +shown by the library in the status bar when the menu item is selected) in this parameter. -Finally note that you can e.g. use a stock menu label without using its stock -help string: +Finally note that you can e.g. use a stock menu label without using its stock help string: that is, stock properties are set independently one from the other. """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec new([Option]) -> wxMenuItem() when Option :: {'parentMenu', wxMenu:wxMenu()} | {'id', integer()} @@ -108,7 +108,7 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxMenuItem_new), wxe_util:rec(?wxMenuItem_new). -%% @equiv check(This, []) +-doc(#{equiv => check(This, [])}). -spec check(This) -> 'ok' when This::wxMenuItem(). @@ -116,7 +116,6 @@ check(This) when is_record(This, wx_ref) -> check(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemcheck">external documentation</a>. -doc """ Checks or unchecks the menu item. @@ -133,7 +132,7 @@ check(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxMenuItem_Check). -%% @equiv enable(This, []) +-doc(#{equiv => enable(This, [])}). -spec enable(This) -> 'ok' when This::wxMenuItem(). @@ -141,7 +140,6 @@ enable(This) when is_record(This, wx_ref) -> enable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemenable">external documentation</a>. -doc "Enables or disables the menu item.". -spec enable(This, [Option]) -> 'ok' when This::wxMenuItem(), @@ -154,7 +152,6 @@ enable(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxMenuItem_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetbitmap">external documentation</a>. -doc """ Returns the checked or unchecked bitmap. @@ -167,7 +164,6 @@ getBitmap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetBitmap), wxe_util:rec(?wxMenuItem_GetBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgethelp">external documentation</a>. -doc "Returns the help string associated with the menu item.". -spec getHelp(This) -> unicode:charlist() when This::wxMenuItem(). @@ -176,7 +172,6 @@ getHelp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetHelp), wxe_util:rec(?wxMenuItem_GetHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetid">external documentation</a>. -doc "Returns the menu item identifier.". -spec getId(This) -> integer() when This::wxMenuItem(). @@ -185,12 +180,8 @@ getId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetId), wxe_util:rec(?wxMenuItem_GetId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetkind">external documentation</a>. -%%<br /> Res = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX --doc """ -Returns the item kind, one of `wxITEM_SEPARATOR`, `wxITEM_NORMAL`, -`wxITEM_CHECK` or `wxITEM_RADIO`. -""". +-doc "Returns the item kind, one of `wxITEM\_SEPARATOR`, `wxITEM\_NORMAL`, `wxITEM\_CHECK` or `wxITEM\_RADIO`.". +%% Res = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec getKind(This) -> wx:wx_enum() when This::wxMenuItem(). getKind(#wx_ref{type=ThisT}=This) -> @@ -198,8 +189,7 @@ getKind(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetKind), wxe_util:rec(?wxMenuItem_GetKind). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetlabeltext">external documentation</a>. --doc "See: `getLabelText/1`.". +-doc "Equivalent to: `getLabelText/1`". -spec getLabelFromText(Text) -> unicode:charlist() when Text::unicode:chardata(). @@ -207,7 +197,6 @@ getLabelFromText(Text) when ?is_chardata(Text) -> getLabelText(Text). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetlabeltext">external documentation</a>. -doc """ Strips all accelerator characters and mnemonics from the given `text`. @@ -215,7 +204,10 @@ For example: will return just `"Hello"`. -See: `getItemLabelText/1`, `getItemLabel/1` +See: +* `getItemLabelText/1` + +* `getItemLabel/1` """. -spec getLabelText(Text) -> unicode:charlist() when Text::unicode:chardata(). @@ -225,8 +217,7 @@ getLabelText(Text) wxe_util:queue_cmd(Text_UC,?get_env(),?wxMenuItem_GetLabelText), wxe_util:rec(?wxMenuItem_GetLabelText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetitemlabel">external documentation</a>. --doc "See: `getItemLabel/1`.". +-doc "Equivalent to: `getItemLabel/1`". -spec getText(This) -> unicode:charlist() when This::wxMenuItem(). @@ -234,12 +225,14 @@ getText(This) when is_record(This, wx_ref) -> getItemLabel(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetitemlabel">external documentation</a>. -doc """ -Returns the text associated with the menu item including any accelerator -characters that were passed to the constructor or `setItemLabel/2`. +Returns the text associated with the menu item including any accelerator characters that +were passed to the constructor or `setItemLabel/2`. + +See: +* `getItemLabelText/1` -See: `getItemLabelText/1`, `getLabelText/1` +* `getLabelText/1` """. -spec getItemLabel(This) -> unicode:charlist() when This::wxMenuItem(). @@ -248,8 +241,7 @@ getItemLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetItemLabel), wxe_util:rec(?wxMenuItem_GetItemLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetitemlabeltext">external documentation</a>. --doc "See: `getItemLabelText/1`.". +-doc "Equivalent to: `getItemLabelText/1`". -spec getLabel(This) -> unicode:charlist() when This::wxMenuItem(). @@ -257,12 +249,13 @@ getLabel(This) when is_record(This, wx_ref) -> getItemLabelText(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetitemlabeltext">external documentation</a>. -doc """ -Returns the text associated with the menu item, without any accelerator -characters. +Returns the text associated with the menu item, without any accelerator characters. -See: `getItemLabel/1`, `getLabelText/1` +See: +* `getItemLabel/1` + +* `getLabelText/1` """. -spec getItemLabelText(This) -> unicode:charlist() when This::wxMenuItem(). @@ -271,11 +264,7 @@ getItemLabelText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetItemLabelText), wxe_util:rec(?wxMenuItem_GetItemLabelText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetmenu">external documentation</a>. --doc """ -Returns the menu this menu item is in, or NULL if this menu item is not -attached. -""". +-doc "Returns the menu this menu item is in, or NULL if this menu item is not attached.". -spec getMenu(This) -> wxMenu:wxMenu() when This::wxMenuItem(). getMenu(#wx_ref{type=ThisT}=This) -> @@ -283,7 +272,6 @@ getMenu(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetMenu), wxe_util:rec(?wxMenuItem_GetMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemgetsubmenu">external documentation</a>. -doc "Returns the submenu associated with the menu item, or NULL if there isn't one.". -spec getSubMenu(This) -> wxMenu:wxMenu() when This::wxMenuItem(). @@ -292,13 +280,12 @@ getSubMenu(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_GetSubMenu), wxe_util:rec(?wxMenuItem_GetSubMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemischeckable">external documentation</a>. -doc """ Returns true if the item is checkable. -Notice that the radio buttons are considered to be checkable as well, so this -method returns true for them too. Use `IsCheck()` (not implemented in wx) if you -want to test for the check items only. +Notice that the radio buttons are considered to be checkable as well, so this method +returns true for them too. Use `IsCheck()` (not implemented in wx) if you want to test for +the check items only. """. -spec isCheckable(This) -> boolean() when This::wxMenuItem(). @@ -307,7 +294,6 @@ isCheckable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_IsCheckable), wxe_util:rec(?wxMenuItem_IsCheckable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemischecked">external documentation</a>. -doc "Returns true if the item is checked.". -spec isChecked(This) -> boolean() when This::wxMenuItem(). @@ -316,7 +302,6 @@ isChecked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_IsChecked), wxe_util:rec(?wxMenuItem_IsChecked). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemisenabled">external documentation</a>. -doc "Returns true if the item is enabled.". -spec isEnabled(This) -> boolean() when This::wxMenuItem(). @@ -325,7 +310,6 @@ isEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_IsEnabled), wxe_util:rec(?wxMenuItem_IsEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemisseparator">external documentation</a>. -doc "Returns true if the item is a separator.". -spec isSeparator(This) -> boolean() when This::wxMenuItem(). @@ -334,7 +318,6 @@ isSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_IsSeparator), wxe_util:rec(?wxMenuItem_IsSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemissubmenu">external documentation</a>. -doc "Returns true if the item is a submenu.". -spec isSubMenu(This) -> boolean() when This::wxMenuItem(). @@ -343,22 +326,19 @@ isSubMenu(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMenuItem_IsSubMenu), wxe_util:rec(?wxMenuItem_IsSubMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsetbitmap">external documentation</a>. -doc """ Sets the bitmap for the menu item. -It is equivalent to wxMenuItem::SetBitmaps(bmp, wxNullBitmap) if `checked` is -true (default value) or SetBitmaps(wxNullBitmap, bmp) otherwise. +It is equivalent to wxMenuItem::SetBitmaps(bmp, wxNullBitmap) if `checked` is true +(default value) or SetBitmaps(wxNullBitmap, bmp) otherwise. -`setBitmap/2` must be called before the item is appended to the menu, i.e. -appending the item without a bitmap and setting one later is not guaranteed to -work. But the bitmap can be changed or reset later if it had been set up -initially. +`setBitmap/2` must be called before the item is appended to the menu, i.e. appending the item without +a bitmap and setting one later is not guaranteed to work. But the bitmap can be changed or +reset later if it had been set up initially. -Notice that GTK+ uses a global setting called `gtk-menu-images` to determine if -the images should be shown in the menus at all. If it is off (which is the case -in e.g. Gnome 2.28 by default), no images will be shown, consistently with the -native behaviour. +Notice that GTK+ uses a global setting called `gtk-menu-images` to determine if the +images should be shown in the menus at all. If it is off (which is the case in e.g. Gnome +2.28 by default), no images will be shown, consistently with the native behaviour. Only for:wxmsw,wxosx,wxgtk """. @@ -369,7 +349,6 @@ setBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=BmpT}=Bmp) -> ?CLASS(BmpT,wxBitmap), wxe_util:queue_cmd(This,Bmp,?get_env(),?wxMenuItem_SetBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsethelp">external documentation</a>. -doc "Sets the help string.". -spec setHelp(This, HelpString) -> 'ok' when This::wxMenuItem(), HelpString::unicode:chardata(). @@ -379,7 +358,6 @@ setHelp(#wx_ref{type=ThisT}=This,HelpString) HelpString_UC = unicode:characters_to_binary(HelpString), wxe_util:queue_cmd(This,HelpString_UC,?get_env(),?wxMenuItem_SetHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsetmenu">external documentation</a>. -doc "Sets the parent menu which will contain this menu item.". -spec setMenu(This, Menu) -> 'ok' when This::wxMenuItem(), Menu::wxMenu:wxMenu(). @@ -388,7 +366,6 @@ setMenu(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu) -> ?CLASS(MenuT,wxMenu), wxe_util:queue_cmd(This,Menu,?get_env(),?wxMenuItem_SetMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsetsubmenu">external documentation</a>. -doc "Sets the submenu of this menu item.". -spec setSubMenu(This, Menu) -> 'ok' when This::wxMenuItem(), Menu::wxMenu:wxMenu(). @@ -397,8 +374,7 @@ setSubMenu(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu) -> ?CLASS(MenuT,wxMenu), wxe_util:queue_cmd(This,Menu,?get_env(),?wxMenuItem_SetSubMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsetitemlabel">external documentation</a>. --doc "See: `setItemLabel/2`.". +-doc "Equivalent to: `setItemLabel/2`". -spec setText(This, Label) -> 'ok' when This::wxMenuItem(), Label::unicode:chardata(). @@ -406,48 +382,197 @@ setText(This,Label) when is_record(This, wx_ref),?is_chardata(Label) -> setItemLabel(This,Label). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmenuitem.html#wxmenuitemsetitemlabel">external documentation</a>. -doc """ Sets the label associated with the menu item. -Note that if the ID of this menu item corresponds to a stock ID, then it is not -necessary to specify a label: wxWidgets will automatically use the stock item -label associated with that ID. See the `new/1` for more info. - -The label string for the normal menu items (not separators) may include the -accelerator which can be used to activate the menu item from keyboard. An -accelerator key can be specified using the ampersand `&` character. In order to -embed an ampersand character in the menu item text, the ampersand must be -doubled. - -Optionally you can specify also an accelerator string appending a tab character -`\t` followed by a valid key combination (e.g. `CTRL+V`). Its general syntax is -any combination of `"CTRL"`, `"RAWCTRL"`, `"ALT"` and `"SHIFT"` strings (case -doesn't matter) separated by either `'-'` or `'+'` characters and followed by -the accelerator itself. Notice that `CTRL` corresponds to the "Ctrl" key on most -platforms but not under macOS where it is mapped to "Cmd" key on Mac keyboard. -Usually this is exactly what you want in portable code but if you really need to -use the (rarely used for this purpose) "Ctrl" key even under Mac, you may use -`RAWCTRL` to prevent this mapping. Under the other platforms `RAWCTRL` is the -same as plain `CTRL`. - -The accelerator may be any alphanumeric character, any function key (from `F1` -to `F12`), any numpad digit key using `KP_` prefix (i.e. from `KP_0` to `KP_9`) -or one of the special strings listed below (again, case doesn't matter) -corresponding to the specified key code: +Note that if the ID of this menu item corresponds to a stock ID, then it is not necessary +to specify a label: wxWidgets will automatically use the stock item label associated with +that ID. See the `new/1` for more info. + +The label string for the normal menu items (not separators) may include the accelerator +which can be used to activate the menu item from keyboard. An accelerator key can be +specified using the ampersand `&` character. In order to embed an ampersand character in +the menu item text, the ampersand must be doubled. + +Optionally you can specify also an accelerator string appending a tab character `\t` +followed by a valid key combination (e.g. `CTRL+V`). Its general syntax is any combination +of `"CTRL"`, `"RAWCTRL"`, `"ALT"` and `"SHIFT"` strings (case doesn't matter) separated by +either `'-'` or `'+'` characters and followed by the accelerator itself. Notice that `CTRL` +corresponds to the "Ctrl" key on most platforms but not under macOS where it is mapped to +"Cmd" key on Mac keyboard. Usually this is exactly what you want in portable code but if +you really need to use the (rarely used for this purpose) "Ctrl" key even under Mac, you +may use `RAWCTRL` to prevent this mapping. Under the other platforms `RAWCTRL` is the same +as plain `CTRL`. + +The accelerator may be any alphanumeric character, any function key (from `F1` to `F12`), +any numpad digit key using `KP_` prefix (i.e. from `KP_0` to `KP_9`) or one of the special +strings listed below (again, case doesn't matter) corresponding to the specified key code: + +* `Del` or `Delete:` WXK_DELETE + +* `Back:` WXK_BACK + +* `Ins` or `Insert:` WXK_INSERT + +* `Enter` or `Return:` WXK_RETURN + +* `PgUp` or `PageUp:` WXK_PAGEUP + +* `PgDn` or `PageDown:` WXK_PAGEDOWN + +* `Left:` WXK_LEFT + +* `Right:` WXK_RIGHT + +* `Up:` WXK_UP + +* `Down:` WXK_DOWN + +* `Home:` WXK_HOME + +* `End:` WXK_END + +* `Space:` WXK_SPACE + +* `Tab:` WXK_TAB + +* `Esc` or `Escape:` WXK_ESCAPE + +* `Cancel:` WXK_CANCEL + +* `Clear:` WXK_CLEAR + +* `Menu:` WXK_MENU + +* `Pause:` WXK_PAUSE + +* `Capital:` WXK_CAPITAL + +* `Select:` WXK_SELECT + +* `Print:` WXK_PRINT + +* `Execute:` WXK_EXECUTE + +* `Snapshot:` WXK_SNAPSHOT + +* `Help:` WXK_HELP + +* `Add:` WXK_ADD + +* `Separator:` WXK_SEPARATOR + +* `Subtract:` WXK_SUBTRACT + +* `Decimal:` WXK_DECIMAL + +* `Divide:` WXK_DIVIDE + +* `Num_lock:` WXK_NUMLOCK + +* `Scroll_lock:` WXK_SCROLL + +* `KP_Space:` WXK_NUMPAD_SPACE + +* `KP_Tab:` WXK_NUMPAD_TAB + +* `KP_Enter:` WXK_NUMPAD_ENTER + +* `KP_Home:` WXK_NUMPAD_HOME + +* `KP_Left:` WXK_NUMPAD_LEFT + +* `KP_Up:` WXK_NUMPAD_UP + +* `KP_Right:` WXK_NUMPAD_RIGHT + +* `KP_Down:` WXK_NUMPAD_DOWN + +* `KP_PageUp:` WXK_NUMPAD_PAGEUP + +* `KP_PageDown:` WXK_NUMPAD_PAGEDOWN + +* `KP_Prior:` WXK_NUMPAD_PAGEUP + +* `KP_Next:` WXK_NUMPAD_PAGEDOWN + +* `KP_End:` WXK_NUMPAD_END + +* `KP_Begin:` WXK_NUMPAD_BEGIN + +* `KP_Insert:` WXK_NUMPAD_INSERT + +* `KP_Delete:` WXK_NUMPAD_DELETE + +* `KP_Equal:` WXK_NUMPAD_EQUAL + +* `KP_Multiply:` WXK_NUMPAD_MULTIPLY + +* `KP_Add:` WXK_NUMPAD_ADD + +* `KP_Separator:` WXK_NUMPAD_SEPARATOR + +* `KP_Subtract:` WXK_NUMPAD_SUBTRACT + +* `KP_Decimal:` WXK_NUMPAD_DECIMAL + +* `KP_Divide:` WXK_NUMPAD_DIVIDE + +* `Windows_Left:` WXK_WINDOWS_LEFT + +* `Windows_Right:` WXK_WINDOWS_RIGHT + +* `Windows_Menu:` WXK_WINDOWS_MENU + +* `Command:` WXK_COMMAND Examples: -Note: In wxGTK using `"SHIFT"` with non-alphabetic characters currently doesn't -work, even in combination with other modifiers, due to GTK+ limitation. E.g. -`Shift+Ctrl+A` works but `Shift+Ctrl+1` or `Shift+/` do not, so avoid using -accelerators of this form in portable code. +Note: In wxGTK using `"SHIFT"` with non-alphabetic characters currently doesn't work, +even in combination with other modifiers, due to GTK+ limitation. E.g. `Shift+Ctrl+A` +works but `Shift+Ctrl+1` or `Shift+/` do not, so avoid using accelerators of this form in +portable code. + +Note: In wxGTk, the left/right/up/down arrow keys do not work as accelerator keys for a +menu item unless a modifier key is used. Additionally, the following keycodes are not +supported as menu accelerator keys: + +* WXK_COMMAND/WXK_CONTROL + +* WXK_SHIFT + +* WXK_ALT + +* WXK_SCROLL + +* WXK_CAPITAL + +* WXK_NUMLOCK + +* WXK_NUMPAD_TAB + +* WXK_TAB + +* WXK_WINDOWS_LEFT + +* WXK_WINDOWS_RIGHT + +* WXK_ADD + +* WXK_SEPARATOR + +* WXK_SUBTRACT + +* WXK_DECIMAL + +* WXK_DIVIDE + +* WXK_SNAPSHOT -Note: In wxGTk, the left/right/up/down arrow keys do not work as accelerator -keys for a menu item unless a modifier key is used. Additionally, the following -keycodes are not supported as menu accelerator keys: +See: +* `getItemLabel/1` -See: `getItemLabel/1`, `getItemLabelText/1` +* `getItemLabelText/1` """. -spec setItemLabel(This, Label) -> 'ok' when This::wxMenuItem(), Label::unicode:chardata(). @@ -457,8 +582,7 @@ setItemLabel(#wx_ref{type=ThisT}=This,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Label_UC,?get_env(),?wxMenuItem_SetItemLabel). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxMenuItem()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMenuItem), diff --git a/lib/wx/src/gen/wxMessageDialog.erl b/lib/wx/src/gen/wxMessageDialog.erl index 96db29a49b52..a8aa5111c77b 100644 --- a/lib/wx/src/gen/wxMessageDialog.erl +++ b/lib/wx/src/gen/wxMessageDialog.erl @@ -20,25 +20,90 @@ -module(wxMessageDialog). -moduledoc """ -Functions for wxMessageDialog class +This class represents a dialog that shows a single or multi-line message, with a choice +of OK, Yes, No and Cancel buttons. -This class represents a dialog that shows a single or multi-line message, with a -choice of OK, Yes, No and Cancel buttons. - -Styles +## Styles This class supports the following styles: -See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_msg) +* wxOK: Puts an Ok button in the message box. May be combined with `wxCANCEL`. + +* wxCANCEL: Puts a Cancel button in the message box. Must be combined with either `wxOK` or `wxYES_NO`. + +* wxYES_NO: Puts Yes and No buttons in the message box. It is recommended to always use `wxCANCEL` +with this style as otherwise the message box won't have a close button under wxMSW and +the user will be forced to answer it. + +* wxHELP: Puts a Help button to the message box. This button can have special appearance or +be specially positioned if its label is not changed from the default one. Notice that +using this button is not supported when showing a message box from non-main thread in +wxOSX/Cocoa. Available since wxWidgets 2.9.3. + +* wxNO_DEFAULT: Makes the "No" button default, can only be used with `wxYES_NO`. + +* wxCANCEL_DEFAULT: Makes the "Cancel" button default, can only be used with `wxCANCEL`. +This style is currently not supported (and ignored) in wxOSX. + +* wxYES_DEFAULT: Makes the "Yes" button default, this is the default behaviour and this +flag exists solely for symmetry with `wxNO_DEFAULT`. + +* wxOK_DEFAULT: Makes the "OK" button default, this is the default behaviour and this flag +exists solely for symmetry with `wxCANCEL_DEFAULT`. + +* wxICON_NONE: Displays no icon in the dialog if possible (an icon might still be displayed +if the current platform mandates its use). This style may be used to prevent the dialog +from using the default icon based on `wxYES_NO` presence as explained in `wxICON_QUESTION` +and `wxICON_INFORMATION` documentation below. + +* wxICON_ERROR: Displays an error icon in the dialog. + +* wxICON_WARNING: Displays a warning icon in the dialog. This style should be used for +informative warnings or, in combination with `wxYES_NO` or `wxCANCEL`, for questions that +have potentially serious consequences (caution icon is used on macOS in this case). + +* wxICON_QUESTION: Displays a question mark symbol. This icon is automatically used with `wxYES_NO` +so it's usually unnecessary to specify it explicitly. This style is not supported for +message dialogs under wxMSW when a task dialog is used to implement them (i.e. when +running under Windows Vista or later) because [Microsoft guidelines](https://docs.microsoft.com/en-us/windows/desktop/uxguide/mess-confirm) +indicate that no icon should be used for routine confirmations. If it is specified, no +icon will be displayed. + +* wxICON_INFORMATION: Displays an information symbol. This icon is used by default if `wxYES_NO` +is not given so it is usually unnecessary to specify it explicitly. + +* wxICON_EXCLAMATION: Alias for `wxICON_WARNING`. + +* wxICON_HAND: Alias for `wxICON_ERROR`. + +* wxICON_AUTH_NEEDED: Displays an authentication needed symbol. This style is only +supported for message dialogs under wxMSW when a task dialog is used to implement them +(i.e. when running under Windows Vista or later). In other cases the default icon +selection logic will be used. Note this can be combined with other styles to provide a +fallback. For instance, using wxICON_AUTH_NEEDED | wxICON_QUESTION will show a shield +symbol on Windows Vista or above and a question symbol on other platforms. Available since +wxWidgets 2.9.5 + +* wxSTAY_ON_TOP: Makes the message box stay on top of all other windows and not only just +its parent (currently implemented only under MSW and GTK). + +* wxCENTRE: Centre the message box on its parent or on the screen if parent is not +specified. Setting this style under MSW makes no differences as the dialog is always +centered on the parent. + +See: [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_msg) + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` -See: `wxRichMessageDialog` (not implemented in wx) +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxMessageDialog](https://docs.wxwidgets.org/3.1/classwx_message_dialog.html) +wxWidgets docs: [wxMessageDialog](https://docs.wxwidgets.org/3.2/classwx_message_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,new/2,new/3]). @@ -90,7 +155,6 @@ wxWidgets docs: -type wxMessageDialog() :: wx:wx_object(). -export_type([wxMessageDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -98,7 +162,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Message, []) +-doc(#{equiv => new(Parent,Message, [])}). -spec new(Parent, Message) -> wxMessageDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(). @@ -106,7 +170,6 @@ new(Parent,Message) when is_record(Parent, wx_ref),?is_chardata(Message) -> new(Parent,Message, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmessagedialog.html#wxmessagedialogwxmessagedialog">external documentation</a>. -doc """ Constructor specifying the message box properties. @@ -114,10 +177,9 @@ Use `wxDialog:showModal/1` to show the dialog. `style` may be a bit list of the identifiers described above. -Notice that not all styles are compatible: only one of `wxOK` and `wxYES_NO` may -be specified (and one of them must be specified) and at most one default button -style can be used and it is only valid if the corresponding button is shown in -the message box. +Notice that not all styles are compatible: only one of `wxOK` and `wxYES_NO` may be +specified (and one of them must be specified) and at most one default button style can be +used and it is only valid if the corresponding button is shown in the message box. """. -spec new(Parent, Message, [Option]) -> wxMessageDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(), @@ -136,659 +198,443 @@ new(#wx_ref{type=ParentT}=Parent,Message, Options) wxe_util:queue_cmd(Parent,Message_UC, Opts,?get_env(),?wxMessageDialog_new), wxe_util:rec(?wxMessageDialog_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxMessageDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMessageDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMiniFrame.erl b/lib/wx/src/gen/wxMiniFrame.erl index 9eba806b54ae..9a9e6a1a2732 100644 --- a/lib/wx/src/gen/wxMiniFrame.erl +++ b/lib/wx/src/gen/wxMiniFrame.erl @@ -20,29 +20,61 @@ -module(wxMiniFrame). -moduledoc """ -Functions for wxMiniFrame class +A miniframe is a frame with a small title bar. -A miniframe is a frame with a small title bar. It is suitable for floating -toolbars that must not take up too much screen area. +It is suitable for floating toolbars that must not take up too much screen area. -An example of mini frame can be seen in the page_samples_dialogs using the "Mini -frame" command of the "Generic dialogs" submenu. +An example of mini frame can be seen in the page_samples_dialogs using the "Mini frame" +command of the "Generic dialogs" submenu. -Styles +## Styles This class supports the following styles: -Remark: This class has miniframe functionality under Windows and GTK, i.e. the -presence of mini frame will not be noted in the task bar and focus behaviour is -different. On other platforms, it behaves like a normal frame. +* wxICONIZE: Display the frame iconized (minimized) (Windows only). -See: `m:wxMDIParentFrame`, `m:wxMDIChildFrame`, `m:wxFrame`, `m:wxDialog` +* wxCAPTION: Puts a caption on the frame. -This class is derived (and can use functions) from: `m:wxFrame` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* wxMINIMIZE: Identical to wxICONIZE. -wxWidgets docs: -[wxMiniFrame](https://docs.wxwidgets.org/3.1/classwx_mini_frame.html) +* wxMINIMIZE_BOX: Displays a minimize box on the frame (Windows and Motif only). + +* wxMAXIMIZE: Displays the frame maximized (Windows only). + +* wxMAXIMIZE_BOX: Displays a maximize box on the frame (Windows and Motif only). + +* wxCLOSE_BOX: Displays a close box on the frame. + +* wxSTAY_ON_TOP: Stay on top of other windows (Windows only). + +* wxSYSTEM_MENU: Displays a system menu (Windows and Motif only). + +* wxRESIZE_BORDER: Displays a resizable border around the window. + +Remark: This class has miniframe functionality under Windows and GTK, i.e. the presence +of mini frame will not be noted in the task bar and focus behaviour is different. On other +platforms, it behaves like a normal frame. + +See: +* `m:wxMDIParentFrame` + +* `m:wxMDIChildFrame` + +* `m:wxFrame` + +* `m:wxDialog` + +This class is derived, and can use functions, from: + +* `m:wxFrame` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxMiniFrame](https://docs.wxwidgets.org/3.2/classwx_mini_frame.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,new/0,new/3,new/4]). @@ -97,7 +129,6 @@ wxWidgets docs: -type wxMiniFrame() :: wx:wx_object(). -export_type([wxMiniFrame/0]). -%% @hidden -doc false. parent_class(wxFrame) -> true; parent_class(wxTopLevelWindow) -> true; @@ -105,14 +136,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxminiframe.html#wxminiframewxminiframe">external documentation</a>. -doc "Default ctor.". -spec new() -> wxMiniFrame(). new() -> wxe_util:queue_cmd(?get_env(), ?wxMiniFrame_new_0), wxe_util:rec(?wxMiniFrame_new_0). -%% @equiv new(Parent,Id,Title, []) +-doc(#{equiv => new(Parent,Id,Title, [])}). -spec new(Parent, Id, Title) -> wxMiniFrame() when Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -120,7 +150,6 @@ new(Parent,Id,Title) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> new(Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxminiframe.html#wxminiframewxminiframe">external documentation</a>. -doc """ Constructor, creating the window. @@ -145,7 +174,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(Parent,Id,Title_UC, Opts,?get_env(),?wxMiniFrame_new_4), wxe_util:rec(?wxMiniFrame_new_4). -%% @equiv create(This,Parent,Id,Title, []) +-doc(#{equiv => create(This,Parent,Id,Title, [])}). -spec create(This, Parent, Id, Title) -> boolean() when This::wxMiniFrame(), Parent::wxWindow:wxWindow(), Id::integer(), Title::unicode:chardata(). @@ -153,7 +182,6 @@ create(This,Parent,Id,Title) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Title) -> create(This,Parent,Id,Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxminiframe.html#wxminiframecreate">external documentation</a>. -doc """ Used in two-step frame construction. @@ -177,693 +205,463 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Title, Options) wxe_util:queue_cmd(This,Parent,Id,Title_UC, Opts,?get_env(),?wxMiniFrame_Create), wxe_util:rec(?wxMiniFrame_Create). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Destroys all child windows and menu bar if present. -""". +-doc "Destroys the object". -spec destroy(This::wxMiniFrame()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMiniFrame), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFrame -%% @hidden -doc false. setToolBar(This,ToolBar) -> wxFrame:setToolBar(This,ToolBar). -%% @hidden -doc false. setStatusWidths(This,Widths_field) -> wxFrame:setStatusWidths(This,Widths_field). -%% @hidden -doc false. setStatusText(This,Text, Options) -> wxFrame:setStatusText(This,Text, Options). -%% @hidden -doc false. setStatusText(This,Text) -> wxFrame:setStatusText(This,Text). -%% @hidden -doc false. setStatusBarPane(This,N) -> wxFrame:setStatusBarPane(This,N). -%% @hidden -doc false. setStatusBar(This,StatusBar) -> wxFrame:setStatusBar(This,StatusBar). -%% @hidden -doc false. setMenuBar(This,MenuBar) -> wxFrame:setMenuBar(This,MenuBar). -%% @hidden -doc false. sendSizeEvent(This, Options) -> wxFrame:sendSizeEvent(This, Options). -%% @hidden -doc false. sendSizeEvent(This) -> wxFrame:sendSizeEvent(This). -%% @hidden -doc false. processCommand(This,Id) -> wxFrame:processCommand(This,Id). -%% @hidden -doc false. getToolBar(This) -> wxFrame:getToolBar(This). -%% @hidden -doc false. getStatusBarPane(This) -> wxFrame:getStatusBarPane(This). -%% @hidden -doc false. getStatusBar(This) -> wxFrame:getStatusBar(This). -%% @hidden -doc false. getMenuBar(This) -> wxFrame:getMenuBar(This). -%% @hidden -doc false. getClientAreaOrigin(This) -> wxFrame:getClientAreaOrigin(This). -%% @hidden -doc false. createToolBar(This, Options) -> wxFrame:createToolBar(This, Options). -%% @hidden -doc false. createToolBar(This) -> wxFrame:createToolBar(This). -%% @hidden -doc false. createStatusBar(This, Options) -> wxFrame:createStatusBar(This, Options). -%% @hidden -doc false. createStatusBar(This) -> wxFrame:createStatusBar(This). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxMirrorDC.erl b/lib/wx/src/gen/wxMirrorDC.erl index c5a6a5a1c11c..e32060a0ab95 100644 --- a/lib/wx/src/gen/wxMirrorDC.erl +++ b/lib/wx/src/gen/wxMirrorDC.erl @@ -20,20 +20,20 @@ -module(wxMirrorDC). -moduledoc """ -Functions for wxMirrorDC class +`m:wxMirrorDC` is a simple wrapper class which is always associated with a real `m:wxDC` +object and either forwards all of its operations to it without changes (no mirroring takes +place) or exchanges `x` and `y` coordinates which makes it possible to reuse the same code +to draw a figure and its mirror -- i.e. -`m:wxMirrorDC` is a simple wrapper class which is always associated with a real -`m:wxDC` object and either forwards all of its operations to it without changes -(no mirroring takes place) or exchanges `x` and `y` coordinates which makes it -possible to reuse the same code to draw a figure and its mirror - i.e. reflection related to the diagonal line x == y. Since: 2.5.0 -This class is derived (and can use functions) from: `m:wxDC` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxMirrorDC](https://docs.wxwidgets.org/3.1/classwx_mirror_d_c.html) +* `m:wxDC` + +wxWidgets docs: [wxMirrorDC](https://docs.wxwidgets.org/3.2/classwx_mirror_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/2]). @@ -62,12 +62,10 @@ wxWidgets docs: -type wxMirrorDC() :: wx:wx_object(). -export_type([wxMirrorDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmirrordc.html#wxmirrordcwxmirrordc">external documentation</a>. -doc """ Creates a (maybe) mirrored DC associated with the real `dc`. @@ -83,287 +81,194 @@ new(#wx_ref{type=DcT}=Dc,Mirror) wxe_util:queue_cmd(Dc,Mirror,?get_env(),?wxMirrorDC_new), wxe_util:rec(?wxMirrorDC_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxMirrorDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMirrorDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxMouseCaptureChangedEvent.erl b/lib/wx/src/gen/wxMouseCaptureChangedEvent.erl index e79ec919b067..674e4818424f 100644 --- a/lib/wx/src/gen/wxMouseCaptureChangedEvent.erl +++ b/lib/wx/src/gen/wxMouseCaptureChangedEvent.erl @@ -20,29 +20,34 @@ -module(wxMouseCaptureChangedEvent). -moduledoc """ -Functions for wxMouseCaptureChangedEvent class - An mouse capture changed event is sent to a window that loses its mouse capture. -This is called even if `wxWindow:releaseMouse/1` was called by the application -code. Handling this event allows an application to cater for unexpected capture -releases which might otherwise confuse mouse handling code. + +This is called even if `wxWindow:releaseMouse/1` was called by the application code. Handling this event allows an +application to cater for unexpected capture releases which might otherwise confuse mouse +handling code. Only for:wxmsw -See: `m:wxMouseCaptureLostEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxWindow:captureMouse/1`, `wxWindow:releaseMouse/1`, `wxWindow:getCapture/0` +See: +* `m:wxMouseCaptureLostEvent` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `wxWindow:captureMouse/1` -This class is derived (and can use functions) from: `m:wxEvent` +* `wxWindow:releaseMouse/1` -wxWidgets docs: -[wxMouseCaptureChangedEvent](https://docs.wxwidgets.org/3.1/classwx_mouse_capture_changed_event.html) +* `wxWindow:getCapture/0` + +This class is derived, and can use functions, from: + +* `m:wxEvent` + +wxWidgets docs: [wxMouseCaptureChangedEvent](https://docs.wxwidgets.org/3.2/classwx_mouse_capture_changed_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxMouseCaptureChangedEventType`](`t:wxMouseCaptureChangedEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxMouseCaptureChangedEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getCapturedWindow/1]). @@ -55,16 +60,11 @@ subscribe to events of this type. -include("wx.hrl"). -type wxMouseCaptureChangedEventType() :: 'mouse_capture_changed'. -export_type([wxMouseCaptureChangedEvent/0, wxMouseCaptureChanged/0, wxMouseCaptureChangedEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmousecapturechangedevent.html#wxmousecapturechangedeventgetcapturedwindow">external documentation</a>. --doc """ -Returns the window that gained the capture, or NULL if it was a non-wxWidgets -window. -""". +-doc "Returns the window that gained the capture, or NULL if it was a non-wxWidgets window.". -spec getCapturedWindow(This) -> wxWindow:wxWindow() when This::wxMouseCaptureChangedEvent(). getCapturedWindow(#wx_ref{type=ThisT}=This) -> @@ -73,30 +73,21 @@ getCapturedWindow(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxMouseCaptureChangedEvent_GetCapturedWindow). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMouseCaptureLostEvent.erl b/lib/wx/src/gen/wxMouseCaptureLostEvent.erl index f6087013ec74..4ac9a23d20f4 100644 --- a/lib/wx/src/gen/wxMouseCaptureLostEvent.erl +++ b/lib/wx/src/gen/wxMouseCaptureLostEvent.erl @@ -20,34 +20,36 @@ -module(wxMouseCaptureLostEvent). -moduledoc """ -Functions for wxMouseCaptureLostEvent class +A mouse capture lost event is sent to a window that had obtained mouse capture, which was +subsequently lost due to an "external" event (for example, when a dialog box is shown or +if another application captures the mouse). -A mouse capture lost event is sent to a window that had obtained mouse capture, -which was subsequently lost due to an "external" event (for example, when a -dialog box is shown or if another application captures the mouse). - -If this happens, this event is sent to all windows that are on the capture stack -(i.e. called CaptureMouse, but didn't call ReleaseMouse yet). The event is not -sent if the capture changes because of a call to CaptureMouse or ReleaseMouse. +If this happens, this event is sent to all windows that are on the capture stack (i.e. +called CaptureMouse, but didn't call ReleaseMouse yet). The event is not sent if the +capture changes because of a call to CaptureMouse or ReleaseMouse. This event is currently emitted under Windows only. -Only for:wxmsw +See: +* `m:wxMouseCaptureChangedEvent` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `wxWindow:captureMouse/1` + +* `wxWindow:releaseMouse/1` + +* `wxWindow:getCapture/0` -See: `m:wxMouseCaptureChangedEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxWindow:captureMouse/1`, `wxWindow:releaseMouse/1`, `wxWindow:getCapture/0` +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxMouseCaptureLostEvent](https://docs.wxwidgets.org/3.1/classwx_mouse_capture_lost_event.html) +wxWidgets docs: [wxMouseCaptureLostEvent](https://docs.wxwidgets.org/3.2/classwx_mouse_capture_lost_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxMouseCaptureLostEventType`](`t:wxMouseCaptureLostEventType/0`) to subscribe -to events of this type. +Use `wxEvtHandler:connect/3` with `wxMouseCaptureLostEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -60,36 +62,26 @@ to events of this type. -include("wx.hrl"). -type wxMouseCaptureLostEventType() :: 'mouse_capture_lost'. -export_type([wxMouseCaptureLostEvent/0, wxMouseCaptureLost/0, wxMouseCaptureLostEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMouseEvent.erl b/lib/wx/src/gen/wxMouseEvent.erl index 69bde9576933..cf213052a598 100644 --- a/lib/wx/src/gen/wxMouseEvent.erl +++ b/lib/wx/src/gen/wxMouseEvent.erl @@ -20,52 +20,44 @@ -module(wxMouseEvent). -moduledoc """ -Functions for wxMouseEvent class - -This event class contains information about the events generated by the mouse: -they include mouse buttons press and release events and mouse move events. - -All mouse events involving the buttons use `wxMOUSE_BTN_LEFT` for the left mouse -button, `wxMOUSE_BTN_MIDDLE` for the middle one and `wxMOUSE_BTN_RIGHT` for the -right one. And if the system supports more buttons, the `wxMOUSE_BTN_AUX1` and -`wxMOUSE_BTN_AUX2` events can also be generated. Note that not all mice have -even a middle button so a portable application should avoid relying on the -events from it (but the right button click can be emulated using the left mouse -button with the control key under Mac platforms with a single button mouse). - -For the `wxEVT_ENTER_WINDOW` and `wxEVT_LEAVE_WINDOW` events purposes, the mouse -is considered to be inside the window if it is in the window client area and not -inside one of its children. In other words, the parent window receives -`wxEVT_LEAVE_WINDOW` event not only when the mouse leaves the window entirely -but also when it enters one of its children. - -The position associated with a mouse event is expressed in the window -coordinates of the window which generated the event, you can use -`wxWindow:clientToScreen/3` to convert it to screen coordinates and possibly -call `wxWindow:screenToClient/2` next to convert it to window coordinates of -another window. - -Note: Note the difference between methods like `leftDown/1` and the inherited -`leftIsDown/1`: the former returns true when the event corresponds to the left -mouse button click while the latter returns true if the left mouse button is -currently being pressed. For example, when the user is dragging the mouse you -can use `leftIsDown/1` to test whether the left mouse button is (still) -depressed. Also, by convention, if `leftDown/1` returns true, `leftIsDown/1` -will also return true in wxWidgets whatever the underlying GUI behaviour is -(which is platform-dependent). The same applies, of course, to other mouse -buttons as well. +This event class contains information about the events generated by the mouse: they +include mouse buttons press and release events and mouse move events. + +All mouse events involving the buttons use `wxMOUSE_BTN_LEFT` for the left mouse button, `wxMOUSE_BTN_MIDDLE` +for the middle one and `wxMOUSE_BTN_RIGHT` for the right one. And if the system supports +more buttons, the `wxMOUSE_BTN_AUX1` and `wxMOUSE_BTN_AUX2` events can also be generated. +Note that not all mice have even a middle button so a portable application should avoid +relying on the events from it (but the right button click can be emulated using the left +mouse button with the control key under Mac platforms with a single button mouse). + +For the `wxEVT_ENTER_WINDOW` and `wxEVT_LEAVE_WINDOW` events purposes, the mouse is +considered to be inside the window if it is in the window client area and not inside one +of its children. In other words, the parent window receives `wxEVT_LEAVE_WINDOW` event not +only when the mouse leaves the window entirely but also when it enters one of its children. + +The position associated with a mouse event is expressed in the window coordinates of the +window which generated the event, you can use `wxWindow:clientToScreen/3` to convert it to screen coordinates and +possibly call `wxWindow:screenToClient/2` next to convert it to window coordinates of another window. + +Note: Note the difference between methods like `leftDown/1` and the inherited `leftIsDown/1`: the former returns +true when the event corresponds to the left mouse button click while the latter returns +true if the left mouse button is currently being pressed. For example, when the user is +dragging the mouse you can use `leftIsDown/1` to test whether the left mouse button is (still) +depressed. Also, by convention, if `leftDown/1` returns true, `leftIsDown/1` will also return true in wxWidgets +whatever the underlying GUI behaviour is (which is platform-dependent). The same applies, +of course, to other mouse buttons as well. See: `m:wxKeyEvent` -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxMouseEvent](https://docs.wxwidgets.org/3.1/classwx_mouse_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxMouseEvent](https://docs.wxwidgets.org/3.2/classwx_mouse_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxMouseEventType`](`t:wxMouseEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxMouseEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([altDown/1,aux1DClick/1,aux1Down/1,aux1Up/1,aux2DClick/1,aux2Down/1, @@ -85,17 +77,14 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxMouseEventType() :: 'left_down' | 'left_up' | 'middle_down' | 'middle_up' | 'right_down' | 'right_up' | 'motion' | 'enter_window' | 'leave_window' | 'left_dclick' | 'middle_dclick' | 'right_dclick' | 'mousewheel' | 'aux1_down' | 'aux1_up' | 'aux1_dclick' | 'aux2_down' | 'aux2_up' | 'aux2_dclick'. -export_type([wxMouseEvent/0, wxMouse/0, wxMouseEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaltdown">external documentation</a>. -doc """ Returns true if the Alt key is pressed. -Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this -one. +Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this one. """. -spec altDown(This) -> boolean() when This::wxMouseEvent(). @@ -104,13 +93,8 @@ altDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_AltDown), wxe_util:rec(?wxMouseEvent_AltDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventbutton">external documentation</a>. -%%<br /> But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX --doc """ -Returns true if the event was generated by the specified button. - -See: wxMouseState::ButtoinIsDown() -""". +-doc "Returns true if the event was generated by the specified button.". +%% But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -spec button(This, But) -> boolean() when This::wxMouseEvent(), But::wx:wx_enum(). button(#wx_ref{type=ThisT}=This,But) @@ -119,7 +103,7 @@ button(#wx_ref{type=ThisT}=This,But) wxe_util:queue_cmd(This,But,?get_env(),?wxMouseEvent_Button), wxe_util:rec(?wxMouseEvent_Button). -%% @equiv buttonDClick(This, []) +-doc(#{equiv => buttonDClick(This, [])}). -spec buttonDClick(This) -> boolean() when This::wxMouseEvent(). @@ -127,15 +111,14 @@ buttonDClick(This) when is_record(This, wx_ref) -> buttonDClick(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventbuttondclick">external documentation</a>. -%%<br /> But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -doc """ -If the argument is omitted, this returns true if the event was a mouse double -click event. +If the argument is omitted, this returns true if the event was a mouse double click +event. -Otherwise the argument specifies which double click event was generated (see -`button/2` for the possible values). +Otherwise the argument specifies which double click event was generated (see `button/2` for the +possible values). """. +%% But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -spec buttonDClick(This, [Option]) -> boolean() when This::wxMouseEvent(), Option :: {'but', wx:wx_enum()}. @@ -148,7 +131,7 @@ buttonDClick(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxMouseEvent_ButtonDClick), wxe_util:rec(?wxMouseEvent_ButtonDClick). -%% @equiv buttonDown(This, []) +-doc(#{equiv => buttonDown(This, [])}). -spec buttonDown(This) -> boolean() when This::wxMouseEvent(). @@ -156,15 +139,13 @@ buttonDown(This) when is_record(This, wx_ref) -> buttonDown(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventbuttondown">external documentation</a>. -%%<br /> But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -doc """ -If the argument is omitted, this returns true if the event was a mouse button -down event. +If the argument is omitted, this returns true if the event was a mouse button down event. -Otherwise the argument specifies which button-down event was generated (see -`button/2` for the possible values). +Otherwise the argument specifies which button-down event was generated (see `button/2` for the +possible values). """. +%% But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -spec buttonDown(This, [Option]) -> boolean() when This::wxMouseEvent(), Option :: {'but', wx:wx_enum()}. @@ -177,7 +158,7 @@ buttonDown(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxMouseEvent_ButtonDown), wxe_util:rec(?wxMouseEvent_ButtonDown). -%% @equiv buttonUp(This, []) +-doc(#{equiv => buttonUp(This, [])}). -spec buttonUp(This) -> boolean() when This::wxMouseEvent(). @@ -185,15 +166,13 @@ buttonUp(This) when is_record(This, wx_ref) -> buttonUp(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventbuttonup">external documentation</a>. -%%<br /> But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -doc """ -If the argument is omitted, this returns true if the event was a mouse button up -event. +If the argument is omitted, this returns true if the event was a mouse button up event. -Otherwise the argument specifies which button-up event was generated (see -`button/2` for the possible values). +Otherwise the argument specifies which button-up event was generated (see `button/2` for the +possible values). """. +%% But = ?wxMOUSE_BTN_ANY | ?wxMOUSE_BTN_NONE | ?wxMOUSE_BTN_LEFT | ?wxMOUSE_BTN_MIDDLE | ?wxMOUSE_BTN_RIGHT | ?wxMOUSE_BTN_AUX1 | ?wxMOUSE_BTN_AUX2 | ?wxMOUSE_BTN_MAX -spec buttonUp(This, [Option]) -> boolean() when This::wxMouseEvent(), Option :: {'but', wx:wx_enum()}. @@ -206,14 +185,12 @@ buttonUp(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxMouseEvent_ButtonUp), wxe_util:rec(?wxMouseEvent_ButtonUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventcmddown">external documentation</a>. -doc """ Returns true if the key used for command accelerators is pressed. Same as `controlDown/1`. Deprecated. -Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this -one. +Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this one. """. -spec cmdDown(This) -> boolean() when This::wxMouseEvent(). @@ -222,14 +199,12 @@ cmdDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_CmdDown), wxe_util:rec(?wxMouseEvent_CmdDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventcontroldown">external documentation</a>. -doc """ Returns true if the Control key or Apple/Command key under macOS is pressed. This function doesn't distinguish between right and left control keys. -Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this -one. +Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this one. """. -spec controlDown(This) -> boolean() when This::wxMouseEvent(). @@ -238,7 +213,6 @@ controlDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_ControlDown), wxe_util:rec(?wxMouseEvent_ControlDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventdragging">external documentation</a>. -doc """ Returns true if this was a dragging event (motion while a button is depressed). @@ -251,7 +225,6 @@ dragging(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Dragging), wxe_util:rec(?wxMouseEvent_Dragging). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseevententering">external documentation</a>. -doc """ Returns true if the mouse was entering the window. @@ -264,14 +237,13 @@ entering(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Entering), wxe_util:rec(?wxMouseEvent_Entering). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetbutton">external documentation</a>. -doc """ -Returns the mouse button which generated this event or `wxMOUSE_BTN_NONE` if no -button is involved (for mouse move, enter or leave event, for example). +Returns the mouse button which generated this event or `wxMOUSE\_BTN\_NONE` if no button +is involved (for mouse move, enter or leave event, for example). -Otherwise `wxMOUSE_BTN_LEFT` is returned for the left button down, up and double -click events, `wxMOUSE_BTN_MIDDLE` and `wxMOUSE_BTN_RIGHT` for the same events -for the middle and the right buttons respectively. +Otherwise `wxMOUSE_BTN_LEFT` is returned for the left button down, up and double click +events, `wxMOUSE_BTN_MIDDLE` and `wxMOUSE_BTN_RIGHT` for the same events for the middle +and the right buttons respectively. """. -spec getButton(This) -> integer() when This::wxMouseEvent(). @@ -280,7 +252,6 @@ getButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetButton), wxe_util:rec(?wxMouseEvent_GetButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetposition">external documentation</a>. -doc "Returns the physical mouse position.". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxMouseEvent(). @@ -289,11 +260,9 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetPosition), wxe_util:rec(?wxMouseEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetlogicalposition">external documentation</a>. -doc """ Returns the logical mouse position in pixels (i.e. translated according to the -translation set for the DC, which usually indicates that the window has been -scrolled). +translation set for the DC, which usually indicates that the window has been scrolled). """. -spec getLogicalPosition(This, Dc) -> {X::integer(), Y::integer()} when This::wxMouseEvent(), Dc::wxDC:wxDC(). @@ -303,14 +272,10 @@ getLogicalPosition(#wx_ref{type=ThisT}=This,#wx_ref{type=DcT}=Dc) -> wxe_util:queue_cmd(This,Dc,?get_env(),?wxMouseEvent_GetLogicalPosition), wxe_util:rec(?wxMouseEvent_GetLogicalPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetlinesperaction">external documentation</a>. -doc """ -Returns the configured number of lines (or whatever) to be scrolled per wheel -action. +Returns the configured number of lines (or whatever) to be scrolled per wheel action. Default value under most platforms is three. - -See: `GetColumnsPerAction()` (not implemented in wx) """. -spec getLinesPerAction(This) -> integer() when This::wxMouseEvent(). @@ -319,16 +284,15 @@ getLinesPerAction(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetLinesPerAction), wxe_util:rec(?wxMouseEvent_GetLinesPerAction). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetwheelrotation">external documentation</a>. -doc """ Get wheel rotation, positive or negative indicates direction of rotation. -Current devices all send an event when rotation is at least +/-WheelDelta, but -finer resolution devices can be created in the future. +Current devices all send an event when rotation is at least +/-WheelDelta, but finer +resolution devices can be created in the future. -Because of this you shouldn't assume that one event is equal to 1 line, but you -should be able to either do partial line scrolling or wait until several events -accumulate before scrolling. +Because of this you shouldn't assume that one event is equal to 1 line, but you should be +able to either do partial line scrolling or wait until several events accumulate before +scrolling. """. -spec getWheelRotation(This) -> integer() when This::wxMouseEvent(). @@ -337,12 +301,11 @@ getWheelRotation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetWheelRotation), wxe_util:rec(?wxMouseEvent_GetWheelRotation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetwheeldelta">external documentation</a>. -doc """ Get wheel delta, normally 120. -This is the threshold for action to be taken, and one such action (for example, -scrolling one increment) should occur for each delta. +This is the threshold for action to be taken, and one such action (for example, scrolling +one increment) should occur for each delta. """. -spec getWheelDelta(This) -> integer() when This::wxMouseEvent(). @@ -351,7 +314,6 @@ getWheelDelta(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetWheelDelta), wxe_util:rec(?wxMouseEvent_GetWheelDelta). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetx">external documentation</a>. -doc "Returns X coordinate of the physical mouse event position.". -spec getX(This) -> integer() when This::wxMouseEvent(). @@ -360,7 +322,6 @@ getX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetX), wxe_util:rec(?wxMouseEvent_GetX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgety">external documentation</a>. -doc "Returns Y coordinate of the physical mouse event position.". -spec getY(This) -> integer() when This::wxMouseEvent(). @@ -369,10 +330,9 @@ getY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetY), wxe_util:rec(?wxMouseEvent_GetY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventisbutton">external documentation</a>. -doc """ -Returns true if the event was a mouse button event (not necessarily a button -down event - that may be tested using `buttonDown/2`). +Returns true if the event was a mouse button event (not necessarily a button down event - +that may be tested using `buttonDown/2`). """. -spec isButton(This) -> boolean() when This::wxMouseEvent(). @@ -381,10 +341,9 @@ isButton(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_IsButton), wxe_util:rec(?wxMouseEvent_IsButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventispagescroll">external documentation</a>. -doc """ -Returns true if the system has been setup to do page scrolling with the mouse -wheel instead of line scrolling. +Returns true if the system has been setup to do page scrolling with the mouse wheel +instead of line scrolling. """. -spec isPageScroll(This) -> boolean() when This::wxMouseEvent(). @@ -393,7 +352,6 @@ isPageScroll(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_IsPageScroll), wxe_util:rec(?wxMouseEvent_IsPageScroll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventleaving">external documentation</a>. -doc """ Returns true if the mouse was leaving the window. @@ -406,7 +364,6 @@ leaving(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Leaving), wxe_util:rec(?wxMouseEvent_Leaving). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventleftdclick">external documentation</a>. -doc "Returns true if the event was a left double click.". -spec leftDClick(This) -> boolean() when This::wxMouseEvent(). @@ -415,7 +372,6 @@ leftDClick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_LeftDClick), wxe_util:rec(?wxMouseEvent_LeftDClick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventleftdown">external documentation</a>. -doc "Returns true if the left mouse button changed to down.". -spec leftDown(This) -> boolean() when This::wxMouseEvent(). @@ -424,7 +380,6 @@ leftDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_LeftDown), wxe_util:rec(?wxMouseEvent_LeftDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventleftisdown">external documentation</a>. -doc "Returns true if the left mouse button is currently down.". -spec leftIsDown(This) -> boolean() when This::wxMouseEvent(). @@ -433,7 +388,6 @@ leftIsDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_LeftIsDown), wxe_util:rec(?wxMouseEvent_LeftIsDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventleftup">external documentation</a>. -doc "Returns true if the left mouse button changed to up.". -spec leftUp(This) -> boolean() when This::wxMouseEvent(). @@ -442,7 +396,6 @@ leftUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_LeftUp), wxe_util:rec(?wxMouseEvent_LeftUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmetadown">external documentation</a>. -doc "Returns true if the Meta key was down at the time of the event.". -spec metaDown(This) -> boolean() when This::wxMouseEvent(). @@ -451,7 +404,6 @@ metaDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_MetaDown), wxe_util:rec(?wxMouseEvent_MetaDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmiddledclick">external documentation</a>. -doc "Returns true if the event was a middle double click.". -spec middleDClick(This) -> boolean() when This::wxMouseEvent(). @@ -460,7 +412,6 @@ middleDClick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_MiddleDClick), wxe_util:rec(?wxMouseEvent_MiddleDClick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmiddledown">external documentation</a>. -doc "Returns true if the middle mouse button changed to down.". -spec middleDown(This) -> boolean() when This::wxMouseEvent(). @@ -469,7 +420,6 @@ middleDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_MiddleDown), wxe_util:rec(?wxMouseEvent_MiddleDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmiddleisdown">external documentation</a>. -doc "Returns true if the middle mouse button is currently down.". -spec middleIsDown(This) -> boolean() when This::wxMouseEvent(). @@ -478,7 +428,6 @@ middleIsDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_MiddleIsDown), wxe_util:rec(?wxMouseEvent_MiddleIsDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmiddleup">external documentation</a>. -doc "Returns true if the middle mouse button changed to up.". -spec middleUp(This) -> boolean() when This::wxMouseEvent(). @@ -487,12 +436,10 @@ middleUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_MiddleUp), wxe_util:rec(?wxMouseEvent_MiddleUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventmoving">external documentation</a>. -doc """ Returns true if this was a motion event and no mouse buttons were pressed. -If any mouse button is held pressed, then this method returns false and -`dragging/1` returns true. +If any mouse button is held pressed, then this method returns false and `dragging/1` returns true. """. -spec moving(This) -> boolean() when This::wxMouseEvent(). @@ -501,7 +448,6 @@ moving(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Moving), wxe_util:rec(?wxMouseEvent_Moving). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventrightdclick">external documentation</a>. -doc "Returns true if the event was a right double click.". -spec rightDClick(This) -> boolean() when This::wxMouseEvent(). @@ -510,7 +456,6 @@ rightDClick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_RightDClick), wxe_util:rec(?wxMouseEvent_RightDClick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventrightdown">external documentation</a>. -doc "Returns true if the right mouse button changed to down.". -spec rightDown(This) -> boolean() when This::wxMouseEvent(). @@ -519,7 +464,6 @@ rightDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_RightDown), wxe_util:rec(?wxMouseEvent_RightDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventrightisdown">external documentation</a>. -doc "Returns true if the right mouse button is currently down.". -spec rightIsDown(This) -> boolean() when This::wxMouseEvent(). @@ -528,7 +472,6 @@ rightIsDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_RightIsDown), wxe_util:rec(?wxMouseEvent_RightIsDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventrightup">external documentation</a>. -doc "Returns true if the right mouse button changed to up.". -spec rightUp(This) -> boolean() when This::wxMouseEvent(). @@ -537,14 +480,12 @@ rightUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_RightUp), wxe_util:rec(?wxMouseEvent_RightUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventshiftdown">external documentation</a>. -doc """ Returns true if the Shift key is pressed. This function doesn't distinguish between right and left shift keys. -Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this -one. +Notice that `wxKeyEvent:getModifiers/1` should usually be used instead of this one. """. -spec shiftDown(This) -> boolean() when This::wxMouseEvent(). @@ -553,17 +494,16 @@ shiftDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_ShiftDown), wxe_util:rec(?wxMouseEvent_ShiftDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventgetwheelaxis">external documentation</a>. -%%<br /> Res = ?wxMOUSE_WHEEL_VERTICAL | ?wxMOUSE_WHEEL_HORIZONTAL -doc """ Gets the axis the wheel operation concerns. -Usually the mouse wheel is used to scroll vertically so `wxMOUSE_WHEEL_VERTICAL` -is returned but some mice (and most trackpads) also allow to use the wheel to -scroll horizontally in which case `wxMOUSE_WHEEL_HORIZONTAL` is returned. +Usually the mouse wheel is used to scroll vertically so `wxMOUSE_WHEEL_VERTICAL` is +returned but some mice (and most trackpads) also allow to use the wheel to scroll +horizontally in which case `wxMOUSE_WHEEL_HORIZONTAL` is returned. Notice that before wxWidgets 2.9.4 this method returned `int`. """. +%% Res = ?wxMOUSE_WHEEL_VERTICAL | ?wxMOUSE_WHEEL_HORIZONTAL -spec getWheelAxis(This) -> wx:wx_enum() when This::wxMouseEvent(). getWheelAxis(#wx_ref{type=ThisT}=This) -> @@ -571,7 +511,6 @@ getWheelAxis(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_GetWheelAxis), wxe_util:rec(?wxMouseEvent_GetWheelAxis). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux1dclick">external documentation</a>. -doc "Returns true if the event was a first extra button double click.". -spec aux1DClick(This) -> boolean() when This::wxMouseEvent(). @@ -580,7 +519,6 @@ aux1DClick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Aux1DClick), wxe_util:rec(?wxMouseEvent_Aux1DClick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux1down">external documentation</a>. -doc "Returns true if the first extra button mouse button changed to down.". -spec aux1Down(This) -> boolean() when This::wxMouseEvent(). @@ -589,7 +527,6 @@ aux1Down(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Aux1Down), wxe_util:rec(?wxMouseEvent_Aux1Down). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux1up">external documentation</a>. -doc "Returns true if the first extra button mouse button changed to up.". -spec aux1Up(This) -> boolean() when This::wxMouseEvent(). @@ -598,7 +535,6 @@ aux1Up(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Aux1Up), wxe_util:rec(?wxMouseEvent_Aux1Up). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux2dclick">external documentation</a>. -doc "Returns true if the event was a second extra button double click.". -spec aux2DClick(This) -> boolean() when This::wxMouseEvent(). @@ -607,7 +543,6 @@ aux2DClick(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Aux2DClick), wxe_util:rec(?wxMouseEvent_Aux2DClick). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux2down">external documentation</a>. -doc "Returns true if the second extra button mouse button changed to down.". -spec aux2Down(This) -> boolean() when This::wxMouseEvent(). @@ -616,7 +551,6 @@ aux2Down(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMouseEvent_Aux2Down), wxe_util:rec(?wxMouseEvent_Aux2Down). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmouseevent.html#wxmouseeventaux2up">external documentation</a>. -doc "Returns true if the second extra button mouse button changed to up.". -spec aux2Up(This) -> boolean() when This::wxMouseEvent(). @@ -626,30 +560,21 @@ aux2Up(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxMouseEvent_Aux2Up). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMoveEvent.erl b/lib/wx/src/gen/wxMoveEvent.erl index f42fdd9b75e9..327c6af57dce 100644 --- a/lib/wx/src/gen/wxMoveEvent.erl +++ b/lib/wx/src/gen/wxMoveEvent.erl @@ -20,25 +20,25 @@ -module(wxMoveEvent). -moduledoc """ -Functions for wxMoveEvent class - A move event holds information about window position change. -These events are currently generated for top level (see `m:wxTopLevelWindow`) -windows in all ports, but are not generated for the child windows in wxGTK. +These events are currently generated for top level (see `m:wxTopLevelWindow`) windows in +all ports, but are not generated for the child windows in wxGTK. + +See: +* {X,Y} + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: \{X,Y\}, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxMoveEvent](https://docs.wxwidgets.org/3.1/classwx_move_event.html) +wxWidgets docs: [wxMoveEvent](https://docs.wxwidgets.org/3.2/classwx_move_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxMoveEventType`](`t:wxMoveEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxMoveEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getPosition/1,getRect/1]). @@ -51,12 +51,10 @@ subscribe to events of this type. -include("wx.hrl"). -type wxMoveEventType() :: 'move'. -export_type([wxMoveEvent/0, wxMove/0, wxMoveEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmoveevent.html#wxmoveeventgetposition">external documentation</a>. -doc "Returns the position of the window generating the move change event.". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxMoveEvent(). @@ -65,7 +63,7 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMoveEvent_GetPosition), wxe_util:rec(?wxMoveEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmoveevent.html#wxmoveeventgetrect">external documentation</a>. +-doc "". -spec getRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxMoveEvent(). getRect(#wx_ref{type=ThisT}=This) -> @@ -74,30 +72,21 @@ getRect(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxMoveEvent_GetRect). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxMultiChoiceDialog.erl b/lib/wx/src/gen/wxMultiChoiceDialog.erl index f85449fffe92..0a2caa0f0e16 100644 --- a/lib/wx/src/gen/wxMultiChoiceDialog.erl +++ b/lib/wx/src/gen/wxMultiChoiceDialog.erl @@ -20,24 +20,35 @@ -module(wxMultiChoiceDialog). -moduledoc """ -Functions for wxMultiChoiceDialog class +This class represents a dialog that shows a list of strings, and allows the user to +select one or more. -This class represents a dialog that shows a list of strings, and allows the user -to select one or more. - -Styles +## Styles This class supports the following styles: +* wxOK: Show an OK button. + +* wxCANCEL: Show a Cancel button. + +* wxCENTRE: Centre the message. + See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_multichoice), -`m:wxSingleChoiceDialog` +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_multichoice) + +* `m:wxSingleChoiceDialog` + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxMultiChoiceDialog](https://docs.wxwidgets.org/3.1/classwx_multi_choice_dialog.html) +wxWidgets docs: [wxMultiChoiceDialog](https://docs.wxwidgets.org/3.2/classwx_multi_choice_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getSelections/1,new/4,new/5,setSelections/2]). @@ -89,7 +100,6 @@ wxWidgets docs: -type wxMultiChoiceDialog() :: wx:wx_object(). -export_type([wxMultiChoiceDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -97,7 +107,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Message,Caption,Choices, []) +-doc(#{equiv => new(Parent,Message,Caption,Choices, [])}). -spec new(Parent, Message, Caption, Choices) -> wxMultiChoiceDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(), Caption::unicode:chardata(), Choices::[unicode:chardata()]. @@ -105,7 +115,6 @@ new(Parent,Message,Caption,Choices) when is_record(Parent, wx_ref),?is_chardata(Message),?is_chardata(Caption),is_list(Choices) -> new(Parent,Message,Caption,Choices, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmultichoicedialog.html#wxmultichoicedialogwxmultichoicedialog">external documentation</a>. -doc """ Constructor taking an array of `wxString` (not implemented in wx) choices. @@ -129,7 +138,6 @@ new(#wx_ref{type=ParentT}=Parent,Message,Caption,Choices, Options) wxe_util:queue_cmd(Parent,Message_UC,Caption_UC,Choices_UCA, Opts,?get_env(),?wxMultiChoiceDialog_new), wxe_util:rec(?wxMultiChoiceDialog_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmultichoicedialog.html#wxmultichoicedialoggetselections">external documentation</a>. -doc "Returns array with indexes of selected items.". -spec getSelections(This) -> [integer()] when This::wxMultiChoiceDialog(). @@ -138,7 +146,6 @@ getSelections(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxMultiChoiceDialog_GetSelections), wxe_util:rec(?wxMultiChoiceDialog_GetSelections). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxmultichoicedialog.html#wxmultichoicedialogsetselections">external documentation</a>. -doc "Sets selected items from the array of selected items' indexes.". -spec setSelections(This, Selections) -> 'ok' when This::wxMultiChoiceDialog(), Selections::[integer()]. @@ -147,659 +154,443 @@ setSelections(#wx_ref{type=ThisT}=This,Selections) ?CLASS(ThisT,wxMultiChoiceDialog), wxe_util:queue_cmd(This,Selections,?get_env(),?wxMultiChoiceDialog_SetSelections). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxMultiChoiceDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxMultiChoiceDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxNavigationKeyEvent.erl b/lib/wx/src/gen/wxNavigationKeyEvent.erl index 6f6295e50953..7c1477097532 100644 --- a/lib/wx/src/gen/wxNavigationKeyEvent.erl +++ b/lib/wx/src/gen/wxNavigationKeyEvent.erl @@ -20,28 +20,24 @@ -module(wxNavigationKeyEvent). -moduledoc """ -Functions for wxNavigationKeyEvent class +This event class contains information about navigation events, generated by navigation +keys such as tab and page down. -This event class contains information about navigation events, generated by -navigation keys such as tab and page down. +This event is mainly used by wxWidgets implementations. A `m:wxNavigationKeyEvent` +handler is automatically provided by wxWidgets when you enable keyboard navigation inside +a window by inheriting it from wxNavigationEnabled<>. -This event is mainly used by wxWidgets implementations. A -`m:wxNavigationKeyEvent` handler is automatically provided by wxWidgets when you -enable keyboard navigation inside a window by inheriting it from -wxNavigationEnabled<>. +See: `wxWindow:navigate/2` -See: `wxWindow:navigate/2`, `wxWindow::NavigateIn` (not implemented in wx) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxNavigationKeyEvent](https://docs.wxwidgets.org/3.1/classwx_navigation_key_event.html) +wxWidgets docs: [wxNavigationKeyEvent](https://docs.wxwidgets.org/3.2/classwx_navigation_key_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxNavigationKeyEventType`](`t:wxNavigationKeyEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxNavigationKeyEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getCurrentFocus/1,getDirection/1,isFromTab/1,isWindowChange/1,setCurrentFocus/2, @@ -55,12 +51,10 @@ events of this type. -include("wx.hrl"). -type wxNavigationKeyEventType() :: 'navigation_key'. -export_type([wxNavigationKeyEvent/0, wxNavigationKey/0, wxNavigationKeyEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventgetdirection">external documentation</a>. -doc "Returns true if the navigation was in the forward direction.". -spec getDirection(This) -> boolean() when This::wxNavigationKeyEvent(). @@ -69,7 +63,6 @@ getDirection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNavigationKeyEvent_GetDirection), wxe_util:rec(?wxNavigationKeyEvent_GetDirection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventsetdirection">external documentation</a>. -doc "Sets the direction to forward if `direction` is true, or backward if false.". -spec setDirection(This, Direction) -> 'ok' when This::wxNavigationKeyEvent(), Direction::boolean(). @@ -78,10 +71,9 @@ setDirection(#wx_ref{type=ThisT}=This,Direction) ?CLASS(ThisT,wxNavigationKeyEvent), wxe_util:queue_cmd(This,Direction,?get_env(),?wxNavigationKeyEvent_SetDirection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventiswindowchange">external documentation</a>. -doc """ -Returns true if the navigation event represents a window change (for example, -from Ctrl-Page Down in a notebook). +Returns true if the navigation event represents a window change (for example, from +Ctrl-Page Down in a notebook). """. -spec isWindowChange(This) -> boolean() when This::wxNavigationKeyEvent(). @@ -90,7 +82,6 @@ isWindowChange(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNavigationKeyEvent_IsWindowChange), wxe_util:rec(?wxNavigationKeyEvent_IsWindowChange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventsetwindowchange">external documentation</a>. -doc "Marks the event as a window change event.". -spec setWindowChange(This, WindowChange) -> 'ok' when This::wxNavigationKeyEvent(), WindowChange::boolean(). @@ -99,7 +90,6 @@ setWindowChange(#wx_ref{type=ThisT}=This,WindowChange) ?CLASS(ThisT,wxNavigationKeyEvent), wxe_util:queue_cmd(This,WindowChange,?get_env(),?wxNavigationKeyEvent_SetWindowChange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventisfromtab">external documentation</a>. -doc """ Returns true if the navigation event was from a tab key. @@ -112,7 +102,6 @@ isFromTab(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNavigationKeyEvent_IsFromTab), wxe_util:rec(?wxNavigationKeyEvent_IsFromTab). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventsetfromtab">external documentation</a>. -doc "Marks the navigation event as from a tab key.". -spec setFromTab(This, FromTab) -> 'ok' when This::wxNavigationKeyEvent(), FromTab::boolean(). @@ -121,7 +110,6 @@ setFromTab(#wx_ref{type=ThisT}=This,FromTab) ?CLASS(ThisT,wxNavigationKeyEvent), wxe_util:queue_cmd(This,FromTab,?get_env(),?wxNavigationKeyEvent_SetFromTab). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventgetcurrentfocus">external documentation</a>. -doc "Returns the child that has the focus, or NULL.". -spec getCurrentFocus(This) -> wxWindow:wxWindow() when This::wxNavigationKeyEvent(). @@ -130,7 +118,6 @@ getCurrentFocus(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNavigationKeyEvent_GetCurrentFocus), wxe_util:rec(?wxNavigationKeyEvent_GetCurrentFocus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnavigationkeyevent.html#wxnavigationkeyeventsetcurrentfocus">external documentation</a>. -doc "Sets the current focus window member.". -spec setCurrentFocus(This, CurrentFocus) -> 'ok' when This::wxNavigationKeyEvent(), CurrentFocus::wxWindow:wxWindow(). @@ -140,30 +127,21 @@ setCurrentFocus(#wx_ref{type=ThisT}=This,#wx_ref{type=CurrentFocusT}=CurrentFocu wxe_util:queue_cmd(This,CurrentFocus,?get_env(),?wxNavigationKeyEvent_SetCurrentFocus). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxNotebook.erl b/lib/wx/src/gen/wxNotebook.erl index 9976007389a5..6f69a59153d2 100644 --- a/lib/wx/src/gen/wxNotebook.erl +++ b/lib/wx/src/gen/wxNotebook.erl @@ -20,54 +20,79 @@ -module(wxNotebook). -moduledoc """ -Functions for wxNotebook class +This class represents a notebook control, which manages multiple windows with associated +tabs. -This class represents a notebook control, which manages multiple windows with -associated tabs. - -To use the class, create a `m:wxNotebook` object and call -`wxBookCtrlBase:addPage/4` or `wxBookCtrlBase:insertPage/5`, passing a window to -be used as the page. Do not explicitly delete the window for a page that is -currently managed by `m:wxNotebook`. +To use the class, create a `m:wxNotebook` object and call `wxBookCtrlBase:addPage/4` or `wxBookCtrlBase:insertPage/5`, passing a window to be +used as the page. Do not explicitly delete the window for a page that is currently managed +by `m:wxNotebook`. `wxNotebookPage` is a typedef for `m:wxWindow`. -Styles +## Styles This class supports the following styles: +* wxNB_TOP: Place tabs on the top side. + +* wxNB_LEFT: Place tabs on the left side. + +* wxNB_RIGHT: Place tabs on the right side. + +* wxNB_BOTTOM: Place tabs under instead of above the notebook pages. + +* wxNB_FIXEDWIDTH: (Windows only) All tabs will have same width. + +* wxNB_MULTILINE: (Windows only) There can be several rows of tabs. + +* wxNB_NOPAGETHEME: (Windows only) Display a solid colour on notebook pages, and not a +gradient, which can reduce performance. The styles wxNB_LEFT, RIGHT and BOTTOM are not +supported under Microsoft Windows when using visual themes. + Page backgrounds -On Windows, the default theme paints a background on the notebook's pages. If -you wish to suppress this theme, for aesthetic or performance reasons, there are -three ways of doing it. You can use `wxNB_NOPAGETHEME` to disable themed drawing -for a particular notebook, you can call `wxSystemOptions:setOption/2` to disable -it for the whole application, or you can disable it for individual pages by -using `wxWindow:setBackgroundColour/2`. +On Windows, the default theme paints a background on the notebook's pages. If you wish to +suppress this theme, for aesthetic or performance reasons, there are three ways of doing +it. You can use `wxNB_NOPAGETHEME` to disable themed drawing for a particular notebook, +you can call `wxSystemOptions:setOption/2` to disable it for the whole application, or you can disable it for +individual pages by using `wxWindow:setBackgroundColour/2`. To disable themed pages globally: -Set the value to 1 to enable it again. To give a single page a solid background -that more or less fits in with the overall theme, use: +Set the value to 1 to enable it again. To give a single page a solid background that more +or less fits in with the overall theme, use: + +On platforms other than Windows, or if the application is not using Windows themes, `getThemeBackgroundColour/1` will +return an uninitialised colour object, and the above code will therefore work on all platforms. + +See: +* ?wxBookCtrl -On platforms other than Windows, or if the application is not using Windows -themes, `getThemeBackgroundColour/1` will return an uninitialised colour object, -and the above code will therefore work on all platforms. +* `m:wxBookCtrlEvent` -See: ?wxBookCtrl, `m:wxBookCtrlEvent`, `m:wxImageList`, -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_notebook) +* `m:wxImageList` -This class is derived (and can use functions) from: `m:wxBookCtrlBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_notebook) -wxWidgets docs: -[wxNotebook](https://docs.wxwidgets.org/3.1/classwx_notebook.html) +This class is derived, and can use functions, from: + +* `m:wxBookCtrlBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxNotebook](https://docs.wxwidgets.org/3.2/classwx_notebook.html) ## Events Event types emitted from this class: -[`command_notebook_page_changed`](`m:wxBookCtrlEvent`), -[`command_notebook_page_changing`](`m:wxBookCtrlEvent`) + +* [`command_notebook_page_changed`](`m:wxBookCtrlEvent`) + +* [`command_notebook_page_changing`](`m:wxBookCtrlEvent`) """. -include("wxe.hrl"). -export([assignImageList/2,create/3,create/4,destroy/1,getImageList/1,getPageImage/2, @@ -118,7 +143,6 @@ Event types emitted from this class: -type wxNotebook() :: wx:wx_object(). -export_type([wxNotebook/0]). -%% @hidden -doc false. parent_class(wxBookCtrlBase) -> true; parent_class(wxControl) -> true; @@ -126,14 +150,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookwxnotebook">external documentation</a>. -doc "Constructs a notebook control.". -spec new() -> wxNotebook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxNotebook_new_0), wxe_util:rec(?wxNotebook_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxNotebook() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -141,12 +164,10 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookwxnotebook">external documentation</a>. -doc """ Constructs a notebook control. -Note that sometimes you can reduce flicker by passing the wxCLIP_CHILDREN window -style. +Note that sometimes you can reduce flicker by passing the wxCLIP_CHILDREN window style. """. -spec new(Parent, Id, [Option]) -> wxNotebook() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -164,11 +185,13 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxNotebook_new_3), wxe_util:rec(?wxNotebook_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookassignimagelist">external documentation</a>. -doc """ Sets the image list for the page control and takes ownership of the list. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec assignImageList(This, ImageList) -> 'ok' when This::wxNotebook(), ImageList::wxImageList:wxImageList(). @@ -177,7 +200,7 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxNotebook_AssignImageList). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxNotebook(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -185,7 +208,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookcreate">external documentation</a>. -doc """ Creates a notebook control. @@ -208,11 +230,13 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxNotebook_Create), wxe_util:rec(?wxNotebook_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookgetimagelist">external documentation</a>. -doc """ Returns the associated image list, may be NULL. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec getImageList(This) -> wxImageList:wxImageList() when This::wxNotebook(). @@ -221,7 +245,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotebook_GetImageList), wxe_util:rec(?wxNotebook_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookgetpageimage">external documentation</a>. -doc "Returns the image index for the given page.". -spec getPageImage(This, NPage) -> integer() when This::wxNotebook(), NPage::integer(). @@ -231,7 +254,6 @@ getPageImage(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxNotebook_GetPageImage), wxe_util:rec(?wxNotebook_GetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookgetrowcount">external documentation</a>. -doc "Returns the number of rows in the notebook control.". -spec getRowCount(This) -> integer() when This::wxNotebook(). @@ -240,11 +262,10 @@ getRowCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotebook_GetRowCount), wxe_util:rec(?wxNotebook_GetRowCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebookgetthemebackgroundcolour">external documentation</a>. -doc """ -If running under Windows and themes are enabled for the application, this -function returns a suitable colour for painting the background of a notebook -page, and can be passed to `wxWindow:setBackgroundColour/2`. +If running under Windows and themes are enabled for the application, this function +returns a suitable colour for painting the background of a notebook page, and can be +passed to `wxWindow:setBackgroundColour/2`. Otherwise, an uninitialised colour will be returned. """. @@ -255,13 +276,15 @@ getThemeBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotebook_GetThemeBackgroundColour), wxe_util:rec(?wxNotebook_GetThemeBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebooksetimagelist">external documentation</a>. -doc """ Sets the image list to use. It does not take ownership of the image list, you must delete it yourself. -See: `m:wxImageList`, `assignImageList/2` +See: +* `m:wxImageList` + +* `assignImageList/2` """. -spec setImageList(This, ImageList) -> 'ok' when This::wxNotebook(), ImageList::wxImageList:wxImageList(). @@ -270,7 +293,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxNotebook_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebooksetpadding">external documentation</a>. -doc """ Sets the amount of space around each page's icon and label, in pixels. @@ -283,7 +305,6 @@ setPadding(#wx_ref{type=ThisT}=This,{PaddingW,PaddingH} = Padding) ?CLASS(ThisT,wxNotebook), wxe_util:queue_cmd(This,Padding,?get_env(),?wxNotebook_SetPadding). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebooksetpagesize">external documentation</a>. -doc """ Sets the width and height of the pages. @@ -296,7 +317,6 @@ setPageSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxNotebook), wxe_util:queue_cmd(This,Size,?get_env(),?wxNotebook_SetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotebook.html#wxnotebooksetpageimage">external documentation</a>. -doc """ Sets the image index for the given page. @@ -310,617 +330,415 @@ setPageImage(#wx_ref{type=ThisT}=This,Page,Image) wxe_util:queue_cmd(This,Page,Image,?get_env(),?wxNotebook_SetPageImage), wxe_util:rec(?wxNotebook_SetPageImage). -%% @doc Destroys this object, do not use object again --doc "Destroys the `m:wxNotebook` object.". +-doc "Destroys the object". -spec destroy(This::wxNotebook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxNotebook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBookCtrlBase -%% @hidden -doc false. setPageText(This,Page,Text) -> wxBookCtrlBase:setPageText(This,Page,Text). -%% @hidden -doc false. getPageText(This,NPage) -> wxBookCtrlBase:getPageText(This,NPage). -%% @hidden -doc false. hitTest(This,Pt) -> wxBookCtrlBase:hitTest(This,Pt). -%% @hidden -doc false. changeSelection(This,Page) -> wxBookCtrlBase:changeSelection(This,Page). -%% @hidden -doc false. getSelection(This) -> wxBookCtrlBase:getSelection(This). -%% @hidden -doc false. setSelection(This,Page) -> wxBookCtrlBase:setSelection(This,Page). -%% @hidden -doc false. advanceSelection(This, Options) -> wxBookCtrlBase:advanceSelection(This, Options). -%% @hidden -doc false. advanceSelection(This) -> wxBookCtrlBase:advanceSelection(This). -%% @hidden -doc false. getCurrentPage(This) -> wxBookCtrlBase:getCurrentPage(This). -%% @hidden -doc false. getPageCount(This) -> wxBookCtrlBase:getPageCount(This). -%% @hidden -doc false. getPage(This,Page) -> wxBookCtrlBase:getPage(This,Page). -%% @hidden -doc false. deleteAllPages(This) -> wxBookCtrlBase:deleteAllPages(This). -%% @hidden -doc false. removePage(This,Page) -> wxBookCtrlBase:removePage(This,Page). -%% @hidden -doc false. deletePage(This,Page) -> wxBookCtrlBase:deletePage(This,Page). -%% @hidden -doc false. insertPage(This,Index,Page,Text, Options) -> wxBookCtrlBase:insertPage(This,Index,Page,Text, Options). -%% @hidden -doc false. insertPage(This,Index,Page,Text) -> wxBookCtrlBase:insertPage(This,Index,Page,Text). -%% @hidden -doc false. addPage(This,Page,Text, Options) -> wxBookCtrlBase:addPage(This,Page,Text, Options). -%% @hidden -doc false. addPage(This,Page,Text) -> wxBookCtrlBase:addPage(This,Page,Text). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxNotificationMessage.erl b/lib/wx/src/gen/wxNotificationMessage.erl index d55790da1e55..5eab8ddb5602 100644 --- a/lib/wx/src/gen/wxNotificationMessage.erl +++ b/lib/wx/src/gen/wxNotificationMessage.erl @@ -20,47 +20,49 @@ -module(wxNotificationMessage). -moduledoc """ -Functions for wxNotificationMessage class - This class allows showing the user a message non intrusively. -Currently it is implemented natively for Windows, macOS, GTK and uses generic -toast notifications under the other platforms. It's not recommended but -`wxGenericNotificationMessage` can be used instead of the native ones. This -might make sense if your application requires features not available in the -native implementation. +Currently it is implemented natively for Windows, macOS, GTK and uses generic toast +notifications under the other platforms. It's not recommended but `wxGenericNotificationMessage` +can be used instead of the native ones. This might make sense if your application +requires features not available in the native implementation. Notice that this class is not a window and so doesn't derive from `m:wxWindow`. Platform Notes -Par: Up to Windows 8 balloon notifications are displayed from an icon in the -notification area of the taskbar. If your application uses a `m:wxTaskBarIcon` -you should call `useTaskBarIcon/1` to ensure that only one icon is shown in the -notification area. Windows 10 displays all notifications as popup toasts. To -suppress the additional icon in the notification area on Windows 10 and for -toast notification support on Windows 8 it is recommended to call -`mSWUseToasts/1` before showing the first notification message. +Par: + +Up to Windows 8 balloon notifications are displayed from an icon in the notification area +of the taskbar. If your application uses a `m:wxTaskBarIcon` you should call `useTaskBarIcon/1` to ensure +that only one icon is shown in the notification area. Windows 10 displays all +notifications as popup toasts. To suppress the additional icon in the notification area on +Windows 10 and for toast notification support on Windows 8 it is recommended to call `mSWUseToasts/1` +before showing the first notification message. + +Par: -Par: The macOS implementation uses Notification Center to display native -notifications. In order to use actions your notifications must use the alert -style. This can be enabled by the user in system settings or by setting the -`NSUserNotificationAlertStyle` value in Info.plist to `alert`. Please note that -the user always has the option to change the notification style. +The macOS implementation uses Notification Center to display native notifications. In +order to use actions your notifications must use the alert style. This can be enabled by +the user in system settings or by setting the `NSUserNotificationAlertStyle` value in +Info.plist to `alert`. Please note that the user always has the option to change the +notification style. -Since: 2.9.0 +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxNotificationMessage](https://docs.wxwidgets.org/3.1/classwx_notification_message.html) +wxWidgets docs: [wxNotificationMessage](https://docs.wxwidgets.org/3.2/classwx_notification_message.html) ## Events Event types emitted from this class: -[`notification_message_click`](`m:wxCommandEvent`), -[`notification_message_dismissed`](`m:wxCommandEvent`), -[`notification_message_action`](`m:wxCommandEvent`) + +* [`notification_message_click`](`m:wxCommandEvent`) + +* [`notification_message_dismissed`](`m:wxCommandEvent`) + +* [`notification_message_action`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([addAction/2,addAction/3,close/1,destroy/1,mSWUseToasts/0,mSWUseToasts/1, @@ -72,22 +74,20 @@ Event types emitted from this class: -type wxNotificationMessage() :: wx:wx_object(). -export_type([wxNotificationMessage/0]). -%% @hidden -doc false. parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagewxnotificationmessage">external documentation</a>. -doc """ -Default constructor, use `setParent/2`, `setTitle/2` and `setMessage/2` to -initialize the object before showing it. +Default constructor, use `setParent/2`, `setTitle/2` and `setMessage/2` to initialize the +object before showing it. """. -spec new() -> wxNotificationMessage(). new() -> wxe_util:queue_cmd(?get_env(), ?wxNotificationMessage_new_0), wxe_util:rec(?wxNotificationMessage_new_0). -%% @equiv new(Title, []) +-doc(#{equiv => new(Title, [])}). -spec new(Title) -> wxNotificationMessage() when Title::unicode:chardata(). @@ -95,12 +95,10 @@ new(Title) when ?is_chardata(Title) -> new(Title, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagewxnotificationmessage">external documentation</a>. -doc """ Create a notification object with the given attributes. -See `setTitle/2`, `setMessage/2`, `setParent/2` and `setFlags/2` for the -description of the corresponding parameters. +See `setTitle/2`, `setMessage/2`, `setParent/2` and `setFlags/2` for the description of the corresponding parameters. """. -spec new(Title, [Option]) -> wxNotificationMessage() when Title::unicode:chardata(), @@ -118,7 +116,7 @@ new(Title, Options) wxe_util:queue_cmd(Title_UC, Opts,?get_env(),?wxNotificationMessage_new_2), wxe_util:rec(?wxNotificationMessage_new_2). -%% @equiv addAction(This,Actionid, []) +-doc(#{equiv => addAction(This,Actionid, [])}). -spec addAction(This, Actionid) -> boolean() when This::wxNotificationMessage(), Actionid::integer(). @@ -126,15 +124,13 @@ addAction(This,Actionid) when is_record(This, wx_ref),is_integer(Actionid) -> addAction(This,Actionid, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessageaddaction">external documentation</a>. -doc """ Add an action to the notification. If supported by the implementation this are usually buttons in the notification selectable by the user. -Return: false if the current implementation or OS version does not support -actions in notifications. +Return: false if the current implementation or OS version does not support actions in notifications. Since: 3.1.0 """. @@ -150,12 +146,11 @@ addAction(#wx_ref{type=ThisT}=This,Actionid, Options) wxe_util:queue_cmd(This,Actionid, Opts,?get_env(),?wxNotificationMessage_AddAction), wxe_util:rec(?wxNotificationMessage_AddAction). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessageclose">external documentation</a>. -doc """ Hides the notification. -Returns true if it was hidden or false if it couldn't be done (e.g. on some -systems automatically hidden notifications can't be hidden manually). +Returns true if it was hidden or false if it couldn't be done (e.g. on some systems +automatically hidden notifications can't be hidden manually). """. -spec close(This) -> boolean() when This::wxNotificationMessage(). @@ -164,14 +159,11 @@ close(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotificationMessage_Close), wxe_util:rec(?wxNotificationMessage_Close). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagesetflags">external documentation</a>. -doc """ -This parameter can be currently used to specify the icon to show in the -notification. +This parameter can be currently used to specify the icon to show in the notification. -Valid values are `wxICON_INFORMATION`, `wxICON_WARNING` and `wxICON_ERROR` -(notice that `wxICON_QUESTION` is not allowed here). Some implementations of -this class may not support the icons. +Valid values are `wxICON_INFORMATION`, `wxICON_WARNING` and `wxICON_ERROR` (notice that `wxICON_QUESTION` +is not allowed here). Some implementations of this class may not support the icons. See: `setIcon/2` """. @@ -182,7 +174,6 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxNotificationMessage), wxe_util:queue_cmd(This,Flags,?get_env(),?wxNotificationMessage_SetFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessageseticon">external documentation</a>. -doc """ Specify a custom icon to be displayed in the notification. @@ -199,12 +190,11 @@ setIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon) -> ?CLASS(IconT,wxIcon), wxe_util:queue_cmd(This,Icon,?get_env(),?wxNotificationMessage_SetIcon). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagesetmessage">external documentation</a>. -doc """ Set the main text of the notification. -This should be a more detailed description than the title but still limited to -reasonable length (not more than 256 characters). +This should be a more detailed description than the title but still limited to reasonable +length (not more than 256 characters). """. -spec setMessage(This, Message) -> 'ok' when This::wxNotificationMessage(), Message::unicode:chardata(). @@ -214,11 +204,10 @@ setMessage(#wx_ref{type=ThisT}=This,Message) Message_UC = unicode:characters_to_binary(Message), wxe_util:queue_cmd(This,Message_UC,?get_env(),?wxNotificationMessage_SetMessage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagesetparent">external documentation</a>. -doc """ -Set the parent for this notification: the notification will be associated with -the top level parent of this window or, if this method is not called, with the -main application window by default. +Set the parent for this notification: the notification will be associated with the top +level parent of this window or, if this method is not called, with the main application +window by default. """. -spec setParent(This, Parent) -> 'ok' when This::wxNotificationMessage(), Parent::wxWindow:wxWindow(). @@ -227,10 +216,9 @@ setParent(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent) -> ?CLASS(ParentT,wxWindow), wxe_util:queue_cmd(This,Parent,?get_env(),?wxNotificationMessage_SetParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagesettitle">external documentation</a>. -doc """ -Set the title, it must be a concise string (not more than 64 characters), use -`setMessage/2` to give the user more details. +Set the title, it must be a concise string (not more than 64 characters), use `setMessage/2` +to give the user more details. """. -spec setTitle(This, Title) -> 'ok' when This::wxNotificationMessage(), Title::unicode:chardata(). @@ -240,7 +228,7 @@ setTitle(#wx_ref{type=ThisT}=This,Title) Title_UC = unicode:characters_to_binary(Title), wxe_util:queue_cmd(This,Title_UC,?get_env(),?wxNotificationMessage_SetTitle). -%% @equiv show(This, []) +-doc(#{equiv => show(This, [])}). -spec show(This) -> boolean() when This::wxNotificationMessage(). @@ -248,20 +236,16 @@ show(This) when is_record(This, wx_ref) -> show(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessageshow">external documentation</a>. -doc """ -Show the notification to the user and hides it after `timeout` seconds are -elapsed. +Show the notification to the user and hides it after `timeout` seconds are elapsed. -Special values `Timeout_Auto` and `Timeout_Never` can be used here, notice that -you shouldn't rely on `timeout` being exactly respected because the current -platform may only support default timeout value and also because the user may be -able to close the notification. +Special values `Timeout_Auto` and `Timeout_Never` can be used here, notice that you +shouldn't rely on `timeout` being exactly respected because the current platform may only +support default timeout value and also because the user may be able to close the notification. Note: When using native notifications in wxGTK, the timeout is ignored for the -notifications with `wxICON_WARNING` or `wxICON_ERROR` flags, they always remain -shown unless they're explicitly hidden by the user, i.e. behave as if -Timeout_Auto were given. +notifications with `wxICON_WARNING` or `wxICON_ERROR` flags, they always remain shown +unless they're explicitly hidden by the user, i.e. behave as if Timeout_Auto were given. Return: false if an error occurred. """. @@ -277,7 +261,6 @@ show(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxNotificationMessage_Show), wxe_util:rec(?wxNotificationMessage_Show). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessageusetaskbaricon">external documentation</a>. -doc """ If the application already uses a `m:wxTaskBarIcon`, it should be connected to notifications by using this method. @@ -295,31 +278,26 @@ useTaskBarIcon(#wx_ref{type=IconT}=Icon) -> wxe_util:queue_cmd(Icon,?get_env(),?wxNotificationMessage_UseTaskBarIcon), wxe_util:rec(?wxNotificationMessage_UseTaskBarIcon). -%% @equiv mSWUseToasts([]) +-doc(#{equiv => mSWUseToasts([])}). -spec mSWUseToasts() -> boolean(). mSWUseToasts() -> mSWUseToasts([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotificationmessage.html#wxnotificationmessagemswusetoasts">external documentation</a>. -doc """ -Enables toast notifications available since Windows 8 and suppresses the -additional icon in the notification area on Windows 10. +Enables toast notifications available since Windows 8 and suppresses the additional icon +in the notification area on Windows 10. -Toast notifications `require` a shortcut to the application in the start menu. -The start menu shortcut needs to contain an Application User Model ID. It is -recommended that the applications setup creates the shortcut and the application -specifies the setup created shortcut in `shortcutPath`. A call to this method -will verify (and if necessary modify) the shortcut before enabling toast -notifications. +Toast notifications `require` a shortcut to the application in the start menu. The start +menu shortcut needs to contain an Application User Model ID. It is recommended that the +applications setup creates the shortcut and the application specifies the setup created +shortcut in `shortcutPath`. A call to this method will verify (and if necessary modify) +the shortcut before enabling toast notifications. Return: false if toast notifications could not be enabled. Only for:wxmsw -See: `wxAppConsole::SetAppName()` (not implemented in wx), -`wxAppConsole::SetVendorName()` (not implemented in wx) - Since: 3.1.0 """. -spec mSWUseToasts([Option]) -> boolean() when @@ -334,31 +312,20 @@ mSWUseToasts(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxNotificationMessage_MSWUseToasts), wxe_util:rec(?wxNotificationMessage_MSWUseToasts). -%% @doc Destroys this object, do not use object again --doc """ -Destructor does not hide the notification. - -The notification can continue to be shown even after the C++ object was -destroyed, call `close/1` explicitly if it needs to be hidden. -""". +-doc "Destroys the object". -spec destroy(This::wxNotificationMessage()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxNotificationMessage), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxNotifyEvent.erl b/lib/wx/src/gen/wxNotifyEvent.erl index 6ac60e3cb5b8..8b6e8a8c6b63 100644 --- a/lib/wx/src/gen/wxNotifyEvent.erl +++ b/lib/wx/src/gen/wxNotifyEvent.erl @@ -20,22 +20,21 @@ -module(wxNotifyEvent). -moduledoc """ -Functions for wxNotifyEvent class +This class is not used by the event handlers by itself, but is a base class for other +event classes (such as `m:wxBookCtrlEvent`). -This class is not used by the event handlers by itself, but is a base class for -other event classes (such as `m:wxBookCtrlEvent`). - -It (or an object of a derived class) is sent when the controls state is being -changed and allows the program to `veto/1` this change if it wants to prevent it -from happening. +It (or an object of a derived class) is sent when the controls state is being changed and +allows the program to `veto/1` this change if it wants to prevent it from happening. See: `m:wxBookCtrlEvent` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxNotifyEvent](https://docs.wxwidgets.org/3.1/classwx_notify_event.html) +wxWidgets docs: [wxNotifyEvent](https://docs.wxwidgets.org/3.2/classwx_notify_event.html) """. -include("wxe.hrl"). -export([allow/1,isAllowed/1,veto/1]). @@ -48,20 +47,17 @@ wxWidgets docs: -type wxNotifyEvent() :: wx:wx_object(). -export_type([wxNotifyEvent/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotifyevent.html#wxnotifyeventallow">external documentation</a>. -doc """ -This is the opposite of `veto/1`: it explicitly allows the event to be -processed. +This is the opposite of `veto/1`: it explicitly allows the event to be processed. -For most events it is not necessary to call this method as the events are -allowed anyhow but some are forbidden by default (this will be mentioned in the -corresponding event description). +For most events it is not necessary to call this method as the events are allowed anyhow +but some are forbidden by default (this will be mentioned in the corresponding event +description). """. -spec allow(This) -> 'ok' when This::wxNotifyEvent(). @@ -69,10 +65,9 @@ allow(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxNotifyEvent), wxe_util:queue_cmd(This,?get_env(),?wxNotifyEvent_Allow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotifyevent.html#wxnotifyeventisallowed">external documentation</a>. -doc """ -Returns true if the change is allowed (`veto/1` hasn't been called) or false -otherwise (if it was). +Returns true if the change is allowed (`veto/1` hasn't been called) or false otherwise +(if it was). """. -spec isAllowed(This) -> boolean() when This::wxNotifyEvent(). @@ -81,13 +76,12 @@ isAllowed(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotifyEvent_IsAllowed), wxe_util:rec(?wxNotifyEvent_IsAllowed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxnotifyevent.html#wxnotifyeventveto">external documentation</a>. -doc """ Prevents the change announced by this event from happening. -It is in general a good idea to notify the user about the reasons for vetoing -the change because otherwise the applications behaviour (which just refuses to -do what the user wants) might be quite surprising. +It is in general a good idea to notify the user about the reasons for vetoing the change +because otherwise the applications behaviour (which just refuses to do what the user +wants) might be quite surprising. """. -spec veto(This) -> 'ok' when This::wxNotifyEvent(). @@ -96,58 +90,40 @@ veto(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxNotifyEvent_Veto). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxOverlay.erl b/lib/wx/src/gen/wxOverlay.erl index 74e4618ad02a..605aa684f766 100644 --- a/lib/wx/src/gen/wxOverlay.erl +++ b/lib/wx/src/gen/wxOverlay.erl @@ -20,15 +20,18 @@ -module(wxOverlay). -moduledoc """ -Functions for wxOverlay class - Creates an overlay over an existing window, allowing for manipulations like -rubberbanding, etc. On wxOSX the overlay is implemented with native platform -APIs, on the other platforms it is simulated using `m:wxMemoryDC`. +rubberbanding, etc. + +On wxOSX the overlay is implemented with native platform APIs, on the other platforms it +is simulated using `m:wxMemoryDC`. + +See: +* `m:wxDCOverlay` -See: `m:wxDCOverlay`, `m:wxDC` +* `m:wxDC` -wxWidgets docs: [wxOverlay](https://docs.wxwidgets.org/3.1/classwx_overlay.html) +wxWidgets docs: [wxOverlay](https://docs.wxwidgets.org/3.2/classwx_overlay.html) """. -include("wxe.hrl"). -export([destroy/1,new/0,reset/1]). @@ -38,17 +41,15 @@ wxWidgets docs: [wxOverlay](https://docs.wxwidgets.org/3.1/classwx_overlay.html) -type wxOverlay() :: wx:wx_object(). -export_type([wxOverlay/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxoverlay.html#wxoverlaywxoverlay">external documentation</a>. +-doc "". -spec new() -> wxOverlay(). new() -> wxe_util:queue_cmd(?get_env(), ?wxOverlay_new), wxe_util:rec(?wxOverlay_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxoverlay.html#wxoverlayreset">external documentation</a>. -doc """ Clears the overlay without restoring the former state. @@ -60,7 +61,7 @@ reset(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxOverlay), wxe_util:queue_cmd(This,?get_env(),?wxOverlay_Reset). -%% @doc Destroys this object, do not use object again +-doc "Destroys the object". -spec destroy(This::wxOverlay()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxOverlay), diff --git a/lib/wx/src/gen/wxPageSetupDialog.erl b/lib/wx/src/gen/wxPageSetupDialog.erl index 24cf1e62d8ca..cd03fe9c2405 100644 --- a/lib/wx/src/gen/wxPageSetupDialog.erl +++ b/lib/wx/src/gen/wxPageSetupDialog.erl @@ -20,29 +20,28 @@ -module(wxPageSetupDialog). -moduledoc """ -Functions for wxPageSetupDialog class - This class represents the page setup common dialog. -The page setup dialog contains controls for paper size (letter, A4, A5 etc.), -orientation (landscape or portrait), and, only under Windows currently, controls -for setting left, top, right and bottom margin sizes in millimetres. +The page setup dialog contains controls for paper size (letter, A4, A5 etc.), orientation +(landscape or portrait), and, only under Windows currently, controls for setting left, +top, right and bottom margin sizes in millimetres. -The exact appearance of this dialog varies among the platforms as a native -dialog is used when available (currently the case for all major platforms). +The exact appearance of this dialog varies among the platforms as a native dialog is used +when available (currently the case for all major platforms). -When the dialog has been closed, you need to query the `m:wxPageSetupDialogData` -object associated with the dialog. +When the dialog has been closed, you need to query the `m:wxPageSetupDialogData` object +associated with the dialog. -Note that the OK and Cancel buttons do not destroy the dialog; this must be done -by the application. +Note that the OK and Cancel buttons do not destroy the dialog; this must be done by the application. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`m:wxPrintDialog`, `m:wxPageSetupDialogData` +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) + +* `m:wxPrintDialog` + +* `m:wxPageSetupDialogData` -wxWidgets docs: -[wxPageSetupDialog](https://docs.wxwidgets.org/3.1/classwx_page_setup_dialog.html) +wxWidgets docs: [wxPageSetupDialog](https://docs.wxwidgets.org/3.2/classwx_page_setup_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getPageSetupData/1,new/1,new/2,showModal/1]). @@ -52,11 +51,10 @@ wxWidgets docs: -type wxPageSetupDialog() :: wx:wx_object(). -export_type([wxPageSetupDialog/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxPageSetupDialog() when Parent::wxWindow:wxWindow(). @@ -64,12 +62,11 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialog.html#wxpagesetupdialogwxpagesetupdialog">external documentation</a>. -doc """ Constructor. -Pass a parent window, and optionally a pointer to a block of page setup data, -which will be copied to the print dialog's internal data. +Pass a parent window, and optionally a pointer to a block of page setup data, which will +be copied to the print dialog's internal data. """. -spec new(Parent, [Option]) -> wxPageSetupDialog() when Parent::wxWindow:wxWindow(), @@ -83,7 +80,6 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxPageSetupDialog_new), wxe_util:rec(?wxPageSetupDialog_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialog.html#wxpagesetupdialoggetpagesetupdata">external documentation</a>. -doc "Returns the `m:wxPageSetupDialogData` object associated with the dialog.". -spec getPageSetupData(This) -> wxPageSetupDialogData:wxPageSetupDialogData() when This::wxPageSetupDialog(). @@ -92,9 +88,8 @@ getPageSetupData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialog_GetPageSetupData), wxe_util:rec(?wxPageSetupDialog_GetPageSetupData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialog.html#wxpagesetupdialogshowmodal">external documentation</a>. -doc """ -Shows the dialog, returning `wxID_OK` if the user pressed OK, and `wxID_CANCEL` +Shows the dialog, returning `wxID\_OK` if the user pressed OK, and `wxID\_CANCEL` otherwise. """. -spec showModal(This) -> integer() when @@ -104,8 +99,7 @@ showModal(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialog_ShowModal), wxe_util:rec(?wxPageSetupDialog_ShowModal). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPageSetupDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPageSetupDialog), diff --git a/lib/wx/src/gen/wxPageSetupDialogData.erl b/lib/wx/src/gen/wxPageSetupDialogData.erl index 375d0407733b..e0132c6c5660 100644 --- a/lib/wx/src/gen/wxPageSetupDialogData.erl +++ b/lib/wx/src/gen/wxPageSetupDialogData.erl @@ -20,20 +20,17 @@ -module(wxPageSetupDialogData). -moduledoc """ -Functions for wxPageSetupDialogData class - This class holds a variety of information related to `m:wxPageSetupDialog`. -It contains a `m:wxPrintData` member which is used to hold basic printer -configuration data (as opposed to the user-interface configuration settings -stored by `m:wxPageSetupDialogData`). +It contains a `m:wxPrintData` member which is used to hold basic printer configuration +data (as opposed to the user-interface configuration settings stored by `m:wxPageSetupDialogData`). See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`m:wxPageSetupDialog` +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) + +* `m:wxPageSetupDialog` -wxWidgets docs: -[wxPageSetupDialogData](https://docs.wxwidgets.org/3.1/classwx_page_setup_dialog_data.html) +wxWidgets docs: [wxPageSetupDialogData](https://docs.wxwidgets.org/3.2/classwx_page_setup_dialog_data.html) """. -include("wxe.hrl"). -export([destroy/1,enableHelp/2,enableMargins/2,enableOrientation/2,enablePaper/2, @@ -50,18 +47,15 @@ wxWidgets docs: -type wxPageSetupDialogData() :: wx:wx_object(). -export_type([wxPageSetupDialogData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatawxpagesetupdialogdata">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPageSetupDialogData(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPageSetupDialogData_new_0), wxe_util:rec(?wxPageSetupDialogData_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatawxpagesetupdialogdata">external documentation</a>. -doc "Construct an object from a print data object.". -spec new(PrintData) -> wxPageSetupDialogData() when PrintData::wxPrintData:wxPrintData() | wxPageSetupDialogData:wxPageSetupDialogData(). @@ -76,7 +70,6 @@ new(#wx_ref{type=PrintDataT}=PrintData) -> wxe_util:queue_cmd(wx:typeCast(PrintData, PrintDataType),?get_env(),?wxPageSetupDialogData_new_1), wxe_util:rec(?wxPageSetupDialogData_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataenablehelp">external documentation</a>. -doc """ Enables or disables the "Help" button (Windows only). """. @@ -87,7 +80,6 @@ enableHelp(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_EnableHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataenablemargins">external documentation</a>. -doc "Enables or disables the margin controls (Windows only).". -spec enableMargins(This, Flag) -> 'ok' when This::wxPageSetupDialogData(), Flag::boolean(). @@ -96,7 +88,6 @@ enableMargins(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_EnableMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataenableorientation">external documentation</a>. -doc "Enables or disables the orientation control (Windows only).". -spec enableOrientation(This, Flag) -> 'ok' when This::wxPageSetupDialogData(), Flag::boolean(). @@ -105,7 +96,6 @@ enableOrientation(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_EnableOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataenablepaper">external documentation</a>. -doc "Enables or disables the paper size control (Windows only).". -spec enablePaper(This, Flag) -> 'ok' when This::wxPageSetupDialogData(), Flag::boolean(). @@ -114,7 +104,6 @@ enablePaper(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_EnablePaper). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataenableprinter">external documentation</a>. -doc """ Enables or disables the "Printer" button, which invokes a printer setup dialog. """. @@ -125,10 +114,9 @@ enablePrinter(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_EnablePrinter). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetdefaultminmargins">external documentation</a>. -doc """ -Returns true if the page setup dialog will take its minimum margin values from -the currently selected printer properties (Windows only). +Returns true if the page setup dialog will take its minimum margin values from the +currently selected printer properties (Windows only). """. -spec getDefaultMinMargins(This) -> boolean() when This::wxPageSetupDialogData(). @@ -137,7 +125,6 @@ getDefaultMinMargins(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetDefaultMinMargins), wxe_util:rec(?wxPageSetupDialogData_GetDefaultMinMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetenablemargins">external documentation</a>. -doc "Returns true if the margin controls are enabled (Windows only).". -spec getEnableMargins(This) -> boolean() when This::wxPageSetupDialogData(). @@ -146,7 +133,6 @@ getEnableMargins(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetEnableMargins), wxe_util:rec(?wxPageSetupDialogData_GetEnableMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetenableorientation">external documentation</a>. -doc "Returns true if the orientation control is enabled (Windows only).". -spec getEnableOrientation(This) -> boolean() when This::wxPageSetupDialogData(). @@ -155,7 +141,6 @@ getEnableOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetEnableOrientation), wxe_util:rec(?wxPageSetupDialogData_GetEnableOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetenablepaper">external documentation</a>. -doc "Returns true if the paper size control is enabled (Windows only).". -spec getEnablePaper(This) -> boolean() when This::wxPageSetupDialogData(). @@ -164,7 +149,6 @@ getEnablePaper(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetEnablePaper), wxe_util:rec(?wxPageSetupDialogData_GetEnablePaper). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetenableprinter">external documentation</a>. -doc "Returns true if the printer setup button is enabled.". -spec getEnablePrinter(This) -> boolean() when This::wxPageSetupDialogData(). @@ -173,7 +157,6 @@ getEnablePrinter(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetEnablePrinter), wxe_util:rec(?wxPageSetupDialogData_GetEnablePrinter). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetenablehelp">external documentation</a>. -doc "Returns true if the printer setup button is enabled.". -spec getEnableHelp(This) -> boolean() when This::wxPageSetupDialogData(). @@ -182,10 +165,9 @@ getEnableHelp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetEnableHelp), wxe_util:rec(?wxPageSetupDialogData_GetEnableHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetdefaultinfo">external documentation</a>. -doc """ -Returns true if the dialog will simply return default printer information (such -as orientation) instead of showing a dialog (Windows only). +Returns true if the dialog will simply return default printer information (such as +orientation) instead of showing a dialog (Windows only). """. -spec getDefaultInfo(This) -> boolean() when This::wxPageSetupDialogData(). @@ -194,7 +176,6 @@ getDefaultInfo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetDefaultInfo), wxe_util:rec(?wxPageSetupDialogData_GetDefaultInfo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetmargintopleft">external documentation</a>. -doc "Returns the left (x) and top (y) margins in millimetres.". -spec getMarginTopLeft(This) -> {X::integer(), Y::integer()} when This::wxPageSetupDialogData(). @@ -203,7 +184,6 @@ getMarginTopLeft(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetMarginTopLeft), wxe_util:rec(?wxPageSetupDialogData_GetMarginTopLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetmarginbottomright">external documentation</a>. -doc "Returns the right (x) and bottom (y) margins in millimetres.". -spec getMarginBottomRight(This) -> {X::integer(), Y::integer()} when This::wxPageSetupDialogData(). @@ -212,10 +192,8 @@ getMarginBottomRight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetMarginBottomRight), wxe_util:rec(?wxPageSetupDialogData_GetMarginBottomRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetminmargintopleft">external documentation</a>. -doc """ -Returns the left (x) and top (y) minimum margins the user can enter (Windows -only). +Returns the left (x) and top (y) minimum margins the user can enter (Windows only). Units are in millimetres. """. @@ -226,10 +204,8 @@ getMinMarginTopLeft(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetMinMarginTopLeft), wxe_util:rec(?wxPageSetupDialogData_GetMinMarginTopLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetminmarginbottomright">external documentation</a>. -doc """ -Returns the right (x) and bottom (y) minimum margins the user can enter (Windows -only). +Returns the right (x) and bottom (y) minimum margins the user can enter (Windows only). Units are in millimetres. """. @@ -240,13 +216,12 @@ getMinMarginBottomRight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetMinMarginBottomRight), wxe_util:rec(?wxPageSetupDialogData_GetMinMarginBottomRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetpaperid">external documentation</a>. -%%<br /> Res = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -doc """ Returns the paper id (stored in the internal `m:wxPrintData` object). See: `wxPrintData:setPaperId/2` """. +%% Res = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -spec getPaperId(This) -> wx:wx_enum() when This::wxPageSetupDialogData(). getPaperId(#wx_ref{type=ThisT}=This) -> @@ -254,7 +229,6 @@ getPaperId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetPaperId), wxe_util:rec(?wxPageSetupDialogData_GetPaperId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetpapersize">external documentation</a>. -doc "Returns the paper size in millimetres.". -spec getPaperSize(This) -> {W::integer(), H::integer()} when This::wxPageSetupDialogData(). @@ -263,7 +237,7 @@ getPaperSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetPaperSize), wxe_util:rec(?wxPageSetupDialogData_GetPaperSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatagetprintdata">external documentation</a>. +-doc "". -spec getPrintData(This) -> wxPrintData:wxPrintData() when This::wxPageSetupDialogData(). getPrintData(#wx_ref{type=ThisT}=This) -> @@ -271,12 +245,11 @@ getPrintData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_GetPrintData), wxe_util:rec(?wxPageSetupDialogData_GetPrintData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdataisok">external documentation</a>. -doc """ Returns true if the print data associated with the dialog data is valid. -This can return false on Windows if the current printer is not set, for example. -On all other platforms, it returns true. +This can return false on Windows if the current printer is not set, for example. On all +other platforms, it returns true. """. -spec isOk(This) -> boolean() when This::wxPageSetupDialogData(). @@ -285,7 +258,6 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPageSetupDialogData_IsOk), wxe_util:rec(?wxPageSetupDialogData_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetdefaultinfo">external documentation</a>. -doc """ Pass true if the dialog will simply return default printer information (such as orientation) instead of showing a dialog (Windows only). @@ -297,10 +269,9 @@ setDefaultInfo(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_SetDefaultInfo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetdefaultminmargins">external documentation</a>. -doc """ -Pass true if the page setup dialog will take its minimum margin values from the -currently selected printer properties (Windows only). +Pass true if the page setup dialog will take its minimum margin values from the currently +selected printer properties (Windows only). Units are in millimetres. """. @@ -311,7 +282,6 @@ setDefaultMinMargins(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPageSetupDialogData_SetDefaultMinMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetmargintopleft">external documentation</a>. -doc "Sets the left (x) and top (y) margins in millimetres.". -spec setMarginTopLeft(This, Pt) -> 'ok' when This::wxPageSetupDialogData(), Pt::{X::integer(), Y::integer()}. @@ -320,7 +290,6 @@ setMarginTopLeft(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Pt,?get_env(),?wxPageSetupDialogData_SetMarginTopLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetmarginbottomright">external documentation</a>. -doc "Sets the right (x) and bottom (y) margins in millimetres.". -spec setMarginBottomRight(This, Pt) -> 'ok' when This::wxPageSetupDialogData(), Pt::{X::integer(), Y::integer()}. @@ -329,7 +298,6 @@ setMarginBottomRight(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Pt,?get_env(),?wxPageSetupDialogData_SetMarginBottomRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetminmargintopleft">external documentation</a>. -doc """ Sets the left (x) and top (y) minimum margins the user can enter (Windows only). @@ -342,10 +310,8 @@ setMinMarginTopLeft(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Pt,?get_env(),?wxPageSetupDialogData_SetMinMarginTopLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetminmarginbottomright">external documentation</a>. -doc """ -Sets the right (x) and bottom (y) minimum margins the user can enter (Windows -only). +Sets the right (x) and bottom (y) minimum margins the user can enter (Windows only). Units are in millimetres. """. @@ -356,16 +322,14 @@ setMinMarginBottomRight(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Pt,?get_env(),?wxPageSetupDialogData_SetMinMarginBottomRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetpaperid">external documentation</a>. -%%<br /> Id = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -doc """ Sets the paper size id. -Calling this function overrides the explicit paper dimensions passed in -`setPaperSize/2`. +Calling this function overrides the explicit paper dimensions passed in `setPaperSize/2`. See: `wxPrintData:setPaperId/2` """. +%% Id = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -spec setPaperId(This, Id) -> 'ok' when This::wxPageSetupDialogData(), Id::wx:wx_enum(). setPaperId(#wx_ref{type=ThisT}=This,Id) @@ -373,12 +337,11 @@ setPaperId(#wx_ref{type=ThisT}=This,Id) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Id,?get_env(),?wxPageSetupDialogData_SetPaperId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetpapersize">external documentation</a>. -doc """ Sets the paper size in millimetres. -If a corresponding paper id is found, it will be set in the internal -`m:wxPrintData` object, otherwise the paper size overrides the paper id. +If a corresponding paper id is found, it will be set in the internal `m:wxPrintData` +object, otherwise the paper size overrides the paper id. """. -spec setPaperSize(This, Size) -> 'ok' when This::wxPageSetupDialogData(), Size::{W::integer(), H::integer()}. @@ -387,7 +350,6 @@ setPaperSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxPageSetupDialogData), wxe_util:queue_cmd(This,Size,?get_env(),?wxPageSetupDialogData_SetPaperSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpagesetupdialogdata.html#wxpagesetupdialogdatasetprintdata">external documentation</a>. -doc "Sets the print data associated with this object.". -spec setPrintData(This, PrintData) -> 'ok' when This::wxPageSetupDialogData(), PrintData::wxPrintData:wxPrintData(). @@ -396,8 +358,7 @@ setPrintData(#wx_ref{type=ThisT}=This,#wx_ref{type=PrintDataT}=PrintData) -> ?CLASS(PrintDataT,wxPrintData), wxe_util:queue_cmd(This,PrintData,?get_env(),?wxPageSetupDialogData_SetPrintData). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPageSetupDialogData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPageSetupDialogData), diff --git a/lib/wx/src/gen/wxPaintDC.erl b/lib/wx/src/gen/wxPaintDC.erl index 8915e74a6b86..af2ce96b7d3c 100644 --- a/lib/wx/src/gen/wxPaintDC.erl +++ b/lib/wx/src/gen/wxPaintDC.erl @@ -20,27 +20,38 @@ -module(wxPaintDC). -moduledoc """ -Functions for wxPaintDC class +A `m:wxPaintDC` must be constructed if an application wishes to paint on the client area +of a window from within an EVT\_PAINT() event handler. -A `m:wxPaintDC` must be constructed if an application wishes to paint on the -client area of a window from within an EVT_PAINT() event handler. This should -normally be constructed as a temporary stack object; don't store a `m:wxPaintDC` -object. If you have an EVT_PAINT() handler, you `must` create a `m:wxPaintDC` -object within it even if you don't actually use it. +This should normally be constructed as a temporary stack object; don't store a `m:wxPaintDC` +object. If you have an EVT_PAINT() handler, you `must` create a `m:wxPaintDC` object +within it even if you don't actually use it. -Using `m:wxPaintDC` within your EVT_PAINT() handler is important because it -automatically sets the clipping area to the damaged area of the window. Attempts -to draw outside this area do not appear. +Using `m:wxPaintDC` within your EVT_PAINT() handler is important because it automatically +sets the clipping area to the damaged area of the window. Attempts to draw outside this +area do not appear. -A `m:wxPaintDC` object is initialized to use the same font and colours as the -window it is associated with. +A `m:wxPaintDC` object is initialized to use the same font and colours as the window it +is associated with. -See: `m:wxDC`, `m:wxClientDC`, `m:wxMemoryDC`, `m:wxWindowDC`, `m:wxScreenDC` +See: +* `m:wxDC` -This class is derived (and can use functions) from: `m:wxWindowDC` `m:wxDC` +* `m:wxClientDC` -wxWidgets docs: -[wxPaintDC](https://docs.wxwidgets.org/3.1/classwx_paint_d_c.html) +* `m:wxMemoryDC` + +* `m:wxWindowDC` + +* `m:wxScreenDC` + +This class is derived, and can use functions, from: + +* `m:wxWindowDC` + +* `m:wxDC` + +wxWidgets docs: [wxPaintDC](https://docs.wxwidgets.org/3.2/classwx_paint_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/1]). @@ -69,13 +80,11 @@ wxWidgets docs: -type wxPaintDC() :: wx:wx_object(). -export_type([wxPaintDC/0]). -%% @hidden -doc false. parent_class(wxWindowDC) -> true; parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpaintdc.html#wxpaintdcwxpaintdc">external documentation</a>. -doc """ Constructor. @@ -88,8 +97,7 @@ new(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxPaintDC_new), wxe_util:rec(?wxPaintDC_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPaintDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPaintDC), @@ -97,279 +105,187 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxWindowDC %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxPaintEvent.erl b/lib/wx/src/gen/wxPaintEvent.erl index c77e7877830e..00fccfda2040 100644 --- a/lib/wx/src/gen/wxPaintEvent.erl +++ b/lib/wx/src/gen/wxPaintEvent.erl @@ -20,40 +20,36 @@ -module(wxPaintEvent). -moduledoc """ -Functions for wxPaintEvent class - A paint event is sent when a window's contents needs to be repainted. -The handler of this event must create a `m:wxPaintDC` object and use it for -painting the window contents. For example: +The handler of this event must create a `m:wxPaintDC` object and use it for painting the +window contents. For example: + +Notice that you must `not` create other kinds of `m:wxDC` (e.g. `m:wxClientDC` or `m:wxWindowDC`) +in EVT_PAINT handlers and also don't create `m:wxPaintDC` outside of this event handlers. -Notice that you must `not` create other kinds of `m:wxDC` (e.g. `m:wxClientDC` -or `m:wxWindowDC`) in EVT_PAINT handlers and also don't create `m:wxPaintDC` -outside of this event handlers. +You can optimize painting by retrieving the rectangles that have been damaged and only +repainting these. The rectangles are in terms of the client area, and are unscrolled, so +you will need to do some calculations using the current view position to obtain logical, +scrolled units. Here is an example of using the `wxRegionIterator` (not implemented in wx) +class: -You can optimize painting by retrieving the rectangles that have been damaged -and only repainting these. The rectangles are in terms of the client area, and -are unscrolled, so you will need to do some calculations using the current view -position to obtain logical, scrolled units. Here is an example of using the -`wxRegionIterator` (not implemented in wx) class: +Remark: Please notice that in general it is impossible to change the drawing of a +standard control (such as `m:wxButton`) and so you shouldn't attempt to handle paint +events for them as even if it might work on some platforms, this is inherently not +portable and won't work everywhere. -Remark: Please notice that in general it is impossible to change the drawing of -a standard control (such as `m:wxButton`) and so you shouldn't attempt to handle -paint events for them as even if it might work on some platforms, this is -inherently not portable and won't work everywhere. +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxPaintEvent](https://docs.wxwidgets.org/3.1/classwx_paint_event.html) +wxWidgets docs: [wxPaintEvent](https://docs.wxwidgets.org/3.2/classwx_paint_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxPaintEventType`](`t:wxPaintEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxPaintEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -66,36 +62,26 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxPaintEventType() :: 'paint'. -export_type([wxPaintEvent/0, wxPaint/0, wxPaintEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxPalette.erl b/lib/wx/src/gen/wxPalette.erl index 6797bdaf6cea..506b233a61c6 100644 --- a/lib/wx/src/gen/wxPalette.erl +++ b/lib/wx/src/gen/wxPalette.erl @@ -20,25 +20,26 @@ -module(wxPalette). -moduledoc """ -Functions for wxPalette class +A palette is a table that maps pixel values to RGB colours. -A palette is a table that maps pixel values to RGB colours. It allows the -colours of a low-depth bitmap, for example, to be mapped to the available -colours in a display. The notion of palettes is becoming more and more obsolete -nowadays and only the MSW port is still using a native palette. All other ports -use generic code which is basically just an array of colours. +It allows the colours of a low-depth bitmap, for example, to be mapped to the available +colours in a display. The notion of palettes is becoming more and more obsolete nowadays +and only the MSW port is still using a native palette. All other ports use generic code +which is basically just an array of colours. -It is likely that in the future the only use for palettes within wxWidgets will -be for representing colour indices from images (such as GIF or PNG). The image -handlers for these formats have been modified to create a palette if there is -such information in the original image file (usually 256 or less colour images). -See `m:wxImage` for more information. +It is likely that in the future the only use for palettes within wxWidgets will be for +representing colour indices from images (such as GIF or PNG). The image handlers for these +formats have been modified to create a palette if there is such information in the +original image file (usually 256 or less colour images). See `m:wxImage` for more information. Predefined objects (include wx.hrl): ?wxNullPalette -See: `wxDC:setPalette/2`, `m:wxBitmap` +See: +* `wxDC:setPalette/2` -wxWidgets docs: [wxPalette](https://docs.wxwidgets.org/3.1/classwx_palette.html) +* `m:wxBitmap` + +wxWidgets docs: [wxPalette](https://docs.wxwidgets.org/3.2/classwx_palette.html) """. -include("wxe.hrl"). -export([create/4,destroy/1,getColoursCount/1,getPixel/4,getRGB/2,isOk/1,new/0, @@ -49,19 +50,16 @@ wxWidgets docs: [wxPalette](https://docs.wxwidgets.org/3.1/classwx_palette.html) -type wxPalette() :: wx:wx_object(). -export_type([wxPalette/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettewxpalette">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPalette(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPalette_new_0), wxe_util:rec(?wxPalette_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettewxpalette">external documentation</a>. --doc "Copy constructor, uses overview_refcount.". +-doc "Copy constructor, uses overview\_refcount.". -spec new(Palette) -> wxPalette() when Palette::wxPalette(). new(#wx_ref{type=PaletteT}=Palette) -> @@ -69,10 +67,8 @@ new(#wx_ref{type=PaletteT}=Palette) -> wxe_util:queue_cmd(Palette,?get_env(),?wxPalette_new_1), wxe_util:rec(?wxPalette_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettewxpalette">external documentation</a>. -doc """ -Creates a palette from arrays of size `n`, one for each red, blue or green -component. +Creates a palette from arrays of size `n`, one for each red, blue or green component. See: `create/4` """. @@ -83,10 +79,8 @@ new(Red,Green,Blue) wxe_util:queue_cmd(Red,Green,Blue,?get_env(),?wxPalette_new_4), wxe_util:rec(?wxPalette_new_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettecreate">external documentation</a>. -doc """ -Creates a palette from arrays of size `n`, one for each red, blue or green -component. +Creates a palette from arrays of size `n`, one for each red, blue or green component. Return: true if the creation was successful, false otherwise. @@ -100,7 +94,6 @@ create(#wx_ref{type=ThisT}=This,Red,Green,Blue) wxe_util:queue_cmd(This,Red,Green,Blue,?get_env(),?wxPalette_Create), wxe_util:rec(?wxPalette_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettegetcolourscount">external documentation</a>. -doc "Returns number of entries in palette.". -spec getColoursCount(This) -> integer() when This::wxPalette(). @@ -109,7 +102,6 @@ getColoursCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPalette_GetColoursCount), wxe_util:rec(?wxPalette_GetColoursCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettegetpixel">external documentation</a>. -doc """ Returns a pixel value (index into the palette) for the given RGB values. @@ -125,7 +117,6 @@ getPixel(#wx_ref{type=ThisT}=This,Red,Green,Blue) wxe_util:queue_cmd(This,Red,Green,Blue,?get_env(),?wxPalette_GetPixel), wxe_util:rec(?wxPalette_GetPixel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpalettegetrgb">external documentation</a>. -doc """ Returns RGB values for a given palette index. @@ -142,8 +133,7 @@ getRGB(#wx_ref{type=ThisT}=This,Pixel) wxe_util:queue_cmd(This,Pixel,?get_env(),?wxPalette_GetRGB), wxe_util:rec(?wxPalette_GetRGB). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpaletteisok">external documentation</a>. --doc "See: `isOk/1`.". +-doc "Equivalent to: `isOk/1`". -spec ok(This) -> boolean() when This::wxPalette(). @@ -151,7 +141,6 @@ ok(This) when is_record(This, wx_ref) -> isOk(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalette.html#wxpaletteisok">external documentation</a>. -doc "Returns true if palette data is present.". -spec isOk(This) -> boolean() when This::wxPalette(). @@ -160,12 +149,7 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPalette_IsOk), wxe_util:rec(?wxPalette_IsOk). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See: reference-counted object destruction -""". +-doc "Destroys the object". -spec destroy(This::wxPalette()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPalette), diff --git a/lib/wx/src/gen/wxPaletteChangedEvent.erl b/lib/wx/src/gen/wxPaletteChangedEvent.erl index 60ca29f8da79..d7d1df16e860 100644 --- a/lib/wx/src/gen/wxPaletteChangedEvent.erl +++ b/lib/wx/src/gen/wxPaletteChangedEvent.erl @@ -22,10 +22,11 @@ -moduledoc """ Functions for wxPaletteChangedEvent class -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxPaletteChangedEvent](https://docs.wxwidgets.org/3.1/classwx_palette_changed_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxPaletteChangedEvent](https://docs.wxwidgets.org/3.2/classwx_palette_changed_event.html) """. -include("wxe.hrl"). -export([getChangedWindow/1,setChangedWindow/2]). @@ -38,12 +39,11 @@ wxWidgets docs: -include("wx.hrl"). -type wxPaletteChangedEventType() :: 'palette_changed'. -export_type([wxPaletteChangedEvent/0, wxPaletteChanged/0, wxPaletteChangedEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalettechangedevent.html#wxpalettechangedeventsetchangedwindow">external documentation</a>. +-doc "". -spec setChangedWindow(This, Win) -> 'ok' when This::wxPaletteChangedEvent(), Win::wxWindow:wxWindow(). setChangedWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=WinT}=Win) -> @@ -51,7 +51,7 @@ setChangedWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=WinT}=Win) -> ?CLASS(WinT,wxWindow), wxe_util:queue_cmd(This,Win,?get_env(),?wxPaletteChangedEvent_SetChangedWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpalettechangedevent.html#wxpalettechangedeventgetchangedwindow">external documentation</a>. +-doc "". -spec getChangedWindow(This) -> wxWindow:wxWindow() when This::wxPaletteChangedEvent(). getChangedWindow(#wx_ref{type=ThisT}=This) -> @@ -60,30 +60,21 @@ getChangedWindow(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxPaletteChangedEvent_GetChangedWindow). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxPanel.erl b/lib/wx/src/gen/wxPanel.erl index 9d193b82c51e..af5cff2220b8 100644 --- a/lib/wx/src/gen/wxPanel.erl +++ b/lib/wx/src/gen/wxPanel.erl @@ -20,35 +20,37 @@ -module(wxPanel). -moduledoc """ -Functions for wxPanel class +A panel is a window on which controls are placed. -A panel is a window on which controls are placed. It is usually placed within a -frame. Its main feature over its parent class `m:wxWindow` is code for handling -child windows and TAB traversal, which is implemented natively if possible (e.g. -in wxGTK) or by wxWidgets itself otherwise. +It is usually placed within a frame. Its main feature over its parent class `m:wxWindow` +is code for handling child windows and TAB traversal, which is implemented natively if +possible (e.g. in wxGTK) or by wxWidgets itself otherwise. -Note: Tab traversal is implemented through an otherwise undocumented -intermediate wxControlContainer class from which any class can derive in -addition to the normal `m:wxWindow` base class. Please see and to find out how -this is achieved. +Note: Tab traversal is implemented through an otherwise undocumented intermediate +wxControlContainer class from which any class can derive in addition to the normal `m:wxWindow` +base class. Please see and to find out how this is achieved. -Note: if not all characters are being intercepted by your OnKeyDown or OnChar -handler, it may be because you are using the `wxTAB_TRAVERSAL` style, which -grabs some keypresses for use by child controls. +Note: if not all characters are being intercepted by your OnKeyDown or OnChar handler, it +may be because you are using the `wxTAB_TRAVERSAL` style, which grabs some keypresses for +use by child controls. Remark: By default, a panel has the same colouring as a dialog. See: `m:wxDialog` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: [wxPanel](https://docs.wxwidgets.org/3.1/classwx_panel.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxPanel](https://docs.wxwidgets.org/3.2/classwx_panel.html) ## Events Event types emitted from this class: -[`navigation_key`](`m:wxNavigationKeyEvent`) + +* [`navigation_key`](`m:wxNavigationKeyEvent`) """. -include("wxe.hrl"). -export([destroy/1,initDialog/1,new/0,new/1,new/2,setFocusIgnoringChildren/1]). @@ -94,20 +96,18 @@ Event types emitted from this class: -type wxPanel() :: wx:wx_object(). -export_type([wxPanel/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpanel.html#wxpanelwxpanel">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPanel(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPanel_new_0), wxe_util:rec(?wxPanel_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxPanel() when Parent::wxWindow:wxWindow(). @@ -115,12 +115,7 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpanel.html#wxpanelwxpanel">external documentation</a>. --doc """ -Constructor. - -See: `Create()` (not implemented in wx) -""". +-doc "Constructor.". -spec new(Parent, [Option]) -> wxPanel() when Parent::wxWindow:wxWindow(), Option :: {'winid', integer()} @@ -139,10 +134,8 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxPanel_new_2), wxe_util:rec(?wxPanel_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpanel.html#wxpanelinitdialog">external documentation</a>. -doc """ -Sends a `m:wxInitDialogEvent`, which in turn transfers data to the dialog via -validators. +Sends a `m:wxInitDialogEvent`, which in turn transfers data to the dialog via validators. See: `m:wxInitDialogEvent` """. @@ -152,10 +145,9 @@ initDialog(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPanel), wxe_util:queue_cmd(This,?get_env(),?wxPanel_InitDialog). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpanel.html#wxpanelsetfocusignoringchildren">external documentation</a>. -doc """ -In contrast to `wxWindow:setFocus/1` (see above) this will set the focus to the -panel even if there are child windows in the panel. +In contrast to `wxWindow:setFocus/1` (see above) this will set the focus to the panel +even if there are child windows in the panel. This is only rarely needed. """. @@ -165,562 +157,375 @@ setFocusIgnoringChildren(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPanel), wxe_util:queue_cmd(This,?get_env(),?wxPanel_SetFocusIgnoringChildren). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Deletes any child windows before deleting the physical window. -""". +-doc "Destroys the object". -spec destroy(This::wxPanel()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPanel), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPasswordEntryDialog.erl b/lib/wx/src/gen/wxPasswordEntryDialog.erl index 95eaa5435549..49e1de677c8a 100644 --- a/lib/wx/src/gen/wxPasswordEntryDialog.erl +++ b/lib/wx/src/gen/wxPasswordEntryDialog.erl @@ -20,21 +20,25 @@ -module(wxPasswordEntryDialog). -moduledoc """ -Functions for wxPasswordEntryDialog class - -This class represents a dialog that requests a one-line password string from the -user. +This class represents a dialog that requests a one-line password string from the user. It is implemented as a generic wxWidgets dialog. -See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_password) +See: [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_password) + +This class is derived, and can use functions, from: + +* `m:wxTextEntryDialog` + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxTextEntryDialog` -`m:wxDialog` `m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxPasswordEntryDialog](https://docs.wxwidgets.org/3.1/classwx_password_entry_dialog.html) +wxWidgets docs: [wxPasswordEntryDialog](https://docs.wxwidgets.org/3.2/classwx_password_entry_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,new/2,new/3]). @@ -87,7 +91,6 @@ wxWidgets docs: -type wxPasswordEntryDialog() :: wx:wx_object(). -export_type([wxPasswordEntryDialog/0]). -%% @hidden -doc false. parent_class(wxTextEntryDialog) -> true; parent_class(wxDialog) -> true; @@ -96,7 +99,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Message, []) +-doc(#{equiv => new(Parent,Message, [])}). -spec new(Parent, Message) -> wxPasswordEntryDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(). @@ -104,7 +107,6 @@ new(Parent,Message) when is_record(Parent, wx_ref),?is_chardata(Message) -> new(Parent,Message, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpasswordentrydialog.html#wxpasswordentrydialogwxpasswordentrydialog">external documentation</a>. -doc """ Constructor. @@ -129,666 +131,448 @@ new(#wx_ref{type=ParentT}=Parent,Message, Options) wxe_util:queue_cmd(Parent,Message_UC, Opts,?get_env(),?wxPasswordEntryDialog_new), wxe_util:rec(?wxPasswordEntryDialog_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPasswordEntryDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPasswordEntryDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxTextEntryDialog -%% @hidden -doc false. setValue(This,Value) -> wxTextEntryDialog:setValue(This,Value). -%% @hidden -doc false. getValue(This) -> wxTextEntryDialog:getValue(This). %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPen.erl b/lib/wx/src/gen/wxPen.erl index 313412027784..f6637f6f1d36 100644 --- a/lib/wx/src/gen/wxPen.erl +++ b/lib/wx/src/gen/wxPen.erl @@ -20,38 +20,63 @@ -module(wxPen). -moduledoc """ -Functions for wxPen class +A pen is a drawing tool for drawing outlines. -A pen is a drawing tool for drawing outlines. It is used for drawing lines and -painting the outline of rectangles, ellipses, etc. It has a colour, a width and -a style. +It is used for drawing lines and painting the outline of rectangles, ellipses, etc. It +has a colour, a width and a style. Note: On a monochrome display, wxWidgets shows all non-white pens as black. Do not initialize objects on the stack before the program commences, since other -required structures may not have been set up yet. Instead, define global -pointers to objects and create them in `wxApp::OnInit()` (not implemented in wx) -or when required. - -An application may wish to dynamically create pens with different -characteristics, and there is the consequent danger that a large number of -duplicate pens will be created. Therefore an application may wish to get a -pointer to a pen by using the global list of pens ?wxThePenList, and calling the -member function `wxPenList::FindOrCreatePen()` (not implemented in wx). See -`wxPenList` (not implemented in wx) for more info. - -This class uses reference counting and copy-on-write internally so that -assignments between two instances of this class are very cheap. You can -therefore use actual objects instead of pointers without efficiency problems. If -an instance of this class is changed it will create its own data internally so -that other instances, which previously shared the data using the reference -counting, are not affected. +required structures may not have been set up yet. Instead, define global pointers to +objects and create them in `wxApp::OnInit()` (not implemented in wx) or when required. + +An application may wish to dynamically create pens with different characteristics, and +there is the consequent danger that a large number of duplicate pens will be created. +Therefore an application may wish to get a pointer to a pen by using the global list of +pens ?wxThePenList, and calling the member function `wxPenList::FindOrCreatePen()` (not +implemented in wx). See `wxPenList` (not implemented in wx) for more info. + +This class uses reference counting and copy-on-write internally so that assignments +between two instances of this class are very cheap. You can therefore use actual objects +instead of pointers without efficiency problems. If an instance of this class is changed +it will create its own data internally so that other instances, which previously shared +the data using the reference counting, are not affected. Predefined objects (include wx.hrl): -See: `wxPenList` (not implemented in wx), `m:wxDC`, `wxDC:setPen/2` +* ?wxNullPen + +* ?wxBLACK\_DASHED\_PEN + +* ?wxBLACK\_PEN + +* ?wxBLUE\_PEN + +* ?wxCYAN\_PEN + +* ?wxGREEN\_PEN + +* ?wxYELLOW\_PEN + +* ?wxGREY\_PEN + +* ?wxLIGHT\_GREY\_PEN + +* ?wxMEDIUM\_GREY\_PEN + +* ?wxRED\_PEN -wxWidgets docs: [wxPen](https://docs.wxwidgets.org/3.1/classwx_pen.html) +* ?wxTRANSPARENT\_PEN + +* ?wxWHITE\_PEN + +See: +* `m:wxDC` + +* `wxDC:setPen/2` + +wxWidgets docs: [wxPen](https://docs.wxwidgets.org/3.2/classwx_pen.html) """. -include("wxe.hrl"). -export([destroy/1,getCap/1,getColour/1,getJoin/1,getStyle/1,getWidth/1,isOk/1, @@ -63,11 +88,9 @@ wxWidgets docs: [wxPen](https://docs.wxwidgets.org/3.1/classwx_pen.html) -type wxPen() :: wx:wx_object(). -export_type([wxPen/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpenwxpen">external documentation</a>. -doc """ Default constructor. @@ -78,13 +101,8 @@ new() -> wxe_util:queue_cmd(?get_env(), ?wxPen_new_0), wxe_util:rec(?wxPen_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpenwxpen">external documentation</a>. -%% <br /> Also:<br /> -%% new(Pen) -> wxPen() when<br /> -%% Pen::wxPen().<br /> -%% -%%<br /> Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH --doc "Copy constructor, uses overview_refcount.". +-doc "Copy constructor, uses overview\_refcount.". +%% Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -spec new(Colour) -> wxPen() when Colour::wx:wx_colour(); (Pen) -> wxPen() when @@ -98,16 +116,20 @@ new(#wx_ref{type=PenT}=Pen) -> wxe_util:queue_cmd(Pen,?get_env(),?wxPen_new_1), wxe_util:rec(?wxPen_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpenwxpen">external documentation</a>. -%%<br /> Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -doc """ Constructs a pen from a colour object, pen width and style. -Remark: Different versions of Windows and different versions of other platforms -support very different subsets of the styles above so handle with care. +Remark: Different versions of Windows and different versions of other platforms support +very different subsets of the styles above so handle with care. + +See: +* `setStyle/2` + +* `setColour/4` -See: `setStyle/2`, `setColour/4`, `setWidth/2` +* `setWidth/2` """. +%% Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -spec new(Colour, [Option]) -> wxPen() when Colour::wx:wx_colour(), Option :: {'width', integer()} @@ -121,16 +143,14 @@ new(Colour, Options) wxe_util:queue_cmd(wxe_util:color(Colour), Opts,?get_env(),?wxPen_new_2), wxe_util:rec(?wxPen_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpengetcap">external documentation</a>. -%%<br /> Res = ?wxCAP_INVALID | ?wxCAP_ROUND | ?wxCAP_PROJECTING | ?wxCAP_BUTT -doc """ -Returns the pen cap style, which may be one of `wxCAP_ROUND`, `wxCAP_PROJECTING` -and `wxCAP_BUTT`. +Returns the pen cap style, which may be one of `wxCAP\_ROUND`, `wxCAP\_PROJECTING` and `wxCAP\_BUTT`. The default is `wxCAP_ROUND`. See: `setCap/2` """. +%% Res = ?wxCAP_INVALID | ?wxCAP_ROUND | ?wxCAP_PROJECTING | ?wxCAP_BUTT -spec getCap(This) -> wx:wx_enum() when This::wxPen(). getCap(#wx_ref{type=ThisT}=This) -> @@ -138,7 +158,6 @@ getCap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_GetCap), wxe_util:rec(?wxPen_GetCap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpengetcolour">external documentation</a>. -doc """ Returns a reference to the pen colour. @@ -151,16 +170,14 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_GetColour), wxe_util:rec(?wxPen_GetColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpengetjoin">external documentation</a>. -%%<br /> Res = ?wxJOIN_INVALID | ?wxJOIN_BEVEL | ?wxJOIN_MITER | ?wxJOIN_ROUND -doc """ -Returns the pen join style, which may be one of `wxJOIN_BEVEL`, `wxJOIN_ROUND` -and `wxJOIN_MITER`. +Returns the pen join style, which may be one of `wxJOIN\_BEVEL`, `wxJOIN\_ROUND` and `wxJOIN\_MITER`. The default is `wxJOIN_ROUND`. See: `setJoin/2` """. +%% Res = ?wxJOIN_INVALID | ?wxJOIN_BEVEL | ?wxJOIN_MITER | ?wxJOIN_ROUND -spec getJoin(This) -> wx:wx_enum() when This::wxPen(). getJoin(#wx_ref{type=ThisT}=This) -> @@ -168,13 +185,15 @@ getJoin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_GetJoin), wxe_util:rec(?wxPen_GetJoin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpengetstyle">external documentation</a>. -%%<br /> Res = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -doc """ Returns the pen style. -See: `new/2`, `setStyle/2` +See: +* `new/2` + +* `setStyle/2` """. +%% Res = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -spec getStyle(This) -> wx:wx_enum() when This::wxPen(). getStyle(#wx_ref{type=ThisT}=This) -> @@ -182,7 +201,6 @@ getStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_GetStyle), wxe_util:rec(?wxPen_GetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpengetwidth">external documentation</a>. -doc """ Returns the pen width. @@ -195,12 +213,11 @@ getWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_GetWidth), wxe_util:rec(?wxPen_GetWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpenisok">external documentation</a>. -doc """ Returns true if the pen is initialised. -Notice that an uninitialized pen object can't be queried for any pen properties -and all calls to the accessor methods on it will result in an assert failure. +Notice that an uninitialized pen object can't be queried for any pen properties and all +calls to the accessor methods on it will result in an assert failure. """. -spec isOk(This) -> boolean() when This::wxPen(). @@ -209,16 +226,14 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPen_IsOk), wxe_util:rec(?wxPen_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetcap">external documentation</a>. -%%<br /> CapStyle = ?wxCAP_INVALID | ?wxCAP_ROUND | ?wxCAP_PROJECTING | ?wxCAP_BUTT -doc """ -Sets the pen cap style, which may be one of `wxCAP_ROUND`, `wxCAP_PROJECTING` -and `wxCAP_BUTT`. +Sets the pen cap style, which may be one of `wxCAP\_ROUND`, `wxCAP\_PROJECTING` and `wxCAP\_BUTT`. The default is `wxCAP_ROUND`. See: `getCap/1` """. +%% CapStyle = ?wxCAP_INVALID | ?wxCAP_ROUND | ?wxCAP_PROJECTING | ?wxCAP_BUTT -spec setCap(This, CapStyle) -> 'ok' when This::wxPen(), CapStyle::wx:wx_enum(). setCap(#wx_ref{type=ThisT}=This,CapStyle) @@ -226,7 +241,6 @@ setCap(#wx_ref{type=ThisT}=This,CapStyle) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,CapStyle,?get_env(),?wxPen_SetCap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetcolour">external documentation</a>. -doc """ The pen's colour is changed to the given colour. @@ -239,7 +253,7 @@ setColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxPen_SetColour_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetcolour">external documentation</a>. +-doc "". -spec setColour(This, Red, Green, Blue) -> 'ok' when This::wxPen(), Red::integer(), Green::integer(), Blue::integer(). setColour(#wx_ref{type=ThisT}=This,Red,Green,Blue) @@ -247,16 +261,14 @@ setColour(#wx_ref{type=ThisT}=This,Red,Green,Blue) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,Red,Green,Blue,?get_env(),?wxPen_SetColour_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetjoin">external documentation</a>. -%%<br /> Join_style = ?wxJOIN_INVALID | ?wxJOIN_BEVEL | ?wxJOIN_MITER | ?wxJOIN_ROUND -doc """ -Sets the pen join style, which may be one of `wxJOIN_BEVEL`, `wxJOIN_ROUND` and -`wxJOIN_MITER`. +Sets the pen join style, which may be one of `wxJOIN\_BEVEL`, `wxJOIN\_ROUND` and `wxJOIN\_MITER`. The default is `wxJOIN_ROUND`. See: `getJoin/1` """. +%% Join_style = ?wxJOIN_INVALID | ?wxJOIN_BEVEL | ?wxJOIN_MITER | ?wxJOIN_ROUND -spec setJoin(This, Join_style) -> 'ok' when This::wxPen(), Join_style::wx:wx_enum(). setJoin(#wx_ref{type=ThisT}=This,Join_style) @@ -264,13 +276,12 @@ setJoin(#wx_ref{type=ThisT}=This,Join_style) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,Join_style,?get_env(),?wxPen_SetJoin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetstyle">external documentation</a>. -%%<br /> Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -doc """ Set the pen style. See: `new/2` """. +%% Style = ?wxPENSTYLE_INVALID | ?wxPENSTYLE_SOLID | ?wxPENSTYLE_DOT | ?wxPENSTYLE_LONG_DASH | ?wxPENSTYLE_SHORT_DASH | ?wxPENSTYLE_DOT_DASH | ?wxPENSTYLE_USER_DASH | ?wxPENSTYLE_TRANSPARENT | ?wxPENSTYLE_STIPPLE_MASK_OPAQUE | ?wxPENSTYLE_STIPPLE_MASK | ?wxPENSTYLE_STIPPLE | ?wxPENSTYLE_BDIAGONAL_HATCH | ?wxPENSTYLE_CROSSDIAG_HATCH | ?wxPENSTYLE_FDIAGONAL_HATCH | ?wxPENSTYLE_CROSS_HATCH | ?wxPENSTYLE_HORIZONTAL_HATCH | ?wxPENSTYLE_VERTICAL_HATCH | ?wxPENSTYLE_FIRST_HATCH | ?wxPENSTYLE_LAST_HATCH -spec setStyle(This, Style) -> 'ok' when This::wxPen(), Style::wx:wx_enum(). setStyle(#wx_ref{type=ThisT}=This,Style) @@ -278,7 +289,6 @@ setStyle(#wx_ref{type=ThisT}=This,Style) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,Style,?get_env(),?wxPen_SetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpen.html#wxpensetwidth">external documentation</a>. -doc """ Sets the pen width. @@ -291,17 +301,7 @@ setWidth(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxPen), wxe_util:queue_cmd(This,Width,?get_env(),?wxPen_SetWidth). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See: reference-counted object destruction - -Remark: Although all remaining pens are deleted when the application exits, the -application should try to clean up all pens itself. This is because wxWidgets -cannot know if a pointer to the pen object is stored in an application data -structure, and there is a risk of double deletion. -""". +-doc "Destroys the object". -spec destroy(This::wxPen()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPen), diff --git a/lib/wx/src/gen/wxPickerBase.erl b/lib/wx/src/gen/wxPickerBase.erl index fd12ecc6e5b8..ddffae436240 100644 --- a/lib/wx/src/gen/wxPickerBase.erl +++ b/lib/wx/src/gen/wxPickerBase.erl @@ -20,29 +20,33 @@ -module(wxPickerBase). -moduledoc """ -Functions for wxPickerBase class - Base abstract class for all pickers which support an auxiliary text control. -This class handles all positioning and sizing of the text control like a an -horizontal `m:wxBoxSizer` would do, with the text control on the left of the -picker button. +This class handles all positioning and sizing of the text control like a an horizontal `m:wxBoxSizer` +would do, with the text control on the left of the picker button. -The proportion (see `m:wxSizer` documentation for more info about proportion -values) of the picker control defaults to 1 when there isn't a text control -associated (see `wxPB_USE_TEXTCTRL` style) and to 0 otherwise. +The proportion (see `m:wxSizer` documentation for more info about proportion values) of +the picker control defaults to 1 when there isn't a text control associated (see `wxPB_USE_TEXTCTRL` +style) and to 0 otherwise. -Styles +## Styles This class supports the following styles: +* wxPB_USE_TEXTCTRL: Creates a text control to the left of the picker which is completely +managed by this `m:wxPickerBase` class. + See: `m:wxColourPickerCtrl` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxControl` -wxWidgets docs: -[wxPickerBase](https://docs.wxwidgets.org/3.1/classwx_picker_base.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxPickerBase](https://docs.wxwidgets.org/3.2/classwx_picker_base.html) """. -include("wxe.hrl"). -export([getInternalMargin/1,getPickerCtrlProportion/1,getTextCtrl/1,getTextCtrlProportion/1, @@ -92,14 +96,12 @@ wxWidgets docs: -type wxPickerBase() :: wx:wx_object(). -export_type([wxPickerBase/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasesetinternalmargin">external documentation</a>. -doc """ Sets the margin (in pixel) between the picker and the text control. @@ -112,7 +114,6 @@ setInternalMargin(#wx_ref{type=ThisT}=This,Margin) ?CLASS(ThisT,wxPickerBase), wxe_util:queue_cmd(This,Margin,?get_env(),?wxPickerBase_SetInternalMargin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasegetinternalmargin">external documentation</a>. -doc """ Returns the margin (in pixel) between the picker and the text control. @@ -125,7 +126,6 @@ getInternalMargin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_GetInternalMargin), wxe_util:rec(?wxPickerBase_GetInternalMargin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasesettextctrlproportion">external documentation</a>. -doc """ Sets the proportion value of the text control. @@ -140,7 +140,6 @@ setTextCtrlProportion(#wx_ref{type=ThisT}=This,Prop) ?CLASS(ThisT,wxPickerBase), wxe_util:queue_cmd(This,Prop,?get_env(),?wxPickerBase_SetTextCtrlProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasesetpickerctrlproportion">external documentation</a>. -doc """ Sets the proportion value of the picker. @@ -153,7 +152,6 @@ setPickerCtrlProportion(#wx_ref{type=ThisT}=This,Prop) ?CLASS(ThisT,wxPickerBase), wxe_util:queue_cmd(This,Prop,?get_env(),?wxPickerBase_SetPickerCtrlProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasegettextctrlproportion">external documentation</a>. -doc """ Returns the proportion value of the text control. @@ -166,7 +164,6 @@ getTextCtrlProportion(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_GetTextCtrlProportion), wxe_util:rec(?wxPickerBase_GetTextCtrlProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasegetpickerctrlproportion">external documentation</a>. -doc "Returns the proportion value of the picker.". -spec getPickerCtrlProportion(This) -> integer() when This::wxPickerBase(). @@ -175,10 +172,9 @@ getPickerCtrlProportion(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_GetPickerCtrlProportion), wxe_util:rec(?wxPickerBase_GetPickerCtrlProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasehastextctrl">external documentation</a>. -doc """ -Returns true if this window has a valid text control (i.e. if the -`wxPB_USE_TEXTCTRL` style was given when creating this control). +Returns true if this window has a valid text control (i.e. if the `wxPB\_USE\_TEXTCTRL` +style was given when creating this control). """. -spec hasTextCtrl(This) -> boolean() when This::wxPickerBase(). @@ -187,17 +183,14 @@ hasTextCtrl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_HasTextCtrl), wxe_util:rec(?wxPickerBase_HasTextCtrl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasegettextctrl">external documentation</a>. -doc """ -Returns a pointer to the text control handled by this window or NULL if the -`wxPB_USE_TEXTCTRL` style was not specified when this control was created. - -Remark: The contents of the text control could be an invalid representation of -the entity which can be chosen through the picker (e.g. when the user enters an -invalid colour syntax because of a typo). Thus you should never parse the -content of the textctrl to get the user's input; rather use the derived-class -getter (e.g. `wxColourPickerCtrl:getColour/1`, `wxFilePickerCtrl:getPath/1`, -etc). +Returns a pointer to the text control handled by this window or NULL if the `wxPB\_USE\_TEXTCTRL` +style was not specified when this control was created. + +Remark: The contents of the text control could be an invalid representation of the entity +which can be chosen through the picker (e.g. when the user enters an invalid colour syntax +because of a typo). Thus you should never parse the content of the textctrl to get the +user's input; rather use the derived-class getter (e.g. `wxColourPickerCtrl:getColour/1`, `wxFilePickerCtrl:getPath/1`, etc). """. -spec getTextCtrl(This) -> wxTextCtrl:wxTextCtrl() when This::wxPickerBase(). @@ -206,7 +199,6 @@ getTextCtrl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_GetTextCtrl), wxe_util:rec(?wxPickerBase_GetTextCtrl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbaseistextctrlgrowable">external documentation</a>. -doc """ Returns true if the text control is growable. @@ -219,7 +211,7 @@ isTextCtrlGrowable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPickerBase_IsTextCtrlGrowable), wxe_util:rec(?wxPickerBase_IsTextCtrlGrowable). -%% @equiv setPickerCtrlGrowable(This, []) +-doc(#{equiv => setPickerCtrlGrowable(This, [])}). -spec setPickerCtrlGrowable(This) -> 'ok' when This::wxPickerBase(). @@ -227,7 +219,6 @@ setPickerCtrlGrowable(This) when is_record(This, wx_ref) -> setPickerCtrlGrowable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasesetpickerctrlgrowable">external documentation</a>. -doc "Sets the picker control as growable when `grow` is true.". -spec setPickerCtrlGrowable(This, [Option]) -> 'ok' when This::wxPickerBase(), @@ -240,7 +231,7 @@ setPickerCtrlGrowable(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxPickerBase_SetPickerCtrlGrowable). -%% @equiv setTextCtrlGrowable(This, []) +-doc(#{equiv => setTextCtrlGrowable(This, [])}). -spec setTextCtrlGrowable(This) -> 'ok' when This::wxPickerBase(). @@ -248,7 +239,6 @@ setTextCtrlGrowable(This) when is_record(This, wx_ref) -> setTextCtrlGrowable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbasesettextctrlgrowable">external documentation</a>. -doc """ Sets the text control as growable when `grow` is true. @@ -265,7 +255,6 @@ setTextCtrlGrowable(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxPickerBase_SetTextCtrlGrowable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpickerbase.html#wxpickerbaseispickerctrlgrowable">external documentation</a>. -doc "Returns true if the picker control is growable.". -spec isPickerCtrlGrowable(This) -> boolean() when This::wxPickerBase(). @@ -275,554 +264,371 @@ isPickerCtrlGrowable(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxPickerBase_IsPickerCtrlGrowable). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPopupTransientWindow.erl b/lib/wx/src/gen/wxPopupTransientWindow.erl index 713be7a13c9b..b71911bc2854 100644 --- a/lib/wx/src/gen/wxPopupTransientWindow.erl +++ b/lib/wx/src/gen/wxPopupTransientWindow.erl @@ -20,21 +20,22 @@ -module(wxPopupTransientWindow). -moduledoc """ -Functions for wxPopupTransientWindow class +A `m:wxPopupWindow` which disappears automatically when the user clicks mouse outside it +or if it loses focus in any other way. -A `m:wxPopupWindow` which disappears automatically when the user clicks mouse -outside it or if it loses focus in any other way. - -This window can be useful for implementing custom combobox-like controls for -example. +This window can be useful for implementing custom combobox-like controls for example. See: `m:wxPopupWindow` -This class is derived (and can use functions) from: `m:wxPopupWindow` -`m:wxWindow` `m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxPopupWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` -wxWidgets docs: -[wxPopupTransientWindow](https://docs.wxwidgets.org/3.1/classwx_popup_transient_window.html) +wxWidgets docs: [wxPopupTransientWindow](https://docs.wxwidgets.org/3.2/classwx_popup_transient_window.html) """. -include("wxe.hrl"). -export([destroy/1,dismiss/1,new/0,new/1,new/2,popup/1,popup/2]). @@ -81,21 +82,19 @@ wxWidgets docs: -type wxPopupTransientWindow() :: wx:wx_object(). -export_type([wxPopupTransientWindow/0]). -%% @hidden -doc false. parent_class(wxPopupWindow) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopuptransientwindow.html#wxpopuptransientwindowwxpopuptransientwindow">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPopupTransientWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPopupTransientWindow_new_0), wxe_util:rec(?wxPopupTransientWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxPopupTransientWindow() when Parent::wxWindow:wxWindow(). @@ -103,7 +102,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopuptransientwindow.html#wxpopuptransientwindowwxpopuptransientwindow">external documentation</a>. -doc "Constructor.". -spec new(Parent, [Option]) -> wxPopupTransientWindow() when Parent::wxWindow:wxWindow(), @@ -117,7 +115,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxPopupTransientWindow_new_2), wxe_util:rec(?wxPopupTransientWindow_new_2). -%% @equiv popup(This, []) +-doc(#{equiv => popup(This, [])}). -spec popup(This) -> 'ok' when This::wxPopupTransientWindow(). @@ -125,14 +123,12 @@ popup(This) when is_record(This, wx_ref) -> popup(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopuptransientwindow.html#wxpopuptransientwindowpopup">external documentation</a>. -doc """ Popup the window (this will show it too). -If `focus` is non-NULL, it will be kept focused while this window is shown if -supported by the current platform, otherwise the popup itself will receive -focus. In any case, the popup will disappear automatically if it loses focus -because of a user action. +If `focus` is non-NULL, it will be kept focused while this window is shown if supported +by the current platform, otherwise the popup itself will receive focus. In any case, the +popup will disappear automatically if it loses focus because of a user action. See: `dismiss/1` """. @@ -147,7 +143,6 @@ popup(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxPopupTransientWindow_Popup). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopuptransientwindow.html#wxpopuptransientwindowdismiss">external documentation</a>. -doc "Hide the window.". -spec dismiss(This) -> 'ok' when This::wxPopupTransientWindow(). @@ -155,565 +150,380 @@ dismiss(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPopupTransientWindow), wxe_util:queue_cmd(This,?get_env(),?wxPopupTransientWindow_Dismiss). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPopupTransientWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPopupTransientWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPopupWindow -%% @hidden -doc false. position(This,PtOrigin,SizePopup) -> wxPopupWindow:position(This,PtOrigin,SizePopup). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPopupWindow.erl b/lib/wx/src/gen/wxPopupWindow.erl index 3418d67bc0a4..d5dbabb730eb 100644 --- a/lib/wx/src/gen/wxPopupWindow.erl +++ b/lib/wx/src/gen/wxPopupWindow.erl @@ -20,22 +20,32 @@ -module(wxPopupWindow). -moduledoc """ -Functions for wxPopupWindow class +A special kind of top level window used for popup menus, combobox popups and such. -A special kind of top level window used for popup menus, combobox popups and -such. - -Styles +## Styles This class supports the following styles: -See: `m:wxDialog`, `m:wxFrame` +* wxPU_CONTAINS_CONTROLS: By default in wxMSW, a popup window will not take focus from its +parent window. However many standard controls, including common ones such as `m:wxTextCtrl`, +need focus to function correctly and will not work when placed on a default popup. This +flag can be used to make the popup take focus and let all controls work but at the price +of not allowing the parent window to keep focus while the popup is shown, which can also +be sometimes desirable. This style is currently only implemented in MSW and simply does +nothing under the other platforms (it's new since wxWidgets 3.1.3). + +See: +* `m:wxDialog` + +* `m:wxFrame` + +This class is derived, and can use functions, from: + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxPopupWindow](https://docs.wxwidgets.org/3.1/classwx_popup_window.html) +wxWidgets docs: [wxPopupWindow](https://docs.wxwidgets.org/3.2/classwx_popup_window.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,new/0,new/1,new/2,position/3]). @@ -82,20 +92,18 @@ wxWidgets docs: -type wxPopupWindow() :: wx:wx_object(). -export_type([wxPopupWindow/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopupwindow.html#wxpopupwindowwxpopupwindow">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPopupWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPopupWindow_new_0), wxe_util:rec(?wxPopupWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxPopupWindow() when Parent::wxWindow:wxWindow(). @@ -103,7 +111,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopupwindow.html#wxpopupwindowwxpopupwindow">external documentation</a>. -doc "Constructor.". -spec new(Parent, [Option]) -> wxPopupWindow() when Parent::wxWindow:wxWindow(), @@ -117,7 +124,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxPopupWindow_new_2), wxe_util:rec(?wxPopupWindow_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxPopupWindow(), Parent::wxWindow:wxWindow(). @@ -125,7 +132,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopupwindow.html#wxpopupwindowcreate">external documentation</a>. -doc "Create method for two-step creation.". -spec create(This, Parent, [Option]) -> boolean() when This::wxPopupWindow(), Parent::wxWindow:wxWindow(), @@ -140,13 +146,11 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxPopupWindow_Create), wxe_util:rec(?wxPopupWindow_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpopupwindow.html#wxpopupwindowposition">external documentation</a>. -doc """ -Move the popup window to the right position, i.e. such that it is entirely -visible. +Move the popup window to the right position, i.e. such that it is entirely visible. -The popup is positioned at ptOrigin + size if it opens below and to the right -(default), at ptOrigin - sizePopup if it opens above and to the left etc. +The popup is positioned at ptOrigin + size if it opens below and to the right (default), +at ptOrigin - sizePopup if it opens above and to the left etc. """. -spec position(This, PtOrigin, SizePopup) -> 'ok' when This::wxPopupWindow(), PtOrigin::{X::integer(), Y::integer()}, SizePopup::{W::integer(), H::integer()}. @@ -155,561 +159,377 @@ position(#wx_ref{type=ThisT}=This,{PtOriginX,PtOriginY} = PtOrigin,{SizePopupW,S ?CLASS(ThisT,wxPopupWindow), wxe_util:queue_cmd(This,PtOrigin,SizePopup,?get_env(),?wxPopupWindow_Position). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPopupWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPopupWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPostScriptDC.erl b/lib/wx/src/gen/wxPostScriptDC.erl index 17570d37e505..b2b1bfb7e03e 100644 --- a/lib/wx/src/gen/wxPostScriptDC.erl +++ b/lib/wx/src/gen/wxPostScriptDC.erl @@ -20,22 +20,21 @@ -module(wxPostScriptDC). -moduledoc """ -Functions for wxPostScriptDC class +This defines the wxWidgets Encapsulated PostScript device context, which can write +PostScript files on any platform. -This defines the wxWidgets Encapsulated PostScript device context, which can -write PostScript files on any platform. See `m:wxDC` for descriptions of the -member functions. +See `m:wxDC` for descriptions of the member functions. Starting a document -Document should be started with call to `wxDC:startDoc/2` prior to calling any -function to execute a drawing operation. However, some functions, like -`wxDC:setFont/2`, may be legitimately called even before `wxDC:startDoc/2`. +Document should be started with call to `wxDC:startDoc/2` prior to calling any function to execute a +drawing operation. However, some functions, like `wxDC:setFont/2`, may be legitimately called even before `wxDC:startDoc/2`. -This class is derived (and can use functions) from: `m:wxDC` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxPostScriptDC](https://docs.wxwidgets.org/3.1/classwx_post_script_d_c.html) +* `m:wxDC` + +wxWidgets docs: [wxPostScriptDC](https://docs.wxwidgets.org/3.2/classwx_post_script_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/0,new/1]). @@ -64,18 +63,16 @@ wxWidgets docs: -type wxPostScriptDC() :: wx:wx_object(). -export_type([wxPostScriptDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpostscriptdc.html#wxpostscriptdcwxpostscriptdc">external documentation</a>. +-doc "". -spec new() -> wxPostScriptDC(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPostScriptDC_new_0), wxe_util:rec(?wxPostScriptDC_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpostscriptdc.html#wxpostscriptdcwxpostscriptdc">external documentation</a>. -doc "Constructs a PostScript printer device context from a `m:wxPrintData` object.". -spec new(PrintData) -> wxPostScriptDC() when PrintData::wxPrintData:wxPrintData(). @@ -84,287 +81,194 @@ new(#wx_ref{type=PrintDataT}=PrintData) -> wxe_util:queue_cmd(PrintData,?get_env(),?wxPostScriptDC_new_1), wxe_util:rec(?wxPostScriptDC_new_1). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPostScriptDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPostScriptDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxPreviewCanvas.erl b/lib/wx/src/gen/wxPreviewCanvas.erl index edd061f84457..7837ab21b727 100644 --- a/lib/wx/src/gen/wxPreviewCanvas.erl +++ b/lib/wx/src/gen/wxPreviewCanvas.erl @@ -20,18 +20,27 @@ -module(wxPreviewCanvas). -moduledoc """ -Functions for wxPreviewCanvas class +A preview canvas is the default canvas used by the print preview system to display the +preview. -A preview canvas is the default canvas used by the print preview system to -display the preview. +See: +* `m:wxPreviewFrame` -See: `m:wxPreviewFrame`, `m:wxPreviewControlBar`, `m:wxPrintPreview` +* `m:wxPreviewControlBar` -This class is derived (and can use functions) from: `m:wxScrolledWindow` -`m:wxPanel` `m:wxWindow` `m:wxEvtHandler` +* `m:wxPrintPreview` -wxWidgets docs: -[wxPreviewCanvas](https://docs.wxwidgets.org/3.1/classwx_preview_canvas.html) +This class is derived, and can use functions, from: + +* `m:wxScrolledWindow` + +* `m:wxPanel` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxPreviewCanvas](https://docs.wxwidgets.org/3.2/classwx_preview_canvas.html) """. -include("wxe.hrl"). -export([]). @@ -80,7 +89,6 @@ wxWidgets docs: -type wxPreviewCanvas() :: wx:wx_object(). -export_type([wxPreviewCanvas/0]). -%% @hidden -doc false. parent_class(wxScrolledWindow) -> true; parent_class(wxPanel) -> true; @@ -89,603 +97,404 @@ parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxScrolledWindow -%% @hidden -doc false. setTargetWindow(This,Window) -> wxScrolledWindow:setTargetWindow(This,Window). -%% @hidden -doc false. setScrollRate(This,Xstep,Ystep) -> wxScrolledWindow:setScrollRate(This,Xstep,Ystep). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Options). -%% @hidden -doc false. setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY) -> wxScrolledWindow:setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY). -%% @hidden -doc false. scroll(This,X,Y) -> wxScrolledWindow:scroll(This,X,Y). -%% @hidden -doc false. scroll(This,Pt) -> wxScrolledWindow:scroll(This,Pt). -%% @hidden -doc false. prepareDC(This,Dc) -> wxScrolledWindow:prepareDC(This,Dc). -%% @hidden -doc false. doPrepareDC(This,Dc) -> wxScrolledWindow:doPrepareDC(This,Dc). -%% @hidden -doc false. getViewStart(This) -> wxScrolledWindow:getViewStart(This). -%% @hidden -doc false. getScrollPixelsPerUnit(This) -> wxScrolledWindow:getScrollPixelsPerUnit(This). -%% @hidden -doc false. enableScrolling(This,XScrolling,YScrolling) -> wxScrolledWindow:enableScrolling(This,XScrolling,YScrolling). -%% @hidden -doc false. calcUnscrolledPosition(This,X,Y) -> wxScrolledWindow:calcUnscrolledPosition(This,X,Y). -%% @hidden -doc false. calcUnscrolledPosition(This,Pt) -> wxScrolledWindow:calcUnscrolledPosition(This,Pt). -%% @hidden -doc false. calcScrolledPosition(This,X,Y) -> wxScrolledWindow:calcScrolledPosition(This,X,Y). -%% @hidden -doc false. calcScrolledPosition(This,Pt) -> wxScrolledWindow:calcScrolledPosition(This,Pt). %% From wxPanel -%% @hidden -doc false. setFocusIgnoringChildren(This) -> wxPanel:setFocusIgnoringChildren(This). -%% @hidden -doc false. initDialog(This) -> wxPanel:initDialog(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPreviewControlBar.erl b/lib/wx/src/gen/wxPreviewControlBar.erl index eb53d432fd7b..8b40535d1833 100644 --- a/lib/wx/src/gen/wxPreviewControlBar.erl +++ b/lib/wx/src/gen/wxPreviewControlBar.erl @@ -20,21 +20,28 @@ -module(wxPreviewControlBar). -moduledoc """ -Functions for wxPreviewControlBar class +This is the default implementation of the preview control bar, a panel with buttons and a +zoom control. -This is the default implementation of the preview control bar, a panel with -buttons and a zoom control. +You can derive a new class from this and override some or all member functions to change +the behaviour and appearance; or you can leave it as it is. -You can derive a new class from this and override some or all member functions -to change the behaviour and appearance; or you can leave it as it is. +See: +* `m:wxPreviewFrame` -See: `m:wxPreviewFrame`, `m:wxPreviewCanvas`, `m:wxPrintPreview` +* `m:wxPreviewCanvas` -This class is derived (and can use functions) from: `m:wxPanel` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxPrintPreview` -wxWidgets docs: -[wxPreviewControlBar](https://docs.wxwidgets.org/3.1/classwx_preview_control_bar.html) +This class is derived, and can use functions, from: + +* `m:wxPanel` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxPreviewControlBar](https://docs.wxwidgets.org/3.2/classwx_preview_control_bar.html) """. -include("wxe.hrl"). -export([createButtons/1,destroy/1,getPrintPreview/1,getZoomControl/1,new/3, @@ -82,14 +89,13 @@ wxWidgets docs: -type wxPreviewControlBar() :: wx:wx_object(). -export_type([wxPreviewControlBar/0]). -%% @hidden -doc false. parent_class(wxPanel) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Preview,Buttons,Parent, []) +-doc(#{equiv => new(Preview,Buttons,Parent, [])}). -spec new(Preview, Buttons, Parent) -> wxPreviewControlBar() when Preview::wxPrintPreview:wxPrintPreview(), Buttons::integer(), Parent::wxWindow:wxWindow(). @@ -97,12 +103,21 @@ new(Preview,Buttons,Parent) when is_record(Preview, wx_ref),is_integer(Buttons),is_record(Parent, wx_ref) -> new(Preview,Buttons,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewcontrolbar.html#wxpreviewcontrolbarwxpreviewcontrolbar">external documentation</a>. -doc """ Constructor. -The `buttons` parameter may be a combination of the following, using the bitwise -'or' operator: +The `buttons` parameter may be a combination of the following, using the bitwise 'or' operator: + +* wxPREVIEW_PRINT: Create a print button. + +* wxPREVIEW_NEXT: Create a next page button. + +* wxPREVIEW_PREVIOUS: Create a previous page button. + +* wxPREVIEW_ZOOM: Create a zoom control. + +* wxPREVIEW_DEFAULT: Equivalent to a combination of `wxPREVIEW_PREVIOUS`, `wxPREVIEW_NEXT` +and `wxPREVIEW_ZOOM`. """. -spec new(Preview, Buttons, Parent, [Option]) -> wxPreviewControlBar() when Preview::wxPrintPreview:wxPrintPreview(), Buttons::integer(), Parent::wxWindow:wxWindow(), @@ -121,7 +136,6 @@ new(#wx_ref{type=PreviewT}=Preview,Buttons,#wx_ref{type=ParentT}=Parent, Options wxe_util:queue_cmd(Preview,Buttons,Parent, Opts,?get_env(),?wxPreviewControlBar_new), wxe_util:rec(?wxPreviewControlBar_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewcontrolbar.html#wxpreviewcontrolbarcreatebuttons">external documentation</a>. -doc "Creates buttons, according to value of the button style flags.". -spec createButtons(This) -> 'ok' when This::wxPreviewControlBar(). @@ -129,7 +143,6 @@ createButtons(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPreviewControlBar), wxe_util:queue_cmd(This,?get_env(),?wxPreviewControlBar_CreateButtons). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewcontrolbar.html#wxpreviewcontrolbargetprintpreview">external documentation</a>. -doc "Gets the print preview object associated with the control bar.". -spec getPrintPreview(This) -> wxPrintPreview:wxPrintPreview() when This::wxPreviewControlBar(). @@ -138,7 +151,6 @@ getPrintPreview(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPreviewControlBar_GetPrintPreview), wxe_util:rec(?wxPreviewControlBar_GetPrintPreview). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewcontrolbar.html#wxpreviewcontrolbargetzoomcontrol">external documentation</a>. -doc "Gets the current zoom setting in percent.". -spec getZoomControl(This) -> integer() when This::wxPreviewControlBar(). @@ -147,7 +159,6 @@ getZoomControl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPreviewControlBar_GetZoomControl), wxe_util:rec(?wxPreviewControlBar_GetZoomControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewcontrolbar.html#wxpreviewcontrolbarsetzoomcontrol">external documentation</a>. -doc "Sets the zoom control.". -spec setZoomControl(This, Percent) -> 'ok' when This::wxPreviewControlBar(), Percent::integer(). @@ -156,565 +167,380 @@ setZoomControl(#wx_ref{type=ThisT}=This,Percent) ?CLASS(ThisT,wxPreviewControlBar), wxe_util:queue_cmd(This,Percent,?get_env(),?wxPreviewControlBar_SetZoomControl). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPreviewControlBar()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPreviewControlBar), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPanel -%% @hidden -doc false. setFocusIgnoringChildren(This) -> wxPanel:setFocusIgnoringChildren(This). -%% @hidden -doc false. initDialog(This) -> wxPanel:initDialog(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPreviewFrame.erl b/lib/wx/src/gen/wxPreviewFrame.erl index e123821b0c18..74c6326106b2 100644 --- a/lib/wx/src/gen/wxPreviewFrame.erl +++ b/lib/wx/src/gen/wxPreviewFrame.erl @@ -20,19 +20,29 @@ -module(wxPreviewFrame). -moduledoc """ -Functions for wxPreviewFrame class - This class provides the default method of managing the print preview interface. -Member functions may be overridden to replace functionality, or the class may be -used without derivation. -See: `m:wxPreviewCanvas`, `m:wxPreviewControlBar`, `m:wxPrintPreview` +Member functions may be overridden to replace functionality, or the class may be used +without derivation. + +See: +* `m:wxPreviewCanvas` + +* `m:wxPreviewControlBar` + +* `m:wxPrintPreview` + +This class is derived, and can use functions, from: + +* `m:wxFrame` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxFrame` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxPreviewFrame](https://docs.wxwidgets.org/3.1/classwx_preview_frame.html) +wxWidgets docs: [wxPreviewFrame](https://docs.wxwidgets.org/3.2/classwx_preview_frame.html) """. -include("wxe.hrl"). -export([createCanvas/1,createControlBar/1,destroy/1,initialize/1,new/2,new/3, @@ -88,7 +98,6 @@ wxWidgets docs: -type wxPreviewFrame() :: wx:wx_object(). -export_type([wxPreviewFrame/0]). -%% @hidden -doc false. parent_class(wxFrame) -> true; parent_class(wxTopLevelWindow) -> true; @@ -96,7 +105,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Preview,Parent, []) +-doc(#{equiv => new(Preview,Parent, [])}). -spec new(Preview, Parent) -> wxPreviewFrame() when Preview::wxPrintPreview:wxPrintPreview(), Parent::wxWindow:wxWindow(). @@ -104,12 +113,11 @@ new(Preview,Parent) when is_record(Preview, wx_ref),is_record(Parent, wx_ref) -> new(Preview,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewframe.html#wxpreviewframewxpreviewframe">external documentation</a>. -doc """ Constructor. -Pass a print preview object plus other normal frame arguments. The print preview -object will be destroyed by the frame when it closes. +Pass a print preview object plus other normal frame arguments. The print preview object +will be destroyed by the frame when it closes. """. -spec new(Preview, Parent, [Option]) -> wxPreviewFrame() when Preview::wxPrintPreview:wxPrintPreview(), Parent::wxWindow:wxWindow(), @@ -130,12 +138,10 @@ new(#wx_ref{type=PreviewT}=Preview,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Preview,Parent, Opts,?get_env(),?wxPreviewFrame_new), wxe_util:rec(?wxPreviewFrame_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewframe.html#wxpreviewframecreatecontrolbar">external documentation</a>. -doc """ Creates a `m:wxPreviewControlBar`. -Override this function to allow a user-defined preview control bar object to be -created. +Override this function to allow a user-defined preview control bar object to be created. """. -spec createControlBar(This) -> 'ok' when This::wxPreviewFrame(). @@ -143,12 +149,10 @@ createControlBar(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPreviewFrame), wxe_util:queue_cmd(This,?get_env(),?wxPreviewFrame_CreateControlBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewframe.html#wxpreviewframecreatecanvas">external documentation</a>. -doc """ Creates a `m:wxPreviewCanvas`. -Override this function to allow a user-defined preview canvas object to be -created. +Override this function to allow a user-defined preview canvas object to be created. """. -spec createCanvas(This) -> 'ok' when This::wxPreviewFrame(). @@ -156,17 +160,14 @@ createCanvas(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPreviewFrame), wxe_util:queue_cmd(This,?get_env(),?wxPreviewFrame_CreateCanvas). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewframe.html#wxpreviewframeinitialize">external documentation</a>. -doc """ Initializes the frame elements and prepares for showing it. -Calling this method is equivalent to calling `InitializeWithModality()` (not -implemented in wx) with wxPreviewFrame_AppModal argument, please see its -documentation for more details. +Calling this method is equivalent to calling `InitializeWithModality()` (not implemented +in wx) with wxPreviewFrame_AppModal argument, please see its documentation for more details. -Please notice that this function is virtual mostly for backwards compatibility -only, there is no real need to override it as it's never called by wxWidgets -itself. +Please notice that this function is virtual mostly for backwards compatibility only, +there is no real need to override it as it's never called by wxWidgets itself. """. -spec initialize(This) -> 'ok' when This::wxPreviewFrame(). @@ -174,11 +175,9 @@ initialize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPreviewFrame), wxe_util:queue_cmd(This,?get_env(),?wxPreviewFrame_Initialize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxpreviewframe.html#wxpreviewframeonclosewindow">external documentation</a>. -doc """ -Enables any disabled frames in the application, and deletes the print preview -object, implicitly deleting any printout objects associated with the print -preview object. +Enables any disabled frames in the application, and deletes the print preview object, +implicitly deleting any printout objects associated with the print preview object. """. -spec onCloseWindow(This, Event) -> 'ok' when This::wxPreviewFrame(), Event::wxCloseEvent:wxCloseEvent(). @@ -187,689 +186,463 @@ onCloseWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=EventT}=Event) -> ?CLASS(EventT,wxCloseEvent), wxe_util:queue_cmd(This,Event,?get_env(),?wxPreviewFrame_OnCloseWindow). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPreviewFrame()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPreviewFrame), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFrame -%% @hidden -doc false. setToolBar(This,ToolBar) -> wxFrame:setToolBar(This,ToolBar). -%% @hidden -doc false. setStatusWidths(This,Widths_field) -> wxFrame:setStatusWidths(This,Widths_field). -%% @hidden -doc false. setStatusText(This,Text, Options) -> wxFrame:setStatusText(This,Text, Options). -%% @hidden -doc false. setStatusText(This,Text) -> wxFrame:setStatusText(This,Text). -%% @hidden -doc false. setStatusBarPane(This,N) -> wxFrame:setStatusBarPane(This,N). -%% @hidden -doc false. setStatusBar(This,StatusBar) -> wxFrame:setStatusBar(This,StatusBar). -%% @hidden -doc false. setMenuBar(This,MenuBar) -> wxFrame:setMenuBar(This,MenuBar). -%% @hidden -doc false. sendSizeEvent(This, Options) -> wxFrame:sendSizeEvent(This, Options). -%% @hidden -doc false. sendSizeEvent(This) -> wxFrame:sendSizeEvent(This). -%% @hidden -doc false. processCommand(This,Id) -> wxFrame:processCommand(This,Id). -%% @hidden -doc false. getToolBar(This) -> wxFrame:getToolBar(This). -%% @hidden -doc false. getStatusBarPane(This) -> wxFrame:getStatusBarPane(This). -%% @hidden -doc false. getStatusBar(This) -> wxFrame:getStatusBar(This). -%% @hidden -doc false. getMenuBar(This) -> wxFrame:getMenuBar(This). -%% @hidden -doc false. getClientAreaOrigin(This) -> wxFrame:getClientAreaOrigin(This). -%% @hidden -doc false. createToolBar(This, Options) -> wxFrame:createToolBar(This, Options). -%% @hidden -doc false. createToolBar(This) -> wxFrame:createToolBar(This). -%% @hidden -doc false. createStatusBar(This, Options) -> wxFrame:createStatusBar(This, Options). -%% @hidden -doc false. createStatusBar(This) -> wxFrame:createStatusBar(This). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPrintData.erl b/lib/wx/src/gen/wxPrintData.erl index 745a251db069..043b0d7f4653 100644 --- a/lib/wx/src/gen/wxPrintData.erl +++ b/lib/wx/src/gen/wxPrintData.erl @@ -20,23 +20,29 @@ -module(wxPrintData). -moduledoc """ -Functions for wxPrintData class - This class holds a variety of information related to printers and printer device -contexts. This class is used to create a `wxPrinterDC` (not implemented in wx) -and a `m:wxPostScriptDC`. It is also used as a data member of -`m:wxPrintDialogData` and `m:wxPageSetupDialogData`, as part of the mechanism -for transferring data between the print dialogs and the application. +contexts. + +This class is used to create a `wxPrinterDC` (not implemented in wx) and a `m:wxPostScriptDC`. +It is also used as a data member of `m:wxPrintDialogData` and `m:wxPageSetupDialogData`, +as part of the mechanism for transferring data between the print dialogs and the application. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`m:wxPrintDialog`, `m:wxPageSetupDialog`, `m:wxPrintDialogData`, -`m:wxPageSetupDialogData`, -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_print), -`wxPrinterDC` (not implemented in wx), `m:wxPostScriptDC` - -wxWidgets docs: -[wxPrintData](https://docs.wxwidgets.org/3.1/classwx_print_data.html) +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) + +* `m:wxPrintDialog` + +* `m:wxPageSetupDialog` + +* `m:wxPrintDialogData` + +* `m:wxPageSetupDialogData` + +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_print) + +* `m:wxPostScriptDC` + +wxWidgets docs: [wxPrintData](https://docs.wxwidgets.org/3.2/classwx_print_data.html) """. -include("wxe.hrl"). -export([destroy/1,getBin/1,getCollate/1,getColour/1,getDuplex/1,getNoCopies/1, @@ -49,18 +55,15 @@ wxWidgets docs: -type wxPrintData() :: wx:wx_object(). -export_type([wxPrintData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatawxprintdata">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPrintData(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPrintData_new_0), wxe_util:rec(?wxPrintData_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatawxprintdata">external documentation</a>. -doc "Copy constructor.". -spec new(Data) -> wxPrintData() when Data::wxPrintData(). @@ -69,7 +72,6 @@ new(#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(Data,?get_env(),?wxPrintData_new_1), wxe_util:rec(?wxPrintData_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetcollate">external documentation</a>. -doc "Returns true if collation is on.". -spec getCollate(This) -> boolean() when This::wxPrintData(). @@ -78,16 +80,14 @@ getCollate(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetCollate), wxe_util:rec(?wxPrintData_GetCollate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetbin">external documentation</a>. -%%<br /> Res = ?wxPRINTBIN_DEFAULT | ?wxPRINTBIN_ONLYONE | ?wxPRINTBIN_LOWER | ?wxPRINTBIN_MIDDLE | ?wxPRINTBIN_MANUAL | ?wxPRINTBIN_ENVELOPE | ?wxPRINTBIN_ENVMANUAL | ?wxPRINTBIN_AUTO | ?wxPRINTBIN_TRACTOR | ?wxPRINTBIN_SMALLFMT | ?wxPRINTBIN_LARGEFMT | ?wxPRINTBIN_LARGECAPACITY | ?wxPRINTBIN_CASSETTE | ?wxPRINTBIN_FORMSOURCE | ?wxPRINTBIN_USER -doc """ Returns the current bin (papersource). -By default, the system is left to select the bin (`wxPRINTBIN_DEFAULT` is -returned). +By default, the system is left to select the bin (`wxPRINTBIN_DEFAULT` is returned). See `setBin/2` for the full list of bin values. """. +%% Res = ?wxPRINTBIN_DEFAULT | ?wxPRINTBIN_ONLYONE | ?wxPRINTBIN_LOWER | ?wxPRINTBIN_MIDDLE | ?wxPRINTBIN_MANUAL | ?wxPRINTBIN_ENVELOPE | ?wxPRINTBIN_ENVMANUAL | ?wxPRINTBIN_AUTO | ?wxPRINTBIN_TRACTOR | ?wxPRINTBIN_SMALLFMT | ?wxPRINTBIN_LARGEFMT | ?wxPRINTBIN_LARGECAPACITY | ?wxPRINTBIN_CASSETTE | ?wxPRINTBIN_FORMSOURCE | ?wxPRINTBIN_USER -spec getBin(This) -> wx:wx_enum() when This::wxPrintData(). getBin(#wx_ref{type=ThisT}=This) -> @@ -95,7 +95,6 @@ getBin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetBin), wxe_util:rec(?wxPrintData_GetBin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetcolour">external documentation</a>. -doc "Returns true if colour printing is on.". -spec getColour(This) -> boolean() when This::wxPrintData(). @@ -104,13 +103,12 @@ getColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetColour), wxe_util:rec(?wxPrintData_GetColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetduplex">external documentation</a>. -%%<br /> Res = ?wxDUPLEX_SIMPLEX | ?wxDUPLEX_HORIZONTAL | ?wxDUPLEX_VERTICAL -doc """ Returns the duplex mode. One of wxDUPLEX_SIMPLEX, wxDUPLEX_HORIZONTAL, wxDUPLEX_VERTICAL. """. +%% Res = ?wxDUPLEX_SIMPLEX | ?wxDUPLEX_HORIZONTAL | ?wxDUPLEX_VERTICAL -spec getDuplex(This) -> wx:wx_enum() when This::wxPrintData(). getDuplex(#wx_ref{type=ThisT}=This) -> @@ -118,7 +116,6 @@ getDuplex(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetDuplex), wxe_util:rec(?wxPrintData_GetDuplex). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetnocopies">external documentation</a>. -doc "Returns the number of copies requested by the user.". -spec getNoCopies(This) -> integer() when This::wxPrintData(). @@ -127,13 +124,12 @@ getNoCopies(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetNoCopies), wxe_util:rec(?wxPrintData_GetNoCopies). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetorientation">external documentation</a>. -%%<br /> Res = ?wxPORTRAIT | ?wxLANDSCAPE -doc """ Gets the orientation. This can be wxLANDSCAPE or wxPORTRAIT. """. +%% Res = ?wxPORTRAIT | ?wxLANDSCAPE -spec getOrientation(This) -> wx:wx_enum() when This::wxPrintData(). getOrientation(#wx_ref{type=ThisT}=This) -> @@ -141,13 +137,12 @@ getOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetOrientation), wxe_util:rec(?wxPrintData_GetOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetpaperid">external documentation</a>. -%%<br /> Res = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -doc """ Returns the paper size id. See: `setPaperId/2` """. +%% Res = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -spec getPaperId(This) -> wx:wx_enum() when This::wxPrintData(). getPaperId(#wx_ref{type=ThisT}=This) -> @@ -155,12 +150,11 @@ getPaperId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetPaperId), wxe_util:rec(?wxPrintData_GetPaperId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetprintername">external documentation</a>. -doc """ Returns the printer name. -If the printer name is the empty string, it indicates that the default printer -should be used. +If the printer name is the empty string, it indicates that the default printer should be +used. """. -spec getPrinterName(This) -> unicode:charlist() when This::wxPrintData(). @@ -169,15 +163,22 @@ getPrinterName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetPrinterName), wxe_util:rec(?wxPrintData_GetPrinterName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatagetquality">external documentation</a>. -doc """ Returns the current print quality. -This can be a positive integer, denoting the number of dots per inch, or one of -the following identifiers: +This can be a positive integer, denoting the number of dots per inch, or one of the +following identifiers: -On input you should pass one of these identifiers, but on return you may get -back a positive integer indicating the current resolution setting. +* wxPRINT_QUALITY_HIGH + +* wxPRINT_QUALITY_MEDIUM + +* wxPRINT_QUALITY_LOW + +* wxPRINT_QUALITY_DRAFT + +On input you should pass one of these identifiers, but on return you may get back a +positive integer indicating the current resolution setting. """. -spec getQuality(This) -> integer() when This::wxPrintData(). @@ -186,12 +187,11 @@ getQuality(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_GetQuality), wxe_util:rec(?wxPrintData_GetQuality). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdataisok">external documentation</a>. -doc """ Returns true if the print data is valid for using in print dialogs. -This can return false on Windows if the current printer is not set, for example. -On all other platforms, it returns true. +This can return false on Windows if the current printer is not set, for example. On all +other platforms, it returns true. """. -spec isOk(This) -> boolean() when This::wxPrintData(). @@ -200,9 +200,8 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintData_IsOk), wxe_util:rec(?wxPrintData_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetbin">external documentation</a>. -%%<br /> Flag = ?wxPRINTBIN_DEFAULT | ?wxPRINTBIN_ONLYONE | ?wxPRINTBIN_LOWER | ?wxPRINTBIN_MIDDLE | ?wxPRINTBIN_MANUAL | ?wxPRINTBIN_ENVELOPE | ?wxPRINTBIN_ENVMANUAL | ?wxPRINTBIN_AUTO | ?wxPRINTBIN_TRACTOR | ?wxPRINTBIN_SMALLFMT | ?wxPRINTBIN_LARGEFMT | ?wxPRINTBIN_LARGECAPACITY | ?wxPRINTBIN_CASSETTE | ?wxPRINTBIN_FORMSOURCE | ?wxPRINTBIN_USER -doc "Sets the current bin.". +%% Flag = ?wxPRINTBIN_DEFAULT | ?wxPRINTBIN_ONLYONE | ?wxPRINTBIN_LOWER | ?wxPRINTBIN_MIDDLE | ?wxPRINTBIN_MANUAL | ?wxPRINTBIN_ENVELOPE | ?wxPRINTBIN_ENVMANUAL | ?wxPRINTBIN_AUTO | ?wxPRINTBIN_TRACTOR | ?wxPRINTBIN_SMALLFMT | ?wxPRINTBIN_LARGEFMT | ?wxPRINTBIN_LARGECAPACITY | ?wxPRINTBIN_CASSETTE | ?wxPRINTBIN_FORMSOURCE | ?wxPRINTBIN_USER -spec setBin(This, Flag) -> 'ok' when This::wxPrintData(), Flag::wx:wx_enum(). setBin(#wx_ref{type=ThisT}=This,Flag) @@ -210,7 +209,6 @@ setBin(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintData_SetBin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetcollate">external documentation</a>. -doc "Sets collation to on or off.". -spec setCollate(This, Flag) -> 'ok' when This::wxPrintData(), Flag::boolean(). @@ -219,7 +217,6 @@ setCollate(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintData_SetCollate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetcolour">external documentation</a>. -doc "Sets colour printing on or off.". -spec setColour(This, Flag) -> 'ok' when This::wxPrintData(), Flag::boolean(). @@ -228,13 +225,12 @@ setColour(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintData_SetColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetduplex">external documentation</a>. -%%<br /> Mode = ?wxDUPLEX_SIMPLEX | ?wxDUPLEX_HORIZONTAL | ?wxDUPLEX_VERTICAL -doc """ Returns the duplex mode. One of wxDUPLEX_SIMPLEX, wxDUPLEX_HORIZONTAL, wxDUPLEX_VERTICAL. """. +%% Mode = ?wxDUPLEX_SIMPLEX | ?wxDUPLEX_HORIZONTAL | ?wxDUPLEX_VERTICAL -spec setDuplex(This, Mode) -> 'ok' when This::wxPrintData(), Mode::wx:wx_enum(). setDuplex(#wx_ref{type=ThisT}=This,Mode) @@ -242,7 +238,6 @@ setDuplex(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Mode,?get_env(),?wxPrintData_SetDuplex). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetnocopies">external documentation</a>. -doc "Sets the default number of copies to be printed out.". -spec setNoCopies(This, N) -> 'ok' when This::wxPrintData(), N::integer(). @@ -251,13 +246,12 @@ setNoCopies(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,N,?get_env(),?wxPrintData_SetNoCopies). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetorientation">external documentation</a>. -%%<br /> Orientation = ?wxPORTRAIT | ?wxLANDSCAPE -doc """ Sets the orientation. This can be wxLANDSCAPE or wxPORTRAIT. """. +%% Orientation = ?wxPORTRAIT | ?wxLANDSCAPE -spec setOrientation(This, Orientation) -> 'ok' when This::wxPrintData(), Orientation::wx:wx_enum(). setOrientation(#wx_ref{type=ThisT}=This,Orientation) @@ -265,17 +259,13 @@ setOrientation(#wx_ref{type=ThisT}=This,Orientation) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Orientation,?get_env(),?wxPrintData_SetOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetpaperid">external documentation</a>. -%%<br /> PaperId = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -doc """ Sets the paper id. -This indicates the type of paper to be used. For a mapping between paper id, -paper size and string name, see wxPrintPaperDatabase in `"paper.h"` (not yet -documented). - -See: `SetPaperSize()` (not implemented in wx) +This indicates the type of paper to be used. For a mapping between paper id, paper size +and string name, see wxPrintPaperDatabase in `"paper.h"` (not yet documented). """. +%% PaperId = ?wxPAPER_NONE | ?wxPAPER_LETTER | ?wxPAPER_LEGAL | ?wxPAPER_A4 | ?wxPAPER_CSHEET | ?wxPAPER_DSHEET | ?wxPAPER_ESHEET | ?wxPAPER_LETTERSMALL | ?wxPAPER_TABLOID | ?wxPAPER_LEDGER | ?wxPAPER_STATEMENT | ?wxPAPER_EXECUTIVE | ?wxPAPER_A3 | ?wxPAPER_A4SMALL | ?wxPAPER_A5 | ?wxPAPER_B4 | ?wxPAPER_B5 | ?wxPAPER_FOLIO | ?wxPAPER_QUARTO | ?wxPAPER_10X14 | ?wxPAPER_11X17 | ?wxPAPER_NOTE | ?wxPAPER_ENV_9 | ?wxPAPER_ENV_10 | ?wxPAPER_ENV_11 | ?wxPAPER_ENV_12 | ?wxPAPER_ENV_14 | ?wxPAPER_ENV_DL | ?wxPAPER_ENV_C5 | ?wxPAPER_ENV_C3 | ?wxPAPER_ENV_C4 | ?wxPAPER_ENV_C6 | ?wxPAPER_ENV_C65 | ?wxPAPER_ENV_B4 | ?wxPAPER_ENV_B5 | ?wxPAPER_ENV_B6 | ?wxPAPER_ENV_ITALY | ?wxPAPER_ENV_MONARCH | ?wxPAPER_ENV_PERSONAL | ?wxPAPER_FANFOLD_US | ?wxPAPER_FANFOLD_STD_GERMAN | ?wxPAPER_FANFOLD_LGL_GERMAN | ?wxPAPER_ISO_B4 | ?wxPAPER_JAPANESE_POSTCARD | ?wxPAPER_9X11 | ?wxPAPER_10X11 | ?wxPAPER_15X11 | ?wxPAPER_ENV_INVITE | ?wxPAPER_LETTER_EXTRA | ?wxPAPER_LEGAL_EXTRA | ?wxPAPER_TABLOID_EXTRA | ?wxPAPER_A4_EXTRA | ?wxPAPER_LETTER_TRANSVERSE | ?wxPAPER_A4_TRANSVERSE | ?wxPAPER_LETTER_EXTRA_TRANSVERSE | ?wxPAPER_A_PLUS | ?wxPAPER_B_PLUS | ?wxPAPER_LETTER_PLUS | ?wxPAPER_A4_PLUS | ?wxPAPER_A5_TRANSVERSE | ?wxPAPER_B5_TRANSVERSE | ?wxPAPER_A3_EXTRA | ?wxPAPER_A5_EXTRA | ?wxPAPER_B5_EXTRA | ?wxPAPER_A2 | ?wxPAPER_A3_TRANSVERSE | ?wxPAPER_A3_EXTRA_TRANSVERSE | ?wxPAPER_DBL_JAPANESE_POSTCARD | ?wxPAPER_A6 | ?wxPAPER_JENV_KAKU2 | ?wxPAPER_JENV_KAKU3 | ?wxPAPER_JENV_CHOU3 | ?wxPAPER_JENV_CHOU4 | ?wxPAPER_LETTER_ROTATED | ?wxPAPER_A3_ROTATED | ?wxPAPER_A4_ROTATED | ?wxPAPER_A5_ROTATED | ?wxPAPER_B4_JIS_ROTATED | ?wxPAPER_B5_JIS_ROTATED | ?wxPAPER_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_DBL_JAPANESE_POSTCARD_ROTATED | ?wxPAPER_A6_ROTATED | ?wxPAPER_JENV_KAKU2_ROTATED | ?wxPAPER_JENV_KAKU3_ROTATED | ?wxPAPER_JENV_CHOU3_ROTATED | ?wxPAPER_JENV_CHOU4_ROTATED | ?wxPAPER_B6_JIS | ?wxPAPER_B6_JIS_ROTATED | ?wxPAPER_12X11 | ?wxPAPER_JENV_YOU4 | ?wxPAPER_JENV_YOU4_ROTATED | ?wxPAPER_P16K | ?wxPAPER_P32K | ?wxPAPER_P32KBIG | ?wxPAPER_PENV_1 | ?wxPAPER_PENV_2 | ?wxPAPER_PENV_3 | ?wxPAPER_PENV_4 | ?wxPAPER_PENV_5 | ?wxPAPER_PENV_6 | ?wxPAPER_PENV_7 | ?wxPAPER_PENV_8 | ?wxPAPER_PENV_9 | ?wxPAPER_PENV_10 | ?wxPAPER_P16K_ROTATED | ?wxPAPER_P32K_ROTATED | ?wxPAPER_P32KBIG_ROTATED | ?wxPAPER_PENV_1_ROTATED | ?wxPAPER_PENV_2_ROTATED | ?wxPAPER_PENV_3_ROTATED | ?wxPAPER_PENV_4_ROTATED | ?wxPAPER_PENV_5_ROTATED | ?wxPAPER_PENV_6_ROTATED | ?wxPAPER_PENV_7_ROTATED | ?wxPAPER_PENV_8_ROTATED | ?wxPAPER_PENV_9_ROTATED | ?wxPAPER_PENV_10_ROTATED | ?wxPAPER_A0 | ?wxPAPER_A1 -spec setPaperId(This, PaperId) -> 'ok' when This::wxPrintData(), PaperId::wx:wx_enum(). setPaperId(#wx_ref{type=ThisT}=This,PaperId) @@ -283,12 +273,10 @@ setPaperId(#wx_ref{type=ThisT}=This,PaperId) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,PaperId,?get_env(),?wxPrintData_SetPaperId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetprintername">external documentation</a>. -doc """ Sets the printer name. -This can be the empty string to indicate that the default printer should be -used. +This can be the empty string to indicate that the default printer should be used. """. -spec setPrinterName(This, PrinterName) -> 'ok' when This::wxPrintData(), PrinterName::unicode:chardata(). @@ -298,15 +286,22 @@ setPrinterName(#wx_ref{type=ThisT}=This,PrinterName) PrinterName_UC = unicode:characters_to_binary(PrinterName), wxe_util:queue_cmd(This,PrinterName_UC,?get_env(),?wxPrintData_SetPrinterName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdata.html#wxprintdatasetquality">external documentation</a>. -doc """ Sets the desired print quality. -This can be a positive integer, denoting the number of dots per inch, or one of -the following identifiers: +This can be a positive integer, denoting the number of dots per inch, or one of the +following identifiers: + +* wxPRINT_QUALITY_HIGH + +* wxPRINT_QUALITY_MEDIUM + +* wxPRINT_QUALITY_LOW + +* wxPRINT_QUALITY_DRAFT -On input you should pass one of these identifiers, but on return you may get -back a positive integer indicating the current resolution setting. +On input you should pass one of these identifiers, but on return you may get back a +positive integer indicating the current resolution setting. """. -spec setQuality(This, Quality) -> 'ok' when This::wxPrintData(), Quality::integer(). @@ -315,8 +310,7 @@ setQuality(#wx_ref{type=ThisT}=This,Quality) ?CLASS(ThisT,wxPrintData), wxe_util:queue_cmd(This,Quality,?get_env(),?wxPrintData_SetQuality). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPrintData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrintData), diff --git a/lib/wx/src/gen/wxPrintDialog.erl b/lib/wx/src/gen/wxPrintDialog.erl index f168d846627d..2d572cbda3c8 100644 --- a/lib/wx/src/gen/wxPrintDialog.erl +++ b/lib/wx/src/gen/wxPrintDialog.erl @@ -20,21 +20,27 @@ -module(wxPrintDialog). -moduledoc """ -Functions for wxPrintDialog class +This class represents the print and print setup common dialogs. -This class represents the print and print setup common dialogs. You may obtain a -`wxPrinterDC` (not implemented in wx) device context from a successfully +You may obtain a `wxPrinterDC` (not implemented in wx) device context from a successfully dismissed print dialog. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_print) +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_print) -wxWidgets docs: -[wxPrintDialog](https://docs.wxwidgets.org/3.1/classwx_print_dialog.html) +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxPrintDialog](https://docs.wxwidgets.org/3.2/classwx_print_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getPrintDC/1,getPrintDialogData/1,new/1,new/2]). @@ -86,7 +92,6 @@ wxWidgets docs: -type wxPrintDialog() :: wx:wx_object(). -export_type([wxPrintDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -94,7 +99,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxPrintDialog() when Parent::wxWindow:wxWindow(). @@ -102,11 +107,7 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialog.html#wxprintdialogwxprintdialog">external documentation</a>. -%% <br /> Also:<br /> -%% new(Parent, Data) -> wxPrintDialog() when<br /> -%% Parent::wxWindow:wxWindow(), Data::wxPrintData:wxPrintData().<br /> -%% +-doc "". -spec new(Parent, [Option]) -> wxPrintDialog() when Parent::wxWindow:wxWindow(), Option :: {'data', wxPrintDialogData:wxPrintDialogData()}; @@ -126,7 +127,6 @@ new(#wx_ref{type=ParentT}=Parent,#wx_ref{type=DataT}=Data) -> wxe_util:queue_cmd(Parent,Data,?get_env(),?wxPrintDialog_new_2_1), wxe_util:rec(?wxPrintDialog_new_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialog.html#wxprintdialoggetprintdialogdata">external documentation</a>. -doc "Returns the print dialog data associated with the print dialog.". -spec getPrintDialogData(This) -> wxPrintDialogData:wxPrintDialogData() when This::wxPrintDialog(). @@ -135,12 +135,11 @@ getPrintDialogData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialog_GetPrintDialogData), wxe_util:rec(?wxPrintDialog_GetPrintDialogData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialog.html#wxprintdialoggetprintdc">external documentation</a>. -doc """ Returns the device context created by the print dialog, if any. -When this function has been called, the ownership of the device context is -transferred to the application, so it must then be deleted explicitly. +When this function has been called, the ownership of the device context is transferred to +the application, so it must then be deleted explicitly. """. -spec getPrintDC(This) -> wxDC:wxDC() when This::wxPrintDialog(). @@ -149,664 +148,443 @@ getPrintDC(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialog_GetPrintDC), wxe_util:rec(?wxPrintDialog_GetPrintDC). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -If `getPrintDC/1` has not been called, the device context obtained by the dialog -(if any) will be deleted. -""". +-doc "Destroys the object". -spec destroy(This::wxPrintDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrintDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxPrintDialogData.erl b/lib/wx/src/gen/wxPrintDialogData.erl index 55eb3aba9f59..cf8489c6df76 100644 --- a/lib/wx/src/gen/wxPrintDialogData.erl +++ b/lib/wx/src/gen/wxPrintDialogData.erl @@ -20,19 +20,18 @@ -module(wxPrintDialogData). -moduledoc """ -Functions for wxPrintDialogData class +This class holds information related to the visual characteristics of `m:wxPrintDialog`. -This class holds information related to the visual characteristics of -`m:wxPrintDialog`. It contains a `m:wxPrintData` object with underlying printing -settings. +It contains a `m:wxPrintData` object with underlying printing settings. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`m:wxPrintDialog`, -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_print) +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) -wxWidgets docs: -[wxPrintDialogData](https://docs.wxwidgets.org/3.1/classwx_print_dialog_data.html) +* `m:wxPrintDialog` + +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_print) + +wxWidgets docs: [wxPrintDialogData](https://docs.wxwidgets.org/3.2/classwx_print_dialog_data.html) """. -include("wxe.hrl"). -export([destroy/1,enableHelp/2,enablePageNumbers/2,enablePrintToFile/2,enableSelection/2, @@ -46,18 +45,15 @@ wxWidgets docs: -type wxPrintDialogData() :: wx:wx_object(). -export_type([wxPrintDialogData/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatawxprintdialogdata">external documentation</a>. -doc "Default constructor.". -spec new() -> wxPrintDialogData(). new() -> wxe_util:queue_cmd(?get_env(), ?wxPrintDialogData_new_0), wxe_util:rec(?wxPrintDialogData_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatawxprintdialogdata">external documentation</a>. -doc "Copy constructor.". -spec new(DialogData) -> wxPrintDialogData() when DialogData::wxPrintDialogData:wxPrintDialogData() | wxPrintData:wxPrintData(). @@ -72,7 +68,6 @@ new(#wx_ref{type=DialogDataT}=DialogData) -> wxe_util:queue_cmd(wx:typeCast(DialogData, DialogDataType),?get_env(),?wxPrintDialogData_new_1), wxe_util:rec(?wxPrintDialogData_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdataenablehelp">external documentation</a>. -doc """ Enables or disables the "Help" button. """. @@ -83,7 +78,6 @@ enableHelp(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_EnableHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdataenablepagenumbers">external documentation</a>. -doc """ Enables or disables the "Page numbers" controls. """. @@ -94,7 +88,6 @@ enablePageNumbers(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_EnablePageNumbers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdataenableprinttofile">external documentation</a>. -doc """ Enables or disables the "Print to file" checkbox. """. @@ -105,7 +98,6 @@ enablePrintToFile(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_EnablePrintToFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdataenableselection">external documentation</a>. -doc """ Enables or disables the "Selection" radio button. """. @@ -116,7 +108,6 @@ enableSelection(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_EnableSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetallpages">external documentation</a>. -doc "Returns true if the user requested that all pages be printed.". -spec getAllPages(This) -> boolean() when This::wxPrintDialogData(). @@ -125,7 +116,6 @@ getAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetAllPages), wxe_util:rec(?wxPrintDialogData_GetAllPages). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetcollate">external documentation</a>. -doc "Returns true if the user requested that the document(s) be collated.". -spec getCollate(This) -> boolean() when This::wxPrintDialogData(). @@ -134,7 +124,6 @@ getCollate(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetCollate), wxe_util:rec(?wxPrintDialogData_GetCollate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetfrompage">external documentation</a>. -doc "Returns the `from` page number, as entered by the user.". -spec getFromPage(This) -> integer() when This::wxPrintDialogData(). @@ -143,7 +132,6 @@ getFromPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetFromPage), wxe_util:rec(?wxPrintDialogData_GetFromPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetmaxpage">external documentation</a>. -doc "Returns the `maximum` page number.". -spec getMaxPage(This) -> integer() when This::wxPrintDialogData(). @@ -152,7 +140,6 @@ getMaxPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetMaxPage), wxe_util:rec(?wxPrintDialogData_GetMaxPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetminpage">external documentation</a>. -doc "Returns the `minimum` page number.". -spec getMinPage(This) -> integer() when This::wxPrintDialogData(). @@ -161,7 +148,6 @@ getMinPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetMinPage), wxe_util:rec(?wxPrintDialogData_GetMinPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetnocopies">external documentation</a>. -doc "Returns the number of copies requested by the user.". -spec getNoCopies(This) -> integer() when This::wxPrintDialogData(). @@ -170,7 +156,6 @@ getNoCopies(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetNoCopies), wxe_util:rec(?wxPrintDialogData_GetNoCopies). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetprintdata">external documentation</a>. -doc "Returns a reference to the internal `m:wxPrintData` object.". -spec getPrintData(This) -> wxPrintData:wxPrintData() when This::wxPrintDialogData(). @@ -179,7 +164,6 @@ getPrintData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetPrintData), wxe_util:rec(?wxPrintDialogData_GetPrintData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetprinttofile">external documentation</a>. -doc "Returns true if the user has selected printing to a file.". -spec getPrintToFile(This) -> boolean() when This::wxPrintDialogData(). @@ -188,10 +172,9 @@ getPrintToFile(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetPrintToFile), wxe_util:rec(?wxPrintDialogData_GetPrintToFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagetselection">external documentation</a>. -doc """ -Returns true if the user requested that the selection be printed (where -"selection" is a concept specific to the application). +Returns true if the user requested that the selection be printed (where "selection" is a +concept specific to the application). """. -spec getSelection(This) -> boolean() when This::wxPrintDialogData(). @@ -200,7 +183,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetSelection), wxe_util:rec(?wxPrintDialogData_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatagettopage">external documentation</a>. -doc """ Returns the `"print to"` page number, as entered by the user. """. @@ -211,12 +193,11 @@ getToPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_GetToPage), wxe_util:rec(?wxPrintDialogData_GetToPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdataisok">external documentation</a>. -doc """ Returns true if the print data is valid for using in print dialogs. -This can return false on Windows if the current printer is not set, for example. -On all other platforms, it returns true. +This can return false on Windows if the current printer is not set, for example. On all +other platforms, it returns true. """. -spec isOk(This) -> boolean() when This::wxPrintDialogData(). @@ -225,7 +206,6 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintDialogData_IsOk), wxe_util:rec(?wxPrintDialogData_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetcollate">external documentation</a>. -doc """ Sets the "Collate" checkbox to true or false. """. @@ -236,7 +216,6 @@ setCollate(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_SetCollate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetfrompage">external documentation</a>. -doc "Sets the `from` page number.". -spec setFromPage(This, Page) -> 'ok' when This::wxPrintDialogData(), Page::integer(). @@ -245,7 +224,6 @@ setFromPage(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Page,?get_env(),?wxPrintDialogData_SetFromPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetmaxpage">external documentation</a>. -doc "Sets the `maximum` page number.". -spec setMaxPage(This, Page) -> 'ok' when This::wxPrintDialogData(), Page::integer(). @@ -254,7 +232,6 @@ setMaxPage(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Page,?get_env(),?wxPrintDialogData_SetMaxPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetminpage">external documentation</a>. -doc "Sets the `minimum` page number.". -spec setMinPage(This, Page) -> 'ok' when This::wxPrintDialogData(), Page::integer(). @@ -263,7 +240,6 @@ setMinPage(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Page,?get_env(),?wxPrintDialogData_SetMinPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetnocopies">external documentation</a>. -doc "Sets the default number of copies the user has requested to be printed out.". -spec setNoCopies(This, N) -> 'ok' when This::wxPrintDialogData(), N::integer(). @@ -272,7 +248,6 @@ setNoCopies(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,N,?get_env(),?wxPrintDialogData_SetNoCopies). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetprintdata">external documentation</a>. -doc "Sets the internal `m:wxPrintData`.". -spec setPrintData(This, PrintData) -> 'ok' when This::wxPrintDialogData(), PrintData::wxPrintData:wxPrintData(). @@ -281,7 +256,6 @@ setPrintData(#wx_ref{type=ThisT}=This,#wx_ref{type=PrintDataT}=PrintData) -> ?CLASS(PrintDataT,wxPrintData), wxe_util:queue_cmd(This,PrintData,?get_env(),?wxPrintDialogData_SetPrintData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetprinttofile">external documentation</a>. -doc """ Sets the "Print to file" checkbox to true or false. """. @@ -292,12 +266,11 @@ setPrintToFile(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_SetPrintToFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasetselection">external documentation</a>. -doc """ Selects the "Selection" radio button. -The effect of printing the selection depends on how the application implements -this command, if at all. +The effect of printing the selection depends on how the application implements this +command, if at all. """. -spec setSelection(This, Flag) -> 'ok' when This::wxPrintDialogData(), Flag::boolean(). @@ -306,7 +279,6 @@ setSelection(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Flag,?get_env(),?wxPrintDialogData_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintdialogdata.html#wxprintdialogdatasettopage">external documentation</a>. -doc """ Sets the `"print to"` page number. """. @@ -317,8 +289,7 @@ setToPage(#wx_ref{type=ThisT}=This,Page) ?CLASS(ThisT,wxPrintDialogData), wxe_util:queue_cmd(This,Page,?get_env(),?wxPrintDialogData_SetToPage). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPrintDialogData()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrintDialogData), diff --git a/lib/wx/src/gen/wxPrintPreview.erl b/lib/wx/src/gen/wxPrintPreview.erl index 181dc74b0571..2bbfa222f422 100644 --- a/lib/wx/src/gen/wxPrintPreview.erl +++ b/lib/wx/src/gen/wxPrintPreview.erl @@ -20,29 +20,36 @@ -module(wxPrintPreview). -moduledoc """ -Functions for wxPrintPreview class - -Objects of this class manage the print preview process. The object is passed a -`m:wxPrintout` object, and the `m:wxPrintPreview` object itself is passed to a -`m:wxPreviewFrame` object. Previewing is started by initializing and showing the -preview frame. Unlike `wxPrinter:print/4`, flow of control returns to the -application immediately after the frame is shown. - -Note: The preview shown is only exact on Windows. On other platforms, the -`m:wxDC` used for preview is different from what is used for printing and the -results may be significantly different, depending on how is the output created. -In particular, printing code relying on `wxDC:getTextExtent/3` heavily (for -example, `m:wxHtmlEasyPrinting` and other wxHTML classes do) is affected. It is -recommended to use native preview functionality on platforms that offer it -(macOS, GTK+). +Objects of this class manage the print preview process. + +The object is passed a `m:wxPrintout` object, and the `m:wxPrintPreview` object itself is +passed to a `m:wxPreviewFrame` object. Previewing is started by initializing and showing +the preview frame. Unlike `wxPrinter:print/4`, flow of control returns to the application immediately after +the frame is shown. + +Note: The preview shown is only exact on Windows. On other platforms, the `m:wxDC` used +for preview is different from what is used for printing and the results may be +significantly different, depending on how is the output created. In particular, printing +code relying on `wxDC:getTextExtent/3` heavily (for example, `m:wxHtmlEasyPrinting` and other wxHTML classes do) +is affected. It is recommended to use native preview functionality on platforms that offer +it (macOS, GTK+). See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`wxPrinterDC` (not implemented in wx), `m:wxPrintDialog`, `m:wxPrintout`, -`m:wxPrinter`, `m:wxPreviewCanvas`, `m:wxPreviewControlBar`, `m:wxPreviewFrame` +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) + +* `m:wxPrintDialog` + +* `m:wxPrintout` + +* `m:wxPrinter` + +* `m:wxPreviewCanvas` + +* `m:wxPreviewControlBar` -wxWidgets docs: -[wxPrintPreview](https://docs.wxwidgets.org/3.1/classwx_print_preview.html) +* `m:wxPreviewFrame` + +wxWidgets docs: [wxPrintPreview](https://docs.wxwidgets.org/3.2/classwx_print_preview.html) """. -include("wxe.hrl"). -export([destroy/1,getCanvas/1,getCurrentPage/1,getFrame/1,getMaxPage/1,getMinPage/1, @@ -55,11 +62,10 @@ wxWidgets docs: -type wxPrintPreview() :: wx:wx_object(). -export_type([wxPrintPreview/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Printout, []) +-doc(#{equiv => new(Printout, [])}). -spec new(Printout) -> wxPrintPreview() when Printout::wxPrintout:wxPrintout(). @@ -67,24 +73,21 @@ new(Printout) when is_record(Printout, wx_ref) -> new(Printout, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewwxprintpreview">external documentation</a>. -doc """ Constructor. -Pass a printout object, an optional printout object to be used for actual -printing, and the address of an optional block of printer data, which will be -copied to the print preview object's print data. +Pass a printout object, an optional printout object to be used for actual printing, and +the address of an optional block of printer data, which will be copied to the print +preview object's print data. -If `printoutForPrinting` is non-NULL, a `"Print..."` button will be placed on -the preview frame so that the user can print directly from the preview -interface. +If `printoutForPrinting` is non-NULL, a `"Print..."` button will be placed on the preview +frame so that the user can print directly from the preview interface. -Remark: Do not explicitly delete the printout objects once this constructor has -been called, since they will be deleted in the `m:wxPrintPreview` destructor. -The same does not apply to the `data` argument. +Remark: Do not explicitly delete the printout objects once this constructor has been +called, since they will be deleted in the `m:wxPrintPreview` destructor. The same does not +apply to the `data` argument. -Use `isOk/1` to check whether the `m:wxPrintPreview` object was created -correctly. +Use `isOk/1` to check whether the `m:wxPrintPreview` object was created correctly. """. -spec new(Printout, [Option]) -> wxPrintPreview() when Printout::wxPrintout:wxPrintout(), @@ -100,7 +103,7 @@ new(#wx_ref{type=PrintoutT}=Printout, Options) wxe_util:queue_cmd(Printout, Opts,?get_env(),?wxPrintPreview_new_2), wxe_util:rec(?wxPrintPreview_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewwxprintpreview">external documentation</a>. +-doc "". -spec new(Printout, PrintoutForPrinting, Data) -> wxPrintPreview() when Printout::wxPrintout:wxPrintout(), PrintoutForPrinting::wxPrintout:wxPrintout(), Data::wxPrintData:wxPrintData(). new(#wx_ref{type=PrintoutT}=Printout,#wx_ref{type=PrintoutForPrintingT}=PrintoutForPrinting,#wx_ref{type=DataT}=Data) -> @@ -110,7 +113,6 @@ new(#wx_ref{type=PrintoutT}=Printout,#wx_ref{type=PrintoutForPrintingT}=Printout wxe_util:queue_cmd(Printout,PrintoutForPrinting,Data,?get_env(),?wxPrintPreview_new_3), wxe_util:rec(?wxPrintPreview_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetcanvas">external documentation</a>. -doc "Gets the preview window used for displaying the print preview image.". -spec getCanvas(This) -> wxPreviewCanvas:wxPreviewCanvas() when This::wxPrintPreview(). @@ -119,7 +121,6 @@ getCanvas(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetCanvas), wxe_util:rec(?wxPrintPreview_GetCanvas). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetcurrentpage">external documentation</a>. -doc "Gets the page currently being previewed.". -spec getCurrentPage(This) -> integer() when This::wxPrintPreview(). @@ -128,7 +129,6 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetCurrentPage), wxe_util:rec(?wxPrintPreview_GetCurrentPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetframe">external documentation</a>. -doc "Gets the frame used for displaying the print preview canvas and control bar.". -spec getFrame(This) -> wxFrame:wxFrame() when This::wxPrintPreview(). @@ -137,7 +137,6 @@ getFrame(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetFrame), wxe_util:rec(?wxPrintPreview_GetFrame). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetmaxpage">external documentation</a>. -doc "Returns the maximum page number.". -spec getMaxPage(This) -> integer() when This::wxPrintPreview(). @@ -146,7 +145,6 @@ getMaxPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetMaxPage), wxe_util:rec(?wxPrintPreview_GetMaxPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetminpage">external documentation</a>. -doc "Returns the minimum page number.". -spec getMinPage(This) -> integer() when This::wxPrintPreview(). @@ -155,7 +153,6 @@ getMinPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetMinPage), wxe_util:rec(?wxPrintPreview_GetMinPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetprintout">external documentation</a>. -doc "Gets the preview printout object associated with the `m:wxPrintPreview` object.". -spec getPrintout(This) -> wxPrintout:wxPrintout() when This::wxPrintPreview(). @@ -164,10 +161,9 @@ getPrintout(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetPrintout), wxe_util:rec(?wxPrintPreview_GetPrintout). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewgetprintoutforprinting">external documentation</a>. -doc """ -Gets the printout object to be used for printing from within the preview -interface, or NULL if none exists. +Gets the printout object to be used for printing from within the preview interface, or +NULL if none exists. """. -spec getPrintoutForPrinting(This) -> wxPrintout:wxPrintout() when This::wxPrintPreview(). @@ -176,12 +172,11 @@ getPrintoutForPrinting(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_GetPrintoutForPrinting), wxe_util:rec(?wxPrintPreview_GetPrintoutForPrinting). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewisok">external documentation</a>. -doc """ Returns true if the `m:wxPrintPreview` is valid, false otherwise. -It could return false if there was a problem initializing the printer device -context (current printer not set, for example). +It could return false if there was a problem initializing the printer device context +(current printer not set, for example). """. -spec isOk(This) -> boolean() when This::wxPrintPreview(). @@ -190,14 +185,13 @@ isOk(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintPreview_IsOk), wxe_util:rec(?wxPrintPreview_IsOk). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewpaintpage">external documentation</a>. -doc """ This refreshes the preview window with the preview image. It must be called from the preview window's OnPaint member. -The implementation simply blits the preview bitmap onto the canvas, creating a -new preview bitmap if none exists. +The implementation simply blits the preview bitmap onto the canvas, creating a new +preview bitmap if none exists. """. -spec paintPage(This, Canvas, Dc) -> boolean() when This::wxPrintPreview(), Canvas::wxPreviewCanvas:wxPreviewCanvas(), Dc::wxDC:wxDC(). @@ -208,16 +202,14 @@ paintPage(#wx_ref{type=ThisT}=This,#wx_ref{type=CanvasT}=Canvas,#wx_ref{type=DcT wxe_util:queue_cmd(This,Canvas,Dc,?get_env(),?wxPrintPreview_PaintPage), wxe_util:rec(?wxPrintPreview_PaintPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewprint">external documentation</a>. -doc """ -Invokes the print process using the second `m:wxPrintout` object supplied in the -`m:wxPrintPreview` constructor. +Invokes the print process using the second `m:wxPrintout` object supplied in the `m:wxPrintPreview` +constructor. -Will normally be called by the `Print`... panel item on the preview frame's -control bar. +Will normally be called by the `Print`... panel item on the preview frame's control bar. -Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed -information about the kind of the error. +Returns false in case of error - call `wxPrinter:getLastError/0` to get detailed information about the kind of the +error. """. -spec print(This, Prompt) -> boolean() when This::wxPrintPreview(), Prompt::boolean(). @@ -227,7 +219,6 @@ print(#wx_ref{type=ThisT}=This,Prompt) wxe_util:queue_cmd(This,Prompt,?get_env(),?wxPrintPreview_Print), wxe_util:rec(?wxPrintPreview_Print). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewrenderpage">external documentation</a>. -doc """ Renders a page into a `m:wxMemoryDC`. @@ -241,7 +232,6 @@ renderPage(#wx_ref{type=ThisT}=This,PageNum) wxe_util:queue_cmd(This,PageNum,?get_env(),?wxPrintPreview_RenderPage), wxe_util:rec(?wxPrintPreview_RenderPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewsetcanvas">external documentation</a>. -doc "Sets the window to be used for displaying the print preview image.". -spec setCanvas(This, Window) -> 'ok' when This::wxPrintPreview(), Window::wxPreviewCanvas:wxPreviewCanvas(). @@ -250,7 +240,6 @@ setCanvas(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxPreviewCanvas), wxe_util:queue_cmd(This,Window,?get_env(),?wxPrintPreview_SetCanvas). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewsetcurrentpage">external documentation</a>. -doc "Sets the current page to be previewed.". -spec setCurrentPage(This, PageNum) -> boolean() when This::wxPrintPreview(), PageNum::integer(). @@ -260,11 +249,7 @@ setCurrentPage(#wx_ref{type=ThisT}=This,PageNum) wxe_util:queue_cmd(This,PageNum,?get_env(),?wxPrintPreview_SetCurrentPage), wxe_util:rec(?wxPrintPreview_SetCurrentPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewsetframe">external documentation</a>. --doc """ -Sets the frame to be used for displaying the print preview canvas and control -bar. -""". +-doc "Sets the frame to be used for displaying the print preview canvas and control bar.". -spec setFrame(This, Frame) -> 'ok' when This::wxPrintPreview(), Frame::wxFrame:wxFrame(). setFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame) -> @@ -272,7 +257,6 @@ setFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame) -> ?CLASS(FrameT,wxFrame), wxe_util:queue_cmd(This,Frame,?get_env(),?wxPrintPreview_SetFrame). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewsetprintout">external documentation</a>. -doc "Associates a printout object with the `m:wxPrintPreview` object.". -spec setPrintout(This, Printout) -> 'ok' when This::wxPrintPreview(), Printout::wxPrintout:wxPrintout(). @@ -281,7 +265,6 @@ setPrintout(#wx_ref{type=ThisT}=This,#wx_ref{type=PrintoutT}=Printout) -> ?CLASS(PrintoutT,wxPrintout), wxe_util:queue_cmd(This,Printout,?get_env(),?wxPrintPreview_SetPrintout). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintpreview.html#wxprintpreviewsetzoom">external documentation</a>. -doc "Sets the percentage preview zoom, and refreshes the preview canvas accordingly.". -spec setZoom(This, Percent) -> 'ok' when This::wxPrintPreview(), Percent::integer(). @@ -290,13 +273,7 @@ setZoom(#wx_ref{type=ThisT}=This,Percent) ?CLASS(ThisT,wxPrintPreview), wxe_util:queue_cmd(This,Percent,?get_env(),?wxPrintPreview_SetZoom). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Deletes both print preview objects, so do not destroy these objects in your -application. -""". +-doc "Destroys the object". -spec destroy(This::wxPrintPreview()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrintPreview), diff --git a/lib/wx/src/gen/wxPrinter.erl b/lib/wx/src/gen/wxPrinter.erl index 31648296fdaf..17570728f8af 100644 --- a/lib/wx/src/gen/wxPrinter.erl +++ b/lib/wx/src/gen/wxPrinter.erl @@ -20,21 +20,22 @@ -module(wxPrinter). -moduledoc """ -Functions for wxPrinter class +This class represents the Windows or PostScript printer, and is the vehicle through which +printing may be launched by an application. -This class represents the Windows or PostScript printer, and is the vehicle -through which printing may be launched by an application. - -Printing can also be achieved through using of lower functions and classes, but -this and associated classes provide a more convenient and general method of -printing. +Printing can also be achieved through using of lower functions and classes, but this and +associated classes provide a more convenient and general method of printing. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`wxPrinterDC` (not implemented in wx), `m:wxPrintDialog`, `m:wxPrintout`, -`m:wxPrintPreview` +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) + +* `m:wxPrintDialog` + +* `m:wxPrintout` + +* `m:wxPrintPreview` -wxWidgets docs: [wxPrinter](https://docs.wxwidgets.org/3.1/classwx_printer.html) +wxWidgets docs: [wxPrinter](https://docs.wxwidgets.org/3.2/classwx_printer.html) """. -include("wxe.hrl"). -export([createAbortWindow/3,destroy/1,getAbort/1,getLastError/0,getPrintDialogData/1, @@ -45,24 +46,25 @@ wxWidgets docs: [wxPrinter](https://docs.wxwidgets.org/3.1/classwx_printer.html) -type wxPrinter() :: wx:wx_object(). -export_type([wxPrinter/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxPrinter(). new() -> new([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprinterwxprinter">external documentation</a>. -doc """ Constructor. -Pass an optional pointer to a block of print dialog data, which will be copied -to the printer object's local data. +Pass an optional pointer to a block of print dialog data, which will be copied to the +printer object's local data. -See: `m:wxPrintDialogData`, `m:wxPrintData` +See: +* `m:wxPrintDialogData` + +* `m:wxPrintData` """. -spec new([Option]) -> wxPrinter() when Option :: {'data', wxPrintDialogData:wxPrintDialogData()}. @@ -74,7 +76,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxPrinter_new), wxe_util:rec(?wxPrinter_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprintercreateabortwindow">external documentation</a>. -doc "Creates the default printing abort window, with a cancel button.". -spec createAbortWindow(This, Parent, Printout) -> wxDialog:wxDialog() when This::wxPrinter(), Parent::wxWindow:wxWindow(), Printout::wxPrintout:wxPrintout(). @@ -85,7 +86,6 @@ createAbortWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,#wx_ref{ wxe_util:queue_cmd(This,Parent,Printout,?get_env(),?wxPrinter_CreateAbortWindow), wxe_util:rec(?wxPrinter_CreateAbortWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprintergetabort">external documentation</a>. -doc "Returns true if the user has aborted the print job.". -spec getAbort(This) -> boolean() when This::wxPrinter(). @@ -94,8 +94,6 @@ getAbort(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrinter_GetAbort), wxe_util:rec(?wxPrinter_GetAbort). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprintergetlasterror">external documentation</a>. -%%<br /> Res = ?wxPRINTER_NO_ERROR | ?wxPRINTER_CANCELLED | ?wxPRINTER_ERROR -doc """ Return last error. @@ -105,12 +103,12 @@ These functions set last error to `wxPRINTER_NO_ERROR` if no error happened. Returned value is one of the following: """. +%% Res = ?wxPRINTER_NO_ERROR | ?wxPRINTER_CANCELLED | ?wxPRINTER_ERROR -spec getLastError() -> wx:wx_enum(). getLastError() -> wxe_util:queue_cmd(?get_env(), ?wxPrinter_GetLastError), wxe_util:rec(?wxPrinter_GetLastError). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprintergetprintdialogdata">external documentation</a>. -doc "Returns the print data associated with the printer object.". -spec getPrintDialogData(This) -> wxPrintDialogData:wxPrintDialogData() when This::wxPrinter(). @@ -119,7 +117,7 @@ getPrintDialogData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrinter_GetPrintDialogData), wxe_util:rec(?wxPrinter_GetPrintDialogData). -%% @equiv print(This,Parent,Printout, []) +-doc(#{equiv => print(This,Parent,Printout, [])}). -spec print(This, Parent, Printout) -> boolean() when This::wxPrinter(), Parent::wxWindow:wxWindow(), Printout::wxPrintout:wxPrintout(). @@ -127,17 +125,15 @@ print(This,Parent,Printout) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_record(Printout, wx_ref) -> print(This,Parent,Printout, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprinterprint">external documentation</a>. -doc """ Starts the printing process. -Provide a parent window, a user-defined `m:wxPrintout` object which controls the -printing of a document, and whether the print dialog should be invoked first. +Provide a parent window, a user-defined `m:wxPrintout` object which controls the printing +of a document, and whether the print dialog should be invoked first. -`print/4` could return false if there was a problem initializing the printer -device context (current printer not set, for example) or the user cancelled -printing. Call `getLastError/0` to get detailed information about the kind of -the error. +`print/4` could return false if there was a problem initializing the printer device context +(current printer not set, for example) or the user cancelled printing. Call `getLastError/0` to get +detailed information about the kind of the error. """. -spec print(This, Parent, Printout, [Option]) -> boolean() when This::wxPrinter(), Parent::wxWindow:wxWindow(), Printout::wxPrintout:wxPrintout(), @@ -153,13 +149,12 @@ print(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,#wx_ref{type=Printou wxe_util:queue_cmd(This,Parent,Printout, Opts,?get_env(),?wxPrinter_Print), wxe_util:rec(?wxPrinter_Print). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprinterprintdialog">external documentation</a>. -doc """ Invokes the print dialog. -If successful (the user did not press Cancel and no error occurred), a suitable -device context will be returned; otherwise NULL is returned; call -`getLastError/0` to get detailed information about the kind of the error. +If successful (the user did not press Cancel and no error occurred), a suitable device +context will be returned; otherwise NULL is returned; call `getLastError/0` to get detailed information +about the kind of the error. Remark: The application must delete this device context to avoid a memory leak. """. @@ -171,7 +166,6 @@ printDialog(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent) -> wxe_util:queue_cmd(This,Parent,?get_env(),?wxPrinter_PrintDialog), wxe_util:rec(?wxPrinter_PrintDialog). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprinterreporterror">external documentation</a>. -doc "Default error-reporting function.". -spec reportError(This, Parent, Printout, Message) -> 'ok' when This::wxPrinter(), Parent::wxWindow:wxWindow(), Printout::wxPrintout:wxPrintout(), Message::unicode:chardata(). @@ -183,12 +177,12 @@ reportError(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,#wx_ref{type=P Message_UC = unicode:characters_to_binary(Message), wxe_util:queue_cmd(This,Parent,Printout,Message_UC,?get_env(),?wxPrinter_ReportError). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprinter.html#wxprintersetup">external documentation</a>. -doc """ Invokes the print setup dialog. -Deprecated: The setup dialog is obsolete, though retained for backward -compatibility. +Deprecated: + +The setup dialog is obsolete, though retained for backward compatibility. """. -spec setup(This, Parent) -> boolean() when This::wxPrinter(), Parent::wxWindow:wxWindow(). @@ -198,8 +192,7 @@ setup(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent) -> wxe_util:queue_cmd(This,Parent,?get_env(),?wxPrinter_Setup), wxe_util:rec(?wxPrinter_Setup). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxPrinter()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrinter), diff --git a/lib/wx/src/gen/wxPrintout.erl b/lib/wx/src/gen/wxPrintout.erl index 40ab5d1bf802..de22b845414c 100644 --- a/lib/wx/src/gen/wxPrintout.erl +++ b/lib/wx/src/gen/wxPrintout.erl @@ -20,41 +20,40 @@ -module(wxPrintout). -moduledoc """ -Functions for wxPrintout class - -This class encapsulates the functionality of printing out an application -document. - -A new class must be derived and members overridden to respond to calls such as -`OnPrintPage()` (not implemented in wx) and `HasPage()` (not implemented in wx) -and to render the print image onto an associated `m:wxDC`. Instances of this -class are passed to `wxPrinter:print/4` or to a `m:wxPrintPreview` object to -initiate printing or previewing. - -Your derived `m:wxPrintout` is responsible for drawing both the preview image -and the printed page. If your windows' drawing routines accept an arbitrary DC -as an argument, you can re-use those routines within your `m:wxPrintout` -subclass to draw the printout image. You may also add additional drawing -elements within your `m:wxPrintout` subclass, like headers, footers, and/or page -numbers. However, the image on the printed page will often differ from the image -drawn on the screen, as will the print preview image - not just in the presence -of headers and footers, but typically in scale. A high-resolution printer -presents a much larger drawing surface (i.e., a higher-resolution DC); a -zoomed-out preview image presents a much smaller drawing surface -(lower-resolution DC). By using the routines FitThisSizeToXXX() and/or -MapScreenSizeToXXX() within your `m:wxPrintout` subclass to set the user scale -and origin of the associated DC, you can easily use a single drawing routine to -draw on your application's windows, to create the print preview image, and to -create the printed paper image, and achieve a common appearance to the preview -image and the printed page. +This class encapsulates the functionality of printing out an application document. + +A new class must be derived and members overridden to respond to calls such as `OnPrintPage()` +(not implemented in wx) and `HasPage()` (not implemented in wx) and to render the print +image onto an associated `m:wxDC`. Instances of this class are passed to `wxPrinter:print/4` or to a `m:wxPrintPreview` +object to initiate printing or previewing. + +Your derived `m:wxPrintout` is responsible for drawing both the preview image and the +printed page. If your windows' drawing routines accept an arbitrary DC as an argument, you +can re-use those routines within your `m:wxPrintout` subclass to draw the printout image. +You may also add additional drawing elements within your `m:wxPrintout` subclass, like +headers, footers, and/or page numbers. However, the image on the printed page will often +differ from the image drawn on the screen, as will the print preview image - not just in +the presence of headers and footers, but typically in scale. A high-resolution printer +presents a much larger drawing surface (i.e., a higher-resolution DC); a zoomed-out +preview image presents a much smaller drawing surface (lower-resolution DC). By using the +routines FitThisSizeToXXX() and/or MapScreenSizeToXXX() within your `m:wxPrintout` +subclass to set the user scale and origin of the associated DC, you can easily use a +single drawing routine to draw on your application's windows, to create the print preview +image, and to create the printed paper image, and achieve a common appearance to the +preview image and the printed page. See: -[Overview printing](https://docs.wxwidgets.org/3.1/overview_printing.html#overview_printing), -`wxPrinterDC` (not implemented in wx), `m:wxPrintDialog`, `m:wxPageSetupDialog`, -`m:wxPrinter`, `m:wxPrintPreview` +* [Overview printing](https://docs.wxwidgets.org/3.2/overview_printing.html#overview_printing) -wxWidgets docs: -[wxPrintout](https://docs.wxwidgets.org/3.1/classwx_printout.html) +* `m:wxPrintDialog` + +* `m:wxPageSetupDialog` + +* `m:wxPrinter` + +* `m:wxPrintPreview` + +wxWidgets docs: [wxPrintout](https://docs.wxwidgets.org/3.2/classwx_printout.html) """. -include("wxe.hrl"). -export([ new/2,new/3 ,destroy/1,fitThisSizeToPage/2,fitThisSizeToPageMargins/3, @@ -69,13 +68,11 @@ wxWidgets docs: -type wxPrintout() :: wx:wx_object(). -export_type([wxPrintout/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc @equiv new(Title, OnPrintPage, []) --doc false. +-doc(#{equiv => new/3}). -spec new(Title::string(), OnPrintPage::function()) -> wxPrintout:wxPrintout(). new(Title, OnPrintPage) -> new(Title, OnPrintPage, []). @@ -89,6 +86,7 @@ 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()), @@ -125,16 +123,14 @@ new(Title, OnPrintPage, Opts) when is_list(Title), is_function(OnPrintPage), is_ wxe_util:queue_cmd(Title_UC, OnPrintPageId, OptsMod, ?get_env(), Op), wxe_util:rec(Op). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetdc">external documentation</a>. -doc """ -Returns the device context associated with the printout (given to the printout -at start of printing or previewing). +Returns the device context associated with the printout (given to the printout at start +of printing or previewing). The application can use `getDC/1` to obtain a device context to draw on. -This will be a `wxPrinterDC` (not implemented in wx) if printing under Windows -or Mac, a `m:wxPostScriptDC` if printing on other platforms, and a -`m:wxMemoryDC` if previewing. +This will be a `wxPrinterDC` (not implemented in wx) if printing under Windows or Mac, a `m:wxPostScriptDC` +if printing on other platforms, and a `m:wxMemoryDC` if previewing. """. -spec getDC(This) -> wxDC:wxDC() when This::wxPrintout(). @@ -143,7 +139,6 @@ getDC(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetDC), wxe_util:rec(?wxPrintout_GetDC). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetpagesizemm">external documentation</a>. -doc "Returns the size of the printer page in millimetres.". -spec getPageSizeMM(This) -> {W::integer(), H::integer()} when This::wxPrintout(). @@ -152,16 +147,14 @@ getPageSizeMM(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetPageSizeMM), wxe_util:rec(?wxPrintout_GetPageSizeMM). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetpagesizepixels">external documentation</a>. -doc """ Returns the size of the printer page in pixels, called the page rectangle. -The page rectangle has a top left corner at (0,0) and a bottom right corner at -(w,h). These values may not be the same as the values returned from -`wxDC:getSize/1`; if the printout is being used for previewing, a memory device -context is used, which uses a bitmap size reflecting the current preview zoom. -The application must take this discrepancy into account if previewing is to be -supported. +The page rectangle has a top left corner at (0,0) and a bottom right corner at (w,h). +These values may not be the same as the values returned from `wxDC:getSize/1`;if the printout is being +used for previewing, a memory device context is used, which uses a bitmap size reflecting +the current preview zoom. The application must take this discrepancy into account if +previewing is to be supported. """. -spec getPageSizePixels(This) -> {W::integer(), H::integer()} when This::wxPrintout(). @@ -170,26 +163,23 @@ getPageSizePixels(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetPageSizePixels), wxe_util:rec(?wxPrintout_GetPageSizePixels). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetpaperrectpixels">external documentation</a>. -doc """ -Returns the rectangle that corresponds to the entire paper in pixels, called the -paper rectangle. - -This distinction between paper rectangle and page rectangle reflects the fact -that most printers cannot print all the way to the edge of the paper. The page -rectangle is a rectangle whose top left corner is at (0,0) and whose width and -height are given by wxDC::GetPageSizePixels(). - -On MSW and Mac, the page rectangle gives the printable area of the paper, while -the paper rectangle represents the entire paper, including non-printable -borders. Thus, the rectangle returned by wxDC::GetPaperRectPixels() will have a -top left corner whose coordinates are small negative numbers and the bottom -right corner will have values somewhat larger than the width and height given by -wxDC::GetPageSizePixels(). - -On other platforms and for PostScript printing, the paper is treated as if its -entire area were printable, so this function will return the same rectangle as -the page rectangle. +Returns the rectangle that corresponds to the entire paper in pixels, called the paper +rectangle. + +This distinction between paper rectangle and page rectangle reflects the fact that most +printers cannot print all the way to the edge of the paper. The page rectangle is a +rectangle whose top left corner is at (0,0) and whose width and height are given by wxDC::GetPageSizePixels(). + +On MSW and Mac, the page rectangle gives the printable area of the paper, while the paper +rectangle represents the entire paper, including non-printable borders. Thus, the +rectangle returned by wxDC::GetPaperRectPixels() will have a top left corner whose +coordinates are small negative numbers and the bottom right corner will have values +somewhat larger than the width and height given by wxDC::GetPageSizePixels(). + +On other platforms and for PostScript printing, the paper is treated as if its entire +area were printable, so this function will return the same rectangle as the page +rectangle. """. -spec getPaperRectPixels(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxPrintout(). @@ -198,16 +188,15 @@ getPaperRectPixels(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetPaperRectPixels), wxe_util:rec(?wxPrintout_GetPaperRectPixels). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetppiprinter">external documentation</a>. -doc """ Returns the number of pixels per logical inch of the printer device context. -Dividing the printer PPI by the screen PPI can give a suitable scaling factor -for drawing text onto the printer. +Dividing the printer PPI by the screen PPI can give a suitable scaling factor for drawing +text onto the printer. -Remember to multiply this by a scaling factor to take the preview DC size into -account. Or you can just use the FitThisSizeToXXX() and MapScreenSizeToXXX -routines below, which do most of the scaling calculations for you. +Remember to multiply this by a scaling factor to take the preview DC size into account. +Or you can just use the FitThisSizeToXXX() and MapScreenSizeToXXX routines below, which do +most of the scaling calculations for you. """. -spec getPPIPrinter(This) -> {W::integer(), H::integer()} when This::wxPrintout(). @@ -216,15 +205,14 @@ getPPIPrinter(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetPPIPrinter), wxe_util:rec(?wxPrintout_GetPPIPrinter). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetppiscreen">external documentation</a>. -doc """ Returns the number of pixels per logical inch of the screen device context. -Dividing the printer PPI by the screen PPI can give a suitable scaling factor -for drawing text onto the printer. +Dividing the printer PPI by the screen PPI can give a suitable scaling factor for drawing +text onto the printer. -If you are doing your own scaling, remember to multiply this by a scaling factor -to take the preview DC size into account. +If you are doing your own scaling, remember to multiply this by a scaling factor to take +the preview DC size into account. """. -spec getPPIScreen(This) -> {W::integer(), H::integer()} when This::wxPrintout(). @@ -233,7 +221,6 @@ getPPIScreen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetPPIScreen), wxe_util:rec(?wxPrintout_GetPPIScreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgettitle">external documentation</a>. -doc "Returns the title of the printout.". -spec getTitle(This) -> unicode:charlist() when This::wxPrintout(). @@ -242,12 +229,7 @@ getTitle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetTitle), wxe_util:rec(?wxPrintout_GetTitle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutispreview">external documentation</a>. --doc """ -Returns true if the printout is currently being used for previewing. - -See: `GetPreview()` (not implemented in wx) -""". +-doc "Returns true if the printout is currently being used for previewing.". -spec isPreview(This) -> boolean() when This::wxPrintout(). isPreview(#wx_ref{type=ThisT}=This) -> @@ -255,16 +237,15 @@ isPreview(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_IsPreview), wxe_util:rec(?wxPrintout_IsPreview). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutfitthissizetopaper">external documentation</a>. -doc """ -Set the user scale and device origin of the `m:wxDC` associated with this -`m:wxPrintout` so that the given image size fits entirely within the paper and -the origin is at the top left corner of the paper. +Set the user scale and device origin of the `m:wxDC` associated with this `m:wxPrintout` +so that the given image size fits entirely within the paper and the origin is at the top +left corner of the paper. Use this if you're managing your own page margins. -Note: With most printers, the region around the edges of the paper are not -printable so that the edges of the image could be cut off. +Note: With most printers, the region around the edges of the paper are not printable so +that the edges of the image could be cut off. """. -spec fitThisSizeToPaper(This, ImageSize) -> 'ok' when This::wxPrintout(), ImageSize::{W::integer(), H::integer()}. @@ -273,18 +254,16 @@ fitThisSizeToPaper(#wx_ref{type=ThisT}=This,{ImageSizeW,ImageSizeH} = ImageSize) ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,ImageSize,?get_env(),?wxPrintout_FitThisSizeToPaper). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutfitthissizetopage">external documentation</a>. -doc """ -Set the user scale and device origin of the `m:wxDC` associated with this -`m:wxPrintout` so that the given image size fits entirely within the page -rectangle and the origin is at the top left corner of the page rectangle. +Set the user scale and device origin of the `m:wxDC` associated with this `m:wxPrintout` +so that the given image size fits entirely within the page rectangle and the origin is at +the top left corner of the page rectangle. -On MSW and Mac, the page rectangle is the printable area of the page. On other -platforms and PostScript printing, the page rectangle is the entire paper. +On MSW and Mac, the page rectangle is the printable area of the page. On other platforms +and PostScript printing, the page rectangle is the entire paper. -Use this if you want your printed image as large as possible, but with the -caveat that on some platforms, portions of the image might be cut off at the -edges. +Use this if you want your printed image as large as possible, but with the caveat that on +some platforms, portions of the image might be cut off at the edges. """. -spec fitThisSizeToPage(This, ImageSize) -> 'ok' when This::wxPrintout(), ImageSize::{W::integer(), H::integer()}. @@ -293,18 +272,17 @@ fitThisSizeToPage(#wx_ref{type=ThisT}=This,{ImageSizeW,ImageSizeH} = ImageSize) ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,ImageSize,?get_env(),?wxPrintout_FitThisSizeToPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutfitthissizetopagemargins">external documentation</a>. -doc """ -Set the user scale and device origin of the `m:wxDC` associated with this -`m:wxPrintout` so that the given image size fits entirely within the page -margins set in the given `m:wxPageSetupDialogData` object. +Set the user scale and device origin of the `m:wxDC` associated with this `m:wxPrintout` +so that the given image size fits entirely within the page margins set in the given `m:wxPageSetupDialogData` +object. -This function provides the greatest consistency across all platforms because it -does not depend on having access to the printable area of the paper. +This function provides the greatest consistency across all platforms because it does not +depend on having access to the printable area of the paper. -Remark: On Mac, the native `m:wxPageSetupDialog` does not let you set the page -margins; you'll have to provide your own mechanism, or you can use the Mac-only -class wxMacPageMarginsDialog. +Remark: On Mac, the native `m:wxPageSetupDialog` does not let you set the page margins; +you'll have to provide your own mechanism, or you can use the Mac-only class +wxMacPageMarginsDialog. """. -spec fitThisSizeToPageMargins(This, ImageSize, PageSetupData) -> 'ok' when This::wxPrintout(), ImageSize::{W::integer(), H::integer()}, PageSetupData::wxPageSetupDialogData:wxPageSetupDialogData(). @@ -314,16 +292,13 @@ fitThisSizeToPageMargins(#wx_ref{type=ThisT}=This,{ImageSizeW,ImageSizeH} = Imag ?CLASS(PageSetupDataT,wxPageSetupDialogData), wxe_util:queue_cmd(This,ImageSize,PageSetupData,?get_env(),?wxPrintout_FitThisSizeToPageMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutmapscreensizetopaper">external documentation</a>. -doc """ -Set the user scale and device origin of the `m:wxDC` associated with this -`m:wxPrintout` so that the printed page matches the screen size as closely as -possible and the logical origin is in the top left corner of the paper -rectangle. +Set the user scale and device origin of the `m:wxDC` associated with this `m:wxPrintout` +so that the printed page matches the screen size as closely as possible and the logical +origin is in the top left corner of the paper rectangle. -That is, a 100-pixel object on screen should appear at the same size on the -printed page. (It will, of course, be larger or smaller in the preview image, -depending on the zoom factor.) +That is, a 100-pixel object on screen should appear at the same size on the printed page. +(It will, of course, be larger or smaller in the preview image, depending on the zoom factor.) Use this if you want WYSIWYG behaviour, e.g., in a text editor. """. @@ -333,11 +308,10 @@ mapScreenSizeToPaper(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,?get_env(),?wxPrintout_MapScreenSizeToPaper). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutmapscreensizetopage">external documentation</a>. -doc """ -This sets the user scale of the `m:wxDC` associated with this `m:wxPrintout` to -the same scale as `mapScreenSizeToPaper/1` but sets the logical origin to the -top left corner of the page rectangle. +This sets the user scale of the `m:wxDC` associated with this `m:wxPrintout` to the same +scale as `mapScreenSizeToPaper/1` but sets the logical origin to the top left corner of +the page rectangle. """. -spec mapScreenSizeToPage(This) -> 'ok' when This::wxPrintout(). @@ -345,12 +319,10 @@ mapScreenSizeToPage(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,?get_env(),?wxPrintout_MapScreenSizeToPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutmapscreensizetopagemargins">external documentation</a>. -doc """ -This sets the user scale of the `m:wxDC` associated with this `m:wxPrintout` to -the same scale as `mapScreenSizeToPageMargins/2` but sets the logical origin to -the top left corner of the page margins specified by the given -`m:wxPageSetupDialogData` object. +This sets the user scale of the `m:wxDC` associated with this `m:wxPrintout` to the same +scale as `mapScreenSizeToPageMargins/2` but sets the logical origin to the top left corner +of the page margins specified by the given `m:wxPageSetupDialogData` object. """. -spec mapScreenSizeToPageMargins(This, PageSetupData) -> 'ok' when This::wxPrintout(), PageSetupData::wxPageSetupDialogData:wxPageSetupDialogData(). @@ -359,23 +331,21 @@ mapScreenSizeToPageMargins(#wx_ref{type=ThisT}=This,#wx_ref{type=PageSetupDataT} ?CLASS(PageSetupDataT,wxPageSetupDialogData), wxe_util:queue_cmd(This,PageSetupData,?get_env(),?wxPrintout_MapScreenSizeToPageMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutmapscreensizetodevice">external documentation</a>. -doc """ -Set the user scale and device origin of the `m:wxDC` associated with this -`m:wxPrintout` so that one screen pixel maps to one device pixel on the DC. +Set the user scale and device origin of the `m:wxDC` associated with this `m:wxPrintout` +so that one screen pixel maps to one device pixel on the DC. That is, the user scale is set to (1,1) and the device origin is set to (0,0). -Use this if you want to do your own scaling prior to calling `m:wxDC` drawing -calls, for example, if your underlying model is floating-point and you want to -achieve maximum drawing precision on high-resolution printers. +Use this if you want to do your own scaling prior to calling `m:wxDC` drawing calls, for +example, if your underlying model is floating-point and you want to achieve maximum +drawing precision on high-resolution printers. -You can use the GetLogicalXXXRect() routines below to obtain the paper -rectangle, page rectangle, or page margins rectangle to perform your own -scaling. +You can use the GetLogicalXXXRect() routines below to obtain the paper rectangle, page +rectangle, or page margins rectangle to perform your own scaling. -Note: While the underlying drawing model of macOS is floating-point, wxWidgets's -drawing model scales from integer coordinates. +Note: While the underlying drawing model of macOS is floating-point, wxWidgets's drawing +model scales from integer coordinates. """. -spec mapScreenSizeToDevice(This) -> 'ok' when This::wxPrintout(). @@ -383,10 +353,9 @@ mapScreenSizeToDevice(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,?get_env(),?wxPrintout_MapScreenSizeToDevice). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetlogicalpaperrect">external documentation</a>. -doc """ -Return the rectangle corresponding to the paper in the associated `m:wxDC` 's -logical coordinates for the current user scale and device origin. +Return the rectangle corresponding to the paper in the associated `m:wxDC` 's logical +coordinates for the current user scale and device origin. """. -spec getLogicalPaperRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxPrintout(). @@ -395,13 +364,12 @@ getLogicalPaperRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetLogicalPaperRect), wxe_util:rec(?wxPrintout_GetLogicalPaperRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetlogicalpagerect">external documentation</a>. -doc """ -Return the rectangle corresponding to the page in the associated `m:wxDC` 's -logical coordinates for the current user scale and device origin. +Return the rectangle corresponding to the page in the associated `m:wxDC` 's logical +coordinates for the current user scale and device origin. -On MSW and Mac, this will be the printable area of the paper. On other platforms -and PostScript printing, this will be the full paper rectangle. +On MSW and Mac, this will be the printable area of the paper. On other platforms and +PostScript printing, this will be the full paper rectangle. """. -spec getLogicalPageRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxPrintout(). @@ -410,14 +378,12 @@ getLogicalPageRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxPrintout_GetLogicalPageRect), wxe_util:rec(?wxPrintout_GetLogicalPageRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutgetlogicalpagemarginsrect">external documentation</a>. -doc """ -Return the rectangle corresponding to the page margins specified by the given -`m:wxPageSetupDialogData` object in the associated `m:wxDC`'s logical -coordinates for the current user scale and device origin. +Return the rectangle corresponding to the page margins specified by the given `m:wxPageSetupDialogData` +object in the associated `m:wxDC`'s logical coordinates for the current user scale and +device origin. -The page margins are specified with respect to the edges of the paper on all -platforms. +The page margins are specified with respect to the edges of the paper on all platforms. """. -spec getLogicalPageMarginsRect(This, PageSetupData) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxPrintout(), PageSetupData::wxPageSetupDialogData:wxPageSetupDialogData(). @@ -427,10 +393,9 @@ getLogicalPageMarginsRect(#wx_ref{type=ThisT}=This,#wx_ref{type=PageSetupDataT}= wxe_util:queue_cmd(This,PageSetupData,?get_env(),?wxPrintout_GetLogicalPageMarginsRect), wxe_util:rec(?wxPrintout_GetLogicalPageMarginsRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutsetlogicalorigin">external documentation</a>. -doc """ -Set the device origin of the associated `m:wxDC` so that the current logical -point becomes the new logical origin. +Set the device origin of the associated `m:wxDC` so that the current logical point +becomes the new logical origin. """. -spec setLogicalOrigin(This, X, Y) -> 'ok' when This::wxPrintout(), X::integer(), Y::integer(). @@ -439,7 +404,6 @@ setLogicalOrigin(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxPrintout_SetLogicalOrigin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprintout.html#wxprintoutoffsetlogicalorigin">external documentation</a>. -doc "Shift the device origin by an amount specified in logical coordinates.". -spec offsetLogicalOrigin(This, Xoff, Yoff) -> 'ok' when This::wxPrintout(), Xoff::integer(), Yoff::integer(). @@ -448,8 +412,7 @@ offsetLogicalOrigin(#wx_ref{type=ThisT}=This,Xoff,Yoff) ?CLASS(ThisT,wxPrintout), wxe_util:queue_cmd(This,Xoff,Yoff,?get_env(),?wxPrintout_OffsetLogicalOrigin). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxPrintout()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxPrintout), diff --git a/lib/wx/src/gen/wxProgressDialog.erl b/lib/wx/src/gen/wxProgressDialog.erl index cb6268cd91ba..ef1696a1b2f9 100644 --- a/lib/wx/src/gen/wxProgressDialog.erl +++ b/lib/wx/src/gen/wxProgressDialog.erl @@ -20,17 +20,20 @@ -module(wxProgressDialog). -moduledoc """ -Functions for wxProgressDialog class +If supported by the platform this class will provide the platform's native progress +dialog, else it will simply be the `wxGenericProgressDialog` (not implemented in wx). -If supported by the platform this class will provide the platform's native -progress dialog, else it will simply be the `wxGenericProgressDialog` (not -implemented in wx). +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxDialog` -wxWidgets docs: -[wxProgressDialog](https://docs.wxwidgets.org/3.1/classwx_progress_dialog.html) +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxProgressDialog](https://docs.wxwidgets.org/3.2/classwx_progress_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,new/2,new/3,resume/1,update/2,update/3]). @@ -82,7 +85,6 @@ wxWidgets docs: -type wxProgressDialog() :: wx:wx_object(). -export_type([wxProgressDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -90,7 +92,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Title,Message, []) +-doc(#{equiv => new(Title,Message, [])}). -spec new(Title, Message) -> wxProgressDialog() when Title::unicode:chardata(), Message::unicode:chardata(). @@ -98,7 +100,7 @@ new(Title,Message) when ?is_chardata(Title),?is_chardata(Message) -> new(Title,Message, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprogressdialog.html#wxprogressdialogwxprogressdialog">external documentation</a>. +-doc "". -spec new(Title, Message, [Option]) -> wxProgressDialog() when Title::unicode:chardata(), Message::unicode:chardata(), Option :: {'maximum', integer()} @@ -116,10 +118,8 @@ new(Title,Message, Options) wxe_util:queue_cmd(Title_UC,Message_UC, Opts,?get_env(),?wxProgressDialog_new), wxe_util:rec(?wxProgressDialog_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprogressdialog.html#wxprogressdialogresume">external documentation</a>. -doc """ -Can be used to continue with the dialog, after the user had clicked the "Abort" -button. +Can be used to continue with the dialog, after the user had clicked the "Abort" button. """. -spec resume(This) -> 'ok' when This::wxProgressDialog(). @@ -127,7 +127,7 @@ resume(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxProgressDialog), wxe_util:queue_cmd(This,?get_env(),?wxProgressDialog_Resume). -%% @equiv update(This,Value, []) +-doc(#{equiv => update(This,Value, [])}). -spec update(This, Value) -> boolean() when This::wxProgressDialog(), Value::integer(). @@ -135,35 +135,32 @@ update(This,Value) when is_record(This, wx_ref),is_integer(Value) -> update(This,Value, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxprogressdialog.html#wxprogressdialogupdate">external documentation</a>. -doc """ -Updates the dialog, setting the progress bar to the new value and updating the -message if new one is specified. +Updates the dialog, setting the progress bar to the new value and updating the message if +new one is specified. Returns true unless the "Cancel" button has been pressed. -If false is returned, the application can either immediately destroy the dialog -or ask the user for the confirmation and if the abort is not confirmed the -dialog may be resumed with `resume/1` function. +If false is returned, the application can either immediately destroy the dialog or ask +the user for the confirmation and if the abort is not confirmed the dialog may be resumed +with `resume/1` function. -If `value` is the maximum value for the dialog, the behaviour of the function -depends on whether `wxPD_AUTO_HIDE` was used when the dialog was created. If it -was, the dialog is hidden and the function returns immediately. If it was not, -the dialog becomes a modal dialog and waits for the user to dismiss it, meaning -that this function does not return until this happens. +If `value` is the maximum value for the dialog, the behaviour of the function depends on +whether `wxPD_AUTO_HIDE` was used when the dialog was created. If it was, the dialog is +hidden and the function returns immediately. If it was not, the dialog becomes a modal +dialog and waits for the user to dismiss it, meaning that this function does not return +until this happens. -Notice that if `newmsg` is longer than the currently shown message, the dialog -will be automatically made wider to account for it. However if the new message -is shorter than the previous one, the dialog doesn't shrink back to avoid -constant resizes if the message is changed often. To do this and fit the dialog -to its current contents you may call `wxWindow:fit/1` explicitly. However the -native MSW implementation of this class does make the dialog shorter if the new -text has fewer lines of text than the old one, so it is recommended to keep the -number of lines of text constant in order to avoid jarring dialog size changes. -You may also want to make the initial message, specified when creating the -dialog, wide enough to avoid having to resize the dialog later, e.g. by -appending a long string of unbreakable spaces (`wxString` (not implemented in -wx)(L'\\u00a0', 100)) to it. +Notice that if `newmsg` is longer than the currently shown message, the dialog will be +automatically made wider to account for it. However if the new message is shorter than the +previous one, the dialog doesn't shrink back to avoid constant resizes if the message is +changed often. To do this and fit the dialog to its current contents you may call `wxWindow:fit/1` +explicitly. However the native MSW implementation of this class does make the dialog +shorter if the new text has fewer lines of text than the old one, so it is recommended to +keep the number of lines of text constant in order to avoid jarring dialog size changes. +You may also want to make the initial message, specified when creating the dialog, wide +enough to avoid having to resize the dialog later, e.g. by appending a long string of +unbreakable spaces (`wxString` (not implemented in wx)(L'\u00a0', 100)) to it. """. -spec update(This, Value, [Option]) -> boolean() when This::wxProgressDialog(), Value::integer(), @@ -177,656 +174,441 @@ update(#wx_ref{type=ThisT}=This,Value, Options) wxe_util:queue_cmd(This,Value, Opts,?get_env(),?wxProgressDialog_Update), wxe_util:rec(?wxProgressDialog_Update). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxProgressDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxProgressDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxQueryNewPaletteEvent.erl b/lib/wx/src/gen/wxQueryNewPaletteEvent.erl index 548ab2a8ea0c..d728c49588d7 100644 --- a/lib/wx/src/gen/wxQueryNewPaletteEvent.erl +++ b/lib/wx/src/gen/wxQueryNewPaletteEvent.erl @@ -22,10 +22,11 @@ -moduledoc """ Functions for wxQueryNewPaletteEvent class -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxQueryNewPaletteEvent](https://docs.wxwidgets.org/3.1/classwx_query_new_palette_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxQueryNewPaletteEvent](https://docs.wxwidgets.org/3.2/classwx_query_new_palette_event.html) """. -include("wxe.hrl"). -export([getPaletteRealized/1,setPaletteRealized/2]). @@ -38,12 +39,11 @@ wxWidgets docs: -include("wx.hrl"). -type wxQueryNewPaletteEventType() :: 'query_new_palette'. -export_type([wxQueryNewPaletteEvent/0, wxQueryNewPalette/0, wxQueryNewPaletteEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxquerynewpaletteevent.html#wxquerynewpaletteeventsetpaletterealized">external documentation</a>. +-doc "". -spec setPaletteRealized(This, Realized) -> 'ok' when This::wxQueryNewPaletteEvent(), Realized::boolean(). setPaletteRealized(#wx_ref{type=ThisT}=This,Realized) @@ -51,7 +51,7 @@ setPaletteRealized(#wx_ref{type=ThisT}=This,Realized) ?CLASS(ThisT,wxQueryNewPaletteEvent), wxe_util:queue_cmd(This,Realized,?get_env(),?wxQueryNewPaletteEvent_SetPaletteRealized). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxquerynewpaletteevent.html#wxquerynewpaletteeventgetpaletterealized">external documentation</a>. +-doc "". -spec getPaletteRealized(This) -> boolean() when This::wxQueryNewPaletteEvent(). getPaletteRealized(#wx_ref{type=ThisT}=This) -> @@ -60,30 +60,21 @@ getPaletteRealized(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxQueryNewPaletteEvent_GetPaletteRealized). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxRadioBox.erl b/lib/wx/src/gen/wxRadioBox.erl index ba0c4ea694da..507b43f7ae1c 100644 --- a/lib/wx/src/gen/wxRadioBox.erl +++ b/lib/wx/src/gen/wxRadioBox.erl @@ -20,29 +20,40 @@ -module(wxRadioBox). -moduledoc """ -Functions for wxRadioBox class - A radio box item is used to select one of number of mutually exclusive choices. + It is displayed as a vertical column or horizontal row of labelled buttons. -Styles +## Styles This class supports the following styles: +* wxRA_SPECIFY_ROWS: The major dimension parameter refers to the maximum number of rows. + +* wxRA_SPECIFY_COLS: The major dimension parameter refers to the maximum number of columns. + See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxRadioButton`, `m:wxCheckBox` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxRadioButton` + +* `m:wxCheckBox` + +This class is derived, and can use functions, from: + +* `m:wxControl` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxWindow` -wxWidgets docs: -[wxRadioBox](https://docs.wxwidgets.org/3.1/classwx_radio_box.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxRadioBox](https://docs.wxwidgets.org/3.2/classwx_radio_box.html) ## Events Event types emitted from this class: -[`command_radiobox_selected`](`m:wxCommandEvent`) + +* [`command_radiobox_selected`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/7,create/8,destroy/1,enable/1,enable/2,enable/3,getColumnCount/1, @@ -90,14 +101,13 @@ Event types emitted from this class: -type wxRadioBox() :: wx:wx_object(). -export_type([wxRadioBox/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Id,Label,Pos,Size,Choices, []) +-doc(#{equiv => new(Parent,Id,Label,Pos,Size,Choices, [])}). -spec new(Parent, Id, Label, Pos, Size, Choices) -> wxRadioBox() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()]. @@ -105,11 +115,10 @@ new(Parent,Id,Label,{PosX,PosY} = Pos,{SizeW,SizeH} = Size,Choices) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label),is_integer(PosX),is_integer(PosY),is_integer(SizeW),is_integer(SizeH),is_list(Choices) -> new(Parent,Id,Label,Pos,Size,Choices, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxwxradiobox">external documentation</a>. -doc """ Constructor, creating and showing a radiobox. -See: `create/8`, `wxValidator` (not implemented in wx) +See: `create/8` """. -spec new(Parent, Id, Label, Pos, Size, Choices, [Option]) -> wxRadioBox() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()], @@ -130,7 +139,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label,{PosX,PosY} = Pos,{SizeW,SizeH} = Size wxe_util:queue_cmd(Parent,Id,Label_UC,Pos,Size,Choices_UCA, Opts,?get_env(),?wxRadioBox_new), wxe_util:rec(?wxRadioBox_new). -%% @equiv create(This,Parent,Id,Label,Pos,Size,Choices, []) +-doc(#{equiv => create(This,Parent,Id,Label,Pos,Size,Choices, [])}). -spec create(This, Parent, Id, Label, Pos, Size, Choices) -> boolean() when This::wxRadioBox(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}, Choices::[unicode:chardata()]. @@ -138,7 +147,6 @@ create(This,Parent,Id,Label,{PosX,PosY} = Pos,{SizeW,SizeH} = Size,Choices) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label),is_integer(PosX),is_integer(PosY),is_integer(SizeW),is_integer(SizeH),is_list(Choices) -> create(This,Parent,Id,Label,Pos,Size,Choices, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxcreate">external documentation</a>. -doc """ Creates the radiobox for two-step construction. @@ -164,7 +172,7 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label,{PosX,PosY wxe_util:queue_cmd(This,Parent,Id,Label_UC,Pos,Size,Choices_UCA, Opts,?get_env(),?wxRadioBox_Create), wxe_util:rec(?wxRadioBox_Create). -%% @equiv enable(This, []) +-doc(#{equiv => enable(This, [])}). -spec enable(This) -> boolean() when This::wxRadioBox(). @@ -172,12 +180,6 @@ enable(This) when is_record(This, wx_ref) -> enable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxenable">external documentation</a>. -%% <br /> Also:<br /> -%% enable(This, [Option]) -> boolean() when<br /> -%% This::wxRadioBox(),<br /> -%% Option :: {'enable', boolean()}.<br /> -%% -doc """ Enables or disables the radiobox. @@ -201,7 +203,6 @@ enable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxRadioBox_Enable_1), wxe_util:rec(?wxRadioBox_Enable_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxenable">external documentation</a>. -doc """ Enables or disables an individual button in the radiobox. @@ -219,17 +220,18 @@ enable(#wx_ref{type=ThisT}=This,N, Options) wxe_util:queue_cmd(This,N, Opts,?get_env(),?wxRadioBox_Enable_2), wxe_util:rec(?wxRadioBox_Enable_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetselection">external documentation</a>. -doc """ -Returns the index of the selected item or `wxNOT_FOUND` if no item is selected. +Returns the index of the selected item or `wxNOT\_FOUND` if no item is selected. Return: The position of the current selection. -Remark: This method can be used with single selection list boxes only, you -should use `wxListBox:getSelections/1` for the list boxes with wxLB_MULTIPLE -style. +Remark: This method can be used with single selection list boxes only, you should use `wxListBox:getSelections/1` +for the list boxes with wxLB_MULTIPLE style. + +See: +* `setSelection/2` -See: `setSelection/2`, `wxControlWithItems:getStringSelection/1` +* `wxControlWithItems:getStringSelection/1` """. -spec getSelection(This) -> integer() when This::wxRadioBox(). @@ -238,7 +240,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRadioBox_GetSelection), wxe_util:rec(?wxRadioBox_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetstring">external documentation</a>. -doc """ Returns the label of the item with the given index. @@ -252,12 +253,11 @@ getString(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxRadioBox_GetString), wxe_util:rec(?wxRadioBox_GetString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxsetselection">external documentation</a>. -doc """ Sets the selection to the given item. -Notice that a radio box always has selection, so `n` must be valid here and -passing `wxNOT_FOUND` is not allowed. +Notice that a radio box always has selection, so `n` must be valid here and passing `wxNOT_FOUND` +is not allowed. """. -spec setSelection(This, N) -> 'ok' when This::wxRadioBox(), N::integer(). @@ -266,7 +266,7 @@ setSelection(#wx_ref{type=ThisT}=This,N) ?CLASS(ThisT,wxRadioBox), wxe_util:queue_cmd(This,N,?get_env(),?wxRadioBox_SetSelection). -%% @equiv show(This,Item, []) +-doc(#{equiv => show(This,Item, [])}). -spec show(This, Item) -> boolean() when This::wxRadioBox(), Item::integer(). @@ -274,12 +274,11 @@ show(This,Item) when is_record(This, wx_ref),is_integer(Item) -> show(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxshow">external documentation</a>. -doc """ Shows or hides individual buttons. -Return: true if the item has been shown or hidden or false if nothing was done -because it already was in the requested state. +Return: true if the item has been shown or hidden or false if nothing was done because it +already was in the requested state. See: `show/3` """. @@ -295,7 +294,6 @@ show(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxRadioBox_Show), wxe_util:rec(?wxRadioBox_Show). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetcolumncount">external documentation</a>. -doc "Returns the number of columns in the radiobox.". -spec getColumnCount(This) -> integer() when This::wxRadioBox(). @@ -304,10 +302,8 @@ getColumnCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRadioBox_GetColumnCount), wxe_util:rec(?wxRadioBox_GetColumnCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetitemhelptext">external documentation</a>. -doc """ -Returns the helptext associated with the specified `item` if any or -`wxEmptyString`. +Returns the helptext associated with the specified `item` if any or `wxEmptyString`. See: `setItemHelpText/3` """. @@ -319,11 +315,13 @@ getItemHelpText(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxRadioBox_GetItemHelpText), wxe_util:rec(?wxRadioBox_GetItemHelpText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetitemtooltip">external documentation</a>. -doc """ Returns the tooltip associated with the specified `item` if any or NULL. -See: `setItemToolTip/3`, `wxWindow:getToolTip/1` +See: +* `setItemToolTip/3` + +* `wxWindow:getToolTip/1` """. -spec getItemToolTip(This, Item) -> wxToolTip:wxToolTip() when This::wxRadioBox(), Item::integer(). @@ -333,10 +331,9 @@ getItemToolTip(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxRadioBox_GetItemToolTip), wxe_util:rec(?wxRadioBox_GetItemToolTip). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetitemfrompoint">external documentation</a>. -doc """ -Returns a radio box item under the point, a zero-based item index, or -`wxNOT_FOUND` if no item is under the point. +Returns a radio box item under the point, a zero-based item index, or `wxNOT\_FOUND` if +no item is under the point. """. -spec getItemFromPoint(This, Pt) -> integer() when This::wxRadioBox(), Pt::{X::integer(), Y::integer()}. @@ -346,7 +343,6 @@ getItemFromPoint(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxRadioBox_GetItemFromPoint), wxe_util:rec(?wxRadioBox_GetItemFromPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxgetrowcount">external documentation</a>. -doc "Returns the number of rows in the radiobox.". -spec getRowCount(This) -> integer() when This::wxRadioBox(). @@ -355,13 +351,11 @@ getRowCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRadioBox_GetRowCount), wxe_util:rec(?wxRadioBox_GetRowCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxisitemenabled">external documentation</a>. -doc """ -Returns true if the item is enabled or false if it was disabled using -`enable/3`. +Returns true if the item is enabled or false if it was disabled using `enable/3`. -This function is currently only implemented in wxMSW, wxGTK, wxQT and -wxUniversal and always returns true in the other ports. +This function is currently only implemented in wxMSW, wxGTK, wxQT and wxUniversal and +always returns true in the other ports. """. -spec isItemEnabled(This, N) -> boolean() when This::wxRadioBox(), N::integer(). @@ -371,16 +365,14 @@ isItemEnabled(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxRadioBox_IsItemEnabled), wxe_util:rec(?wxRadioBox_IsItemEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxisitemshown">external documentation</a>. -doc """ -Returns true if the item is currently shown or false if it was hidden using -`show/3`. +Returns true if the item is currently shown or false if it was hidden using `show/3`. -Note that this function returns true for an item which hadn't been hidden even -if the entire radiobox is not currently shown. +Note that this function returns true for an item which hadn't been hidden even if the +entire radiobox is not currently shown. -This function is currently only implemented in wxMSW, wxGTK, wxQT and -wxUniversal and always returns true in the other ports. +This function is currently only implemented in wxMSW, wxGTK, wxQT and wxUniversal and +always returns true in the other ports. """. -spec isItemShown(This, N) -> boolean() when This::wxRadioBox(), N::integer(). @@ -390,7 +382,6 @@ isItemShown(#wx_ref{type=ThisT}=This,N) wxe_util:queue_cmd(This,N,?get_env(),?wxRadioBox_IsItemShown), wxe_util:rec(?wxRadioBox_IsItemShown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxsetitemhelptext">external documentation</a>. -doc """ Sets the helptext for an item. @@ -406,14 +397,16 @@ setItemHelpText(#wx_ref{type=ThisT}=This,Item,Helptext) Helptext_UC = unicode:characters_to_binary(Helptext), wxe_util:queue_cmd(This,Item,Helptext_UC,?get_env(),?wxRadioBox_SetItemHelpText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobox.html#wxradioboxsetitemtooltip">external documentation</a>. -doc """ Sets the tooltip text for the specified item in the radio group. -This function is currently only implemented in wxMSW and wxGTK2 and does nothing -in the other ports. +This function is currently only implemented in wxMSW and wxGTK2 and does nothing in the +other ports. + +See: +* `getItemToolTip/2` -See: `getItemToolTip/2`, `wxWindow:setToolTip/2` +* `wxWindow:setToolTip/2` """. -spec setItemToolTip(This, Item, Text) -> 'ok' when This::wxRadioBox(), Item::integer(), Text::unicode:chardata(). @@ -423,550 +416,370 @@ setItemToolTip(#wx_ref{type=ThisT}=This,Item,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Item,Text_UC,?get_env(),?wxRadioBox_SetItemToolTip). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the radiobox item.". +-doc "Destroys the object". -spec destroy(This::wxRadioBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxRadioBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxRadioButton.erl b/lib/wx/src/gen/wxRadioButton.erl index be4906bd70ec..71ef047bab0d 100644 --- a/lib/wx/src/gen/wxRadioButton.erl +++ b/lib/wx/src/gen/wxRadioButton.erl @@ -20,33 +20,48 @@ -module(wxRadioButton). -moduledoc """ -Functions for wxRadioButton class +A radio button item is a button which usually denotes one of several mutually exclusive +options. -A radio button item is a button which usually denotes one of several mutually -exclusive options. It has a text label next to a (usually) round button. +It has a text label next to a (usually) round button. -You can create a group of mutually-exclusive radio buttons by specifying -`wxRB_GROUP` for the first in the group. The group ends when another radio -button group is created, or there are no more radio buttons. +You can create a group of mutually-exclusive radio buttons by specifying `wxRB_GROUP` for +the first in the group. The group ends when another radio button group is created, or +there are no more radio buttons. -Styles +## Styles This class supports the following styles: +* wxRB_GROUP: Marks the beginning of a new group of radio buttons. + +* wxRB_SINGLE: In some circumstances, radio buttons that are not consecutive siblings +trigger a hang bug in Windows (only). If this happens, add this style to mark the button +as not belonging to a group, and implement the mutually-exclusive group behaviour +yourself. + See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxRadioBox`, `m:wxCheckBox` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxRadioBox` + +* `m:wxCheckBox` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxRadioButton](https://docs.wxwidgets.org/3.1/classwx_radio_button.html) +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxRadioButton](https://docs.wxwidgets.org/3.2/classwx_radio_button.html) ## Events Event types emitted from this class: -[`command_radiobutton_selected`](`m:wxCommandEvent`) + +* [`command_radiobutton_selected`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getValue/1,new/0,new/3,new/4,setValue/2]). @@ -93,25 +108,23 @@ Event types emitted from this class: -type wxRadioButton() :: wx:wx_object(). -export_type([wxRadioButton/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobutton.html#wxradiobuttonwxradiobutton">external documentation</a>. -doc """ Default constructor. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new() -> wxRadioButton(). new() -> wxe_util:queue_cmd(?get_env(), ?wxRadioButton_new_0), wxe_util:rec(?wxRadioButton_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxRadioButton() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -119,11 +132,10 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> new(Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobutton.html#wxradiobuttonwxradiobutton">external documentation</a>. -doc """ Constructor, creating and showing a radio button. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new(Parent, Id, Label, [Option]) -> wxRadioButton() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), @@ -144,7 +156,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(Parent,Id,Label_UC, Opts,?get_env(),?wxRadioButton_new_4), wxe_util:rec(?wxRadioButton_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxRadioButton(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -152,7 +164,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> create(This,Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobutton.html#wxradiobuttoncreate">external documentation</a>. -doc """ Creates the choice for two-step construction. @@ -178,7 +189,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(This,Parent,Id,Label_UC, Opts,?get_env(),?wxRadioButton_Create), wxe_util:rec(?wxRadioButton_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobutton.html#wxradiobuttongetvalue">external documentation</a>. -doc "Returns true if the radio button is checked, false otherwise.". -spec getValue(This) -> boolean() when This::wxRadioButton(). @@ -187,21 +197,19 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRadioButton_GetValue), wxe_util:rec(?wxRadioButton_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxradiobutton.html#wxradiobuttonsetvalue">external documentation</a>. -doc """ Sets the radio button to checked or unchecked status. This does not cause a `wxEVT_RADIOBUTTON` event to get emitted. -If the radio button belongs to a radio group exactly one button in the group may -be checked and so this method can be only called with `value` set to true. To -uncheck a radio button in a group you must check another button in the same -group. +If the radio button belongs to a radio group exactly one button in the group may be +checked and so this method can be only called with `value` set to true. To uncheck a radio +button in a group you must check another button in the same group. -Note: Under MSW, the focused radio button is always selected, i.e. its value is -true. And, conversely, calling `SetValue(true)` will also set focus to the radio -button if the focus had previously been on another radio button in the same -group - as otherwise setting it on wouldn't work. +Note: Under MSW, the focused radio button is always selected, i.e. its value is true. +And, conversely, calling `SetValue(true)` will also set focus to the radio button if the +focus had previously been on another radio button in the same group - as otherwise setting +it on wouldn't work. """. -spec setValue(This, Value) -> 'ok' when This::wxRadioButton(), Value::boolean(). @@ -210,562 +218,378 @@ setValue(#wx_ref{type=ThisT}=This,Value) ?CLASS(ThisT,wxRadioButton), wxe_util:queue_cmd(This,Value,?get_env(),?wxRadioButton_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the radio button item.". +-doc "Destroys the object". -spec destroy(This::wxRadioButton()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxRadioButton), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxRegion.erl b/lib/wx/src/gen/wxRegion.erl index 46242a3d136f..58750cf7eb3a 100644 --- a/lib/wx/src/gen/wxRegion.erl +++ b/lib/wx/src/gen/wxRegion.erl @@ -20,23 +20,19 @@ -module(wxRegion). -moduledoc """ -Functions for wxRegion class +A `m:wxRegion` represents a simple or complex region on a device context or window. -A `m:wxRegion` represents a simple or complex region on a device context or -window. - -This class uses reference counting and copy-on-write internally so that -assignments between two instances of this class are very cheap. You can -therefore use actual objects instead of pointers without efficiency problems. If -an instance of this class is changed it will create its own data internally so -that other instances, which previously shared the data using the reference -counting, are not affected. +This class uses reference counting and copy-on-write internally so that assignments +between two instances of this class are very cheap. You can therefore use actual objects +instead of pointers without efficiency problems. If an instance of this class is changed +it will create its own data internally so that other instances, which previously shared +the data using the reference counting, are not affected. Predefined objects (include wx.hrl): -See: `wxRegionIterator` (not implemented in wx) +* ?wxNullRegion -wxWidgets docs: [wxRegion](https://docs.wxwidgets.org/3.1/classwx_region.html) +wxWidgets docs: [wxRegion](https://docs.wxwidgets.org/3.2/classwx_region.html) """. -include("wxe.hrl"). -export(['Xor'/2,'Xor'/5,clear/1,contains/2,contains/3,contains/5,convertToBitmap/1, @@ -48,27 +44,20 @@ wxWidgets docs: [wxRegion](https://docs.wxwidgets.org/3.1/classwx_region.html) -type wxRegion() :: wx:wx_object(). -export_type([wxRegion/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionwxregion">external documentation</a>. -doc """ Default constructor. -This constructor creates an invalid, or null, object, i.e. calling IsOk() on it -returns false and `isEmpty/1` returns true. +This constructor creates an invalid, or null, object, i.e. calling IsOk() on it returns +false and `isEmpty/1` returns true. """. -spec new() -> wxRegion(). new() -> wxe_util:queue_cmd(?get_env(), ?wxRegion_new_0), wxe_util:rec(?wxRegion_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionwxregion">external documentation</a>. -%% <br /> Also:<br /> -%% new(Bmp) -> wxRegion() when<br /> -%% Bmp::wxBitmap:wxBitmap().<br /> -%% -doc """ Constructs a region using a bitmap. @@ -87,11 +76,7 @@ new(#wx_ref{type=BmpT}=Bmp) -> wxe_util:queue_cmd(Bmp,?get_env(),?wxRegion_new_1_1), wxe_util:rec(?wxRegion_new_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionwxregion">external documentation</a>. --doc """ -Constructs a rectangular region from the top left point and the bottom right -point. -""". +-doc "Constructs a rectangular region from the top left point and the bottom right point.". -spec new(TopLeft, BottomRight) -> wxRegion() when TopLeft::{X::integer(), Y::integer()}, BottomRight::{X::integer(), Y::integer()}. new({TopLeftX,TopLeftY} = TopLeft,{BottomRightX,BottomRightY} = BottomRight) @@ -99,7 +84,6 @@ new({TopLeftX,TopLeftY} = TopLeft,{BottomRightX,BottomRightY} = BottomRight) wxe_util:queue_cmd(TopLeft,BottomRight,?get_env(),?wxRegion_new_2), wxe_util:rec(?wxRegion_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionwxregion">external documentation</a>. -doc "Constructs a rectangular region with the given position and size.". -spec new(X, Y, Width, Height) -> wxRegion() when X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -108,7 +92,6 @@ new(X,Y,Width,Height) wxe_util:queue_cmd(X,Y,Width,Height,?get_env(),?wxRegion_new_4), wxe_util:rec(?wxRegion_new_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionclear">external documentation</a>. -doc """ Clears the current region. @@ -120,25 +103,18 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxRegion), wxe_util:queue_cmd(This,?get_env(),?wxRegion_Clear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregioncontains">external documentation</a>. -%% <br /> Also:<br /> -%% contains(This, Rect) -> wx:wx_enum() when<br /> -%% This::wxRegion(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}.<br /> -%% -%%<br /> Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -doc """ -Returns a value indicating whether the given rectangle is contained within the -region. +Returns a value indicating whether the given rectangle is contained within the region. -This method always returns `wxOutRegion` for an invalid region but may, -nevertheless, be safely called in this case. +This method always returns `wxOutRegion` for an invalid region but may, nevertheless, be +safely called in this case. Return: One of ?wxOutRegion, ?wxPartRegion or ?wxInRegion. -Note: On Windows, only ?wxOutRegion and ?wxInRegion are returned; a value -?wxInRegion then indicates that all or some part of the region is contained in -this region. +Note: On Windows, only ?wxOutRegion and ?wxInRegion are returned; a value ?wxInRegion +then indicates that all or some part of the region is contained in this region. """. +%% Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -spec contains(This, Pt) -> wx:wx_enum() when This::wxRegion(), Pt::{X::integer(), Y::integer()}; (This, Rect) -> wx:wx_enum() when @@ -154,17 +130,15 @@ contains(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) wxe_util:queue_cmd(This,Rect,?get_env(),?wxRegion_Contains_1_1), wxe_util:rec(?wxRegion_Contains_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregioncontains">external documentation</a>. -%%<br /> Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -doc """ -Returns a value indicating whether the given point is contained within the -region. +Returns a value indicating whether the given point is contained within the region. -This method always returns `wxOutRegion` for an invalid region but may, -nevertheless, be safely called in this case. +This method always returns `wxOutRegion` for an invalid region but may, nevertheless, be +safely called in this case. Return: The return value is one of `wxOutRegion` and `wxInRegion`. """. +%% Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -spec contains(This, X, Y) -> wx:wx_enum() when This::wxRegion(), X::integer(), Y::integer(). contains(#wx_ref{type=ThisT}=This,X,Y) @@ -173,21 +147,18 @@ contains(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxRegion_Contains_2), wxe_util:rec(?wxRegion_Contains_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregioncontains">external documentation</a>. -%%<br /> Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -doc """ -Returns a value indicating whether the given rectangle is contained within the -region. +Returns a value indicating whether the given rectangle is contained within the region. -This method always returns `wxOutRegion` for an invalid region but may, -nevertheless, be safely called in this case. +This method always returns `wxOutRegion` for an invalid region but may, nevertheless, be +safely called in this case. Return: One of ?wxOutRegion, ?wxPartRegion or ?wxInRegion. -Note: On Windows, only ?wxOutRegion and ?wxInRegion are returned; a value -?wxInRegion then indicates that all or some part of the region is contained in -this region. +Note: On Windows, only ?wxOutRegion and ?wxInRegion are returned; a value ?wxInRegion +then indicates that all or some part of the region is contained in this region. """. +%% Res = ?wxOutRegion | ?wxPartRegion | ?wxInRegion -spec contains(This, X, Y, Width, Height) -> wx:wx_enum() when This::wxRegion(), X::integer(), Y::integer(), Width::integer(), Height::integer(). contains(#wx_ref{type=ThisT}=This,X,Y,Width,Height) @@ -196,10 +167,9 @@ contains(#wx_ref{type=ThisT}=This,X,Y,Width,Height) wxe_util:queue_cmd(This,X,Y,Width,Height,?get_env(),?wxRegion_Contains_4), wxe_util:rec(?wxRegion_Contains_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionconverttobitmap">external documentation</a>. -doc """ -Convert the region to a black and white bitmap with the white pixels being -inside the region. +Convert the region to a black and white bitmap with the white pixels being inside the +region. This method can't be used for invalid region. """. @@ -210,7 +180,7 @@ convertToBitmap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRegion_ConvertToBitmap), wxe_util:rec(?wxRegion_ConvertToBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregiongetbox">external documentation</a>. +-doc "". -spec getBox(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxRegion(). getBox(#wx_ref{type=ThisT}=This) -> @@ -218,11 +188,6 @@ getBox(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRegion_GetBox), wxe_util:rec(?wxRegion_GetBox). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionintersect">external documentation</a>. -%% <br /> Also:<br /> -%% intersect(This, Region) -> boolean() when<br /> -%% This::wxRegion(), Region::wxRegion().<br /> -%% -doc """ Finds the intersection of this region and another region. @@ -231,8 +196,8 @@ nevertheless be safely used even in this case. Return: true if successful, false otherwise. -Remark: Creates the intersection of the two regions, that is, the parts which -are in both regions. The result is stored in this region. +Remark: Creates the intersection of the two regions, that is, the parts which are in both +regions. The result is stored in this region. """. -spec intersect(This, Rect) -> boolean() when This::wxRegion(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}; @@ -249,18 +214,17 @@ intersect(#wx_ref{type=ThisT}=This,#wx_ref{type=RegionT}=Region) -> wxe_util:queue_cmd(This,Region,?get_env(),?wxRegion_Intersect_1_1), wxe_util:rec(?wxRegion_Intersect_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionintersect">external documentation</a>. -doc """ -Finds the intersection of this region and another, rectangular region, specified -using position and size. +Finds the intersection of this region and another, rectangular region, specified using +position and size. This method always fails, i.e. returns false, if this region is invalid but may nevertheless be safely used even in this case. Return: true if successful, false otherwise. -Remark: Creates the intersection of the two regions, that is, the parts which -are in both regions. The result is stored in this region. +Remark: Creates the intersection of the two regions, that is, the parts which are in both +regions. The result is stored in this region. """. -spec intersect(This, X, Y, Width, Height) -> boolean() when This::wxRegion(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -270,7 +234,6 @@ intersect(#wx_ref{type=ThisT}=This,X,Y,Width,Height) wxe_util:queue_cmd(This,X,Y,Width,Height,?get_env(),?wxRegion_Intersect_4), wxe_util:rec(?wxRegion_Intersect_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionisempty">external documentation</a>. -doc """ Returns true if the region is empty, false otherwise. @@ -283,11 +246,6 @@ isEmpty(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxRegion_IsEmpty), wxe_util:rec(?wxRegion_IsEmpty). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionsubtract">external documentation</a>. -%% <br /> Also:<br /> -%% subtract(This, Region) -> boolean() when<br /> -%% This::wxRegion(), Region::wxRegion().<br /> -%% -doc """ Subtracts a region from this region. @@ -296,8 +254,8 @@ nevertheless be safely used even in this case. Return: true if successful, false otherwise. -Remark: This operation combines the parts of 'this' region that are not part of -the second region. The result is stored in this region. +Remark: This operation combines the parts of 'this' region that are not part of the +second region. The result is stored in this region. """. -spec subtract(This, Rect) -> boolean() when This::wxRegion(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}; @@ -314,7 +272,7 @@ subtract(#wx_ref{type=ThisT}=This,#wx_ref{type=RegionT}=Region) -> wxe_util:queue_cmd(This,Region,?get_env(),?wxRegion_Subtract_1_1), wxe_util:rec(?wxRegion_Subtract_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionoffset">external documentation</a>. +-doc "". -spec offset(This, Pt) -> boolean() when This::wxRegion(), Pt::{X::integer(), Y::integer()}. offset(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) @@ -323,12 +281,11 @@ offset(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxRegion_Offset_1), wxe_util:rec(?wxRegion_Offset_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionoffset">external documentation</a>. -doc """ Moves the region by the specified offsets in horizontal and vertical directions. -This method can't be called if the region is invalid as it doesn't make sense to -offset it then. Attempts to do it will result in assert failure. +This method can't be called if the region is invalid as it doesn't make sense to offset +it then. Attempts to do it will result in assert failure. Return: true if successful, false otherwise (the region is unchanged then). """. @@ -340,21 +297,16 @@ offset(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxRegion_Offset_2), wxe_util:rec(?wxRegion_Offset_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionunion">external documentation</a>. -%% <br /> Also:<br /> -%% union(This, Rect) -> boolean() when<br /> -%% This::wxRegion(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}.<br /> -%% -doc """ Finds the union of this region and another, rectangular region. -This method can be used even if this region is invalid and has the natural -behaviour in this case, i.e. makes this region equal to the given rectangle. +This method can be used even if this region is invalid and has the natural behaviour in +this case, i.e. makes this region equal to the given rectangle. Return: true if successful, false otherwise. -Remark: This operation creates a region that combines all of this region and the -second region. The result is stored in this region. +Remark: This operation creates a region that combines all of this region and the second +region. The result is stored in this region. """. -spec union(This, Region) -> boolean() when This::wxRegion(), Region::wxRegion:wxRegion() | wxBitmap:wxBitmap(); @@ -377,7 +329,7 @@ union(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) wxe_util:queue_cmd(This,Rect,?get_env(),?wxRegion_Union_1_1), wxe_util:rec(?wxRegion_Union_1_1). -%% @equiv union(This,Bmp,TransColour, []) +-doc(#{equiv => union(This,Bmp,TransColour, [])}). -spec union(This, Bmp, TransColour) -> boolean() when This::wxRegion(), Bmp::wxBitmap:wxBitmap(), TransColour::wx:wx_colour(). @@ -385,17 +337,16 @@ union(This,Bmp,TransColour) when is_record(This, wx_ref),is_record(Bmp, wx_ref),?is_colordata(TransColour) -> union(This,Bmp,TransColour, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionunion">external documentation</a>. -doc """ Finds the union of this region and the non-transparent pixels of a bitmap. -Colour to be treated as transparent is specified in the `transColour` argument, -along with an optional colour tolerance value. +Colour to be treated as transparent is specified in the `transColour` argument, along +with an optional colour tolerance value. Return: true if successful, false otherwise. -Remark: This operation creates a region that combines all of this region and the -second region. The result is stored in this region. +Remark: This operation creates a region that combines all of this region and the second +region. The result is stored in this region. """. -spec union(This, Bmp, TransColour, [Option]) -> boolean() when This::wxRegion(), Bmp::wxBitmap:wxBitmap(), TransColour::wx:wx_colour(), @@ -410,18 +361,17 @@ union(#wx_ref{type=ThisT}=This,#wx_ref{type=BmpT}=Bmp,TransColour, Options) wxe_util:queue_cmd(This,Bmp,wxe_util:color(TransColour), Opts,?get_env(),?wxRegion_Union_3), wxe_util:rec(?wxRegion_Union_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionunion">external documentation</a>. -doc """ -Finds the union of this region and another, rectangular region, specified using -position and size. +Finds the union of this region and another, rectangular region, specified using position +and size. -This method can be used even if this region is invalid and has the natural -behaviour in this case, i.e. makes this region equal to the given rectangle. +This method can be used even if this region is invalid and has the natural behaviour in +this case, i.e. makes this region equal to the given rectangle. Return: true if successful, false otherwise. -Remark: This operation creates a region that combines all of this region and the -second region. The result is stored in this region. +Remark: This operation creates a region that combines all of this region and the second +region. The result is stored in this region. """. -spec union(This, X, Y, Width, Height) -> boolean() when This::wxRegion(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -431,22 +381,16 @@ union(#wx_ref{type=ThisT}=This,X,Y,Width,Height) wxe_util:queue_cmd(This,X,Y,Width,Height,?get_env(),?wxRegion_Union_4), wxe_util:rec(?wxRegion_Union_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionxor">external documentation</a>. -%% <br /> Also:<br /> -%% 'Xor'(This, Region) -> boolean() when<br /> -%% This::wxRegion(), Region::wxRegion().<br /> -%% -doc """ Finds the Xor of this region and another region. -This method can be used even if this region is invalid and has the natural -behaviour in this case, i.e. makes this region equal to the given `region`. +This method can be used even if this region is invalid and has the natural behaviour in +this case, i.e. makes this region equal to the given `region`. Return: true if successful, false otherwise. -Remark: This operation creates a region that combines all of this region and the -second region, except for any overlapping areas. The result is stored in this -region. +Remark: This operation creates a region that combines all of this region and the second +region, except for any overlapping areas. The result is stored in this region. """. -spec 'Xor'(This, Rect) -> boolean() when This::wxRegion(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}; @@ -463,19 +407,17 @@ region. wxe_util:queue_cmd(This,Region,?get_env(),?wxRegion_Xor_1_1), wxe_util:rec(?wxRegion_Xor_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxregion.html#wxregionxor">external documentation</a>. -doc """ -Finds the Xor of this region and another, rectangular region, specified using -position and size. +Finds the Xor of this region and another, rectangular region, specified using position +and size. -This method can be used even if this region is invalid and has the natural -behaviour in this case, i.e. makes this region equal to the given rectangle. +This method can be used even if this region is invalid and has the natural behaviour in +this case, i.e. makes this region equal to the given rectangle. Return: true if successful, false otherwise. -Remark: This operation creates a region that combines all of this region and the -second region, except for any overlapping areas. The result is stored in this -region. +Remark: This operation creates a region that combines all of this region and the second +region, except for any overlapping areas. The result is stored in this region. """. -spec 'Xor'(This, X, Y, Width, Height) -> boolean() when This::wxRegion(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -485,12 +427,7 @@ region. wxe_util:queue_cmd(This,X,Y,Width,Height,?get_env(),?wxRegion_Xor_4), wxe_util:rec(?wxRegion_Xor_4). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -See reference-counted object destruction for more info. -""". +-doc "Destroys the object". -spec destroy(This::wxRegion()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxRegion), diff --git a/lib/wx/src/gen/wxSashEvent.erl b/lib/wx/src/gen/wxSashEvent.erl index b93dd89452ad..40f37359fc1d 100644 --- a/lib/wx/src/gen/wxSashEvent.erl +++ b/lib/wx/src/gen/wxSashEvent.erl @@ -20,35 +20,33 @@ -module(wxSashEvent). -moduledoc """ -Functions for wxSashEvent class +A sash event is sent when the sash of a `m:wxSashWindow` has been dragged by the user. -A sash event is sent when the sash of a `m:wxSashWindow` has been dragged by the -user. +Remark: When a sash belonging to a sash window is dragged by the user, and then released, +this event is sent to the window, where it may be processed by an event table entry in a +derived class, a plug-in event handler or an ancestor class. Note that the `m:wxSashWindow` +doesn't change the window's size itself. It relies on the application's event handler to +do that. This is because the application may have to handle other consequences of the +resize, or it may wish to veto it altogether. The event handler should look at the drag +rectangle: see `getDragRect/1` to see what the new size of the window would be if the resize were to be +applied. It should also call `getDragStatus/1` to see whether the drag was OK or out of the current allowed range. -Remark: When a sash belonging to a sash window is dragged by the user, and then -released, this event is sent to the window, where it may be processed by an -event table entry in a derived class, a plug-in event handler or an ancestor -class. Note that the `m:wxSashWindow` doesn't change the window's size itself. -It relies on the application's event handler to do that. This is because the -application may have to handle other consequences of the resize, or it may wish -to veto it altogether. The event handler should look at the drag rectangle: see -`getDragRect/1` to see what the new size of the window would be if the resize -were to be applied. It should also call `getDragStatus/1` to see whether the -drag was OK or out of the current allowed range. +See: +* `m:wxSashWindow` -See: `m:wxSashWindow`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxSashEvent](https://docs.wxwidgets.org/3.1/classwx_sash_event.html) +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxSashEvent](https://docs.wxwidgets.org/3.2/classwx_sash_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxSashEventType`](`t:wxSashEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxSashEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getDragRect/1,getDragStatus/1,getEdge/1]). @@ -63,19 +61,17 @@ subscribe to events of this type. -include("wx.hrl"). -type wxSashEventType() :: 'sash_dragged'. -export_type([wxSashEvent/0, wxSash/0, wxSashEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashevent.html#wxsasheventgetedge">external documentation</a>. -%%<br /> Res = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -doc """ Returns the dragged edge. The return value is one of wxSASH_TOP, wxSASH_RIGHT, wxSASH_BOTTOM, wxSASH_LEFT. """. +%% Res = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -spec getEdge(This) -> wx:wx_enum() when This::wxSashEvent(). getEdge(#wx_ref{type=ThisT}=This) -> @@ -83,10 +79,9 @@ getEdge(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashEvent_GetEdge), wxe_util:rec(?wxSashEvent_GetEdge). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashevent.html#wxsasheventgetdragrect">external documentation</a>. -doc """ -Returns the rectangle representing the new size the window would be if the -resize was applied. +Returns the rectangle representing the new size the window would be if the resize was +applied. It is up to the application to set the window size if required. """. @@ -97,15 +92,14 @@ getDragRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashEvent_GetDragRect), wxe_util:rec(?wxSashEvent_GetDragRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashevent.html#wxsasheventgetdragstatus">external documentation</a>. -%%<br /> Res = ?wxSASH_STATUS_OK | ?wxSASH_STATUS_OUT_OF_RANGE -doc """ -Returns the status of the sash: one of wxSASH_STATUS_OK, -wxSASH_STATUS_OUT_OF_RANGE. +Returns the status of the sash: one of wxSASH\_STATUS\_OK, +wxSASH\_STATUS\_OUT\_OF\_RANGE. -If the drag caused the notional bounding box of the window to flip over, for -example, the drag will be out of rage. +If the drag caused the notional bounding box of the window to flip over, for example, the +drag will be out of rage. """. +%% Res = ?wxSASH_STATUS_OK | ?wxSASH_STATUS_OUT_OF_RANGE -spec getDragStatus(This) -> wx:wx_enum() when This::wxSashEvent(). getDragStatus(#wx_ref{type=ThisT}=This) -> @@ -114,58 +108,40 @@ getDragStatus(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxSashEvent_GetDragStatus). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSashLayoutWindow.erl b/lib/wx/src/gen/wxSashLayoutWindow.erl index aa48d4008de5..526c549bd3fe 100644 --- a/lib/wx/src/gen/wxSashLayoutWindow.erl +++ b/lib/wx/src/gen/wxSashLayoutWindow.erl @@ -20,34 +20,38 @@ -module(wxSashLayoutWindow). -moduledoc """ -Functions for wxSashLayoutWindow class +`m:wxSashLayoutWindow` responds to OnCalculateLayout events generated by `m:wxLayoutAlgorithm`. -`m:wxSashLayoutWindow` responds to OnCalculateLayout events generated by -`m:wxLayoutAlgorithm`. It allows the application to use simple accessors to -specify how the window should be laid out, rather than having to respond to -events. +It allows the application to use simple accessors to specify how the window should be +laid out, rather than having to respond to events. -The fact that the class derives from `m:wxSashWindow` allows sashes to be used -if required, to allow the windows to be user-resizable. +The fact that the class derives from `m:wxSashWindow` allows sashes to be used if +required, to allow the windows to be user-resizable. -The documentation for `m:wxLayoutAlgorithm` explains the purpose of this class -in more detail. +The documentation for `m:wxLayoutAlgorithm` explains the purpose of this class in more detail. For the window styles see `m:wxSashWindow`. -This class handles the EVT_QUERY_LAYOUT_INFO and EVT_CALCULATE_LAYOUT events for -you. However, if you use sashes, see `m:wxSashWindow` for relevant event -information. See also `m:wxLayoutAlgorithm` for information about the layout -events. +This class handles the EVT_QUERY_LAYOUT_INFO and EVT_CALCULATE_LAYOUT events for you. +However, if you use sashes, see `m:wxSashWindow` for relevant event information. See also `m:wxLayoutAlgorithm` +for information about the layout events. -See: `m:wxLayoutAlgorithm`, `m:wxSashWindow`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +See: +* `m:wxLayoutAlgorithm` -This class is derived (and can use functions) from: `m:wxSashWindow` -`m:wxWindow` `m:wxEvtHandler` +* `m:wxSashWindow` -wxWidgets docs: -[wxSashLayoutWindow](https://docs.wxwidgets.org/3.1/classwx_sash_layout_window.html) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: + +* `m:wxSashWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxSashLayoutWindow](https://docs.wxwidgets.org/3.2/classwx_sash_layout_window.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getAlignment/1,getOrientation/1,new/0,new/1, @@ -97,21 +101,19 @@ wxWidgets docs: -type wxSashLayoutWindow() :: wx:wx_object(). -export_type([wxSashLayoutWindow/0]). -%% @hidden -doc false. parent_class(wxSashWindow) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowwxsashlayoutwindow">external documentation</a>. -doc "Default ctor.". -spec new() -> wxSashLayoutWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSashLayoutWindow_new_0), wxe_util:rec(?wxSashLayoutWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxSashLayoutWindow() when Parent::wxWindow:wxWindow(). @@ -119,10 +121,9 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowwxsashlayoutwindow">external documentation</a>. -doc """ -Constructs a sash layout window, which can be a child of a frame, dialog or any -other non-control window. +Constructs a sash layout window, which can be a child of a frame, dialog or any other +non-control window. """. -spec new(Parent, [Option]) -> wxSashLayoutWindow() when Parent::wxWindow:wxWindow(), @@ -142,7 +143,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxSashLayoutWindow_new_2), wxe_util:rec(?wxSashLayoutWindow_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxSashLayoutWindow(), Parent::wxWindow:wxWindow(). @@ -150,10 +151,9 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowcreate">external documentation</a>. -doc """ -Initializes a sash layout window, which can be a child of a frame, dialog or any -other non-control window. +Initializes a sash layout window, which can be a child of a frame, dialog or any other +non-control window. """. -spec create(This, Parent, [Option]) -> boolean() when This::wxSashLayoutWindow(), Parent::wxWindow:wxWindow(), @@ -174,12 +174,11 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxSashLayoutWindow_Create), wxe_util:rec(?wxSashLayoutWindow_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowgetalignment">external documentation</a>. -%%<br /> Res = ?wxLAYOUT_NONE | ?wxLAYOUT_TOP | ?wxLAYOUT_LEFT | ?wxLAYOUT_RIGHT | ?wxLAYOUT_BOTTOM -doc """ -Returns the alignment of the window: one of wxLAYOUT_TOP, wxLAYOUT_LEFT, -wxLAYOUT_RIGHT, wxLAYOUT_BOTTOM. +Returns the alignment of the window: one of wxLAYOUT\_TOP, wxLAYOUT\_LEFT, +wxLAYOUT\_RIGHT, wxLAYOUT\_BOTTOM. """. +%% Res = ?wxLAYOUT_NONE | ?wxLAYOUT_TOP | ?wxLAYOUT_LEFT | ?wxLAYOUT_RIGHT | ?wxLAYOUT_BOTTOM -spec getAlignment(This) -> wx:wx_enum() when This::wxSashLayoutWindow(). getAlignment(#wx_ref{type=ThisT}=This) -> @@ -187,12 +186,8 @@ getAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashLayoutWindow_GetAlignment), wxe_util:rec(?wxSashLayoutWindow_GetAlignment). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowgetorientation">external documentation</a>. -%%<br /> Res = ?wxLAYOUT_HORIZONTAL | ?wxLAYOUT_VERTICAL --doc """ -Returns the orientation of the window: one of wxLAYOUT_HORIZONTAL, -wxLAYOUT_VERTICAL. -""". +-doc "Returns the orientation of the window: one of wxLAYOUT\_HORIZONTAL, wxLAYOUT\_VERTICAL.". +%% Res = ?wxLAYOUT_HORIZONTAL | ?wxLAYOUT_VERTICAL -spec getOrientation(This) -> wx:wx_enum() when This::wxSashLayoutWindow(). getOrientation(#wx_ref{type=ThisT}=This) -> @@ -200,15 +195,13 @@ getOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashLayoutWindow_GetOrientation), wxe_util:rec(?wxSashLayoutWindow_GetOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowsetalignment">external documentation</a>. -%%<br /> Alignment = ?wxLAYOUT_NONE | ?wxLAYOUT_TOP | ?wxLAYOUT_LEFT | ?wxLAYOUT_RIGHT | ?wxLAYOUT_BOTTOM -doc """ -Sets the alignment of the window (which edge of the available parent client area -the window is attached to). +Sets the alignment of the window (which edge of the available parent client area the +window is attached to). -`alignment` is one of wxLAYOUT_TOP, wxLAYOUT_LEFT, wxLAYOUT_RIGHT, -wxLAYOUT_BOTTOM. +`alignment` is one of wxLAYOUT_TOP, wxLAYOUT_LEFT, wxLAYOUT_RIGHT, wxLAYOUT_BOTTOM. """. +%% Alignment = ?wxLAYOUT_NONE | ?wxLAYOUT_TOP | ?wxLAYOUT_LEFT | ?wxLAYOUT_RIGHT | ?wxLAYOUT_BOTTOM -spec setAlignment(This, Alignment) -> 'ok' when This::wxSashLayoutWindow(), Alignment::wx:wx_enum(). setAlignment(#wx_ref{type=ThisT}=This,Alignment) @@ -216,13 +209,11 @@ setAlignment(#wx_ref{type=ThisT}=This,Alignment) ?CLASS(ThisT,wxSashLayoutWindow), wxe_util:queue_cmd(This,Alignment,?get_env(),?wxSashLayoutWindow_SetAlignment). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowsetdefaultsize">external documentation</a>. -doc """ Sets the default dimensions of the window. -The dimension other than the orientation will be fixed to this value, and the -orientation dimension will be ignored and the window stretched to fit the -available space. +The dimension other than the orientation will be fixed to this value, and the orientation +dimension will be ignored and the window stretched to fit the available space. """. -spec setDefaultSize(This, Size) -> 'ok' when This::wxSashLayoutWindow(), Size::{W::integer(), H::integer()}. @@ -231,14 +222,13 @@ setDefaultSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSashLayoutWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxSashLayoutWindow_SetDefaultSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashlayoutwindow.html#wxsashlayoutwindowsetorientation">external documentation</a>. -%%<br /> Orientation = ?wxLAYOUT_HORIZONTAL | ?wxLAYOUT_VERTICAL -doc """ -Sets the orientation of the window (the direction the window will stretch in, to -fill the available parent client area). +Sets the orientation of the window (the direction the window will stretch in, to fill the +available parent client area). `orientation` is one of wxLAYOUT_HORIZONTAL, wxLAYOUT_VERTICAL. """. +%% Orientation = ?wxLAYOUT_HORIZONTAL | ?wxLAYOUT_VERTICAL -spec setOrientation(This, Orientation) -> 'ok' when This::wxSashLayoutWindow(), Orientation::wx:wx_enum(). setOrientation(#wx_ref{type=ThisT}=This,Orientation) @@ -246,592 +236,398 @@ setOrientation(#wx_ref{type=ThisT}=This,Orientation) ?CLASS(ThisT,wxSashLayoutWindow), wxe_util:queue_cmd(This,Orientation,?get_env(),?wxSashLayoutWindow_SetOrientation). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxSashLayoutWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSashLayoutWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxSashWindow -%% @hidden -doc false. setSashVisible(This,Edge,Visible) -> wxSashWindow:setSashVisible(This,Edge,Visible). -%% @hidden -doc false. setMinimumSizeY(This,Min) -> wxSashWindow:setMinimumSizeY(This,Min). -%% @hidden -doc false. setMinimumSizeX(This,Min) -> wxSashWindow:setMinimumSizeX(This,Min). -%% @hidden -doc false. setMaximumSizeY(This,Min) -> wxSashWindow:setMaximumSizeY(This,Min). -%% @hidden -doc false. setMaximumSizeX(This,Min) -> wxSashWindow:setMaximumSizeX(This,Min). -%% @hidden -doc false. getMinimumSizeY(This) -> wxSashWindow:getMinimumSizeY(This). -%% @hidden -doc false. getMinimumSizeX(This) -> wxSashWindow:getMinimumSizeX(This). -%% @hidden -doc false. getMaximumSizeY(This) -> wxSashWindow:getMaximumSizeY(This). -%% @hidden -doc false. getMaximumSizeX(This) -> wxSashWindow:getMaximumSizeX(This). -%% @hidden -doc false. getSashVisible(This,Edge) -> wxSashWindow:getSashVisible(This,Edge). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSashWindow.erl b/lib/wx/src/gen/wxSashWindow.erl index 6fb3b49a5268..329f50ec5f12 100644 --- a/lib/wx/src/gen/wxSashWindow.erl +++ b/lib/wx/src/gen/wxSashWindow.erl @@ -20,31 +20,45 @@ -module(wxSashWindow). -moduledoc """ -Functions for wxSashWindow class +`m:wxSashWindow` allows any of its edges to have a sash which can be dragged to resize +the window. -`m:wxSashWindow` allows any of its edges to have a sash which can be dragged to -resize the window. The actual content window will be created by the application -as a child of `m:wxSashWindow`. +The actual content window will be created by the application as a child of `m:wxSashWindow`. -The window (or an ancestor) will be notified of a drag via a `m:wxSashEvent` -notification. +The window (or an ancestor) will be notified of a drag via a `m:wxSashEvent` notification. -Styles +## Styles This class supports the following styles: -See: `m:wxSashEvent`, `m:wxSashLayoutWindow`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* wxSW_3D: Draws a 3D effect sash and border. -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* wxSW_3DSASH: Draws a 3D effect sash. -wxWidgets docs: -[wxSashWindow](https://docs.wxwidgets.org/3.1/classwx_sash_window.html) +* wxSW_3DBORDER: Draws a 3D effect border. + +* wxSW_BORDER: Draws a thin black border. + +See: +* `m:wxSashEvent` + +* `m:wxSashLayoutWindow` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxSashWindow](https://docs.wxwidgets.org/3.2/classwx_sash_window.html) ## Events -Event types emitted from this class: [`sash_dragged`](`m:wxSashEvent`) +Event types emitted from this class: + +* [`sash_dragged`](`m:wxSashEvent`) """. -include("wxe.hrl"). -export([destroy/1,getMaximumSizeX/1,getMaximumSizeY/1,getMinimumSizeX/1,getMinimumSizeY/1, @@ -93,20 +107,18 @@ Event types emitted from this class: [`sash_dragged`](`m:wxSashEvent`) -type wxSashWindow() :: wx:wx_object(). -export_type([wxSashWindow/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowwxsashwindow">external documentation</a>. -doc "Default ctor.". -spec new() -> wxSashWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSashWindow_new_0), wxe_util:rec(?wxSashWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxSashWindow() when Parent::wxWindow:wxWindow(). @@ -114,7 +126,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowwxsashwindow">external documentation</a>. -doc """ Constructs a sash window, which can be a child of a frame, dialog or any other non-control window. @@ -137,13 +148,12 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxSashWindow_new_2), wxe_util:rec(?wxSashWindow_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowgetsashvisible">external documentation</a>. -%%<br /> Edge = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -doc """ Returns true if a sash is visible on the given edge, false otherwise. See: `setSashVisible/3` """. +%% Edge = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -spec getSashVisible(This, Edge) -> boolean() when This::wxSashWindow(), Edge::wx:wx_enum(). getSashVisible(#wx_ref{type=ThisT}=This,Edge) @@ -152,7 +162,6 @@ getSashVisible(#wx_ref{type=ThisT}=This,Edge) wxe_util:queue_cmd(This,Edge,?get_env(),?wxSashWindow_GetSashVisible), wxe_util:rec(?wxSashWindow_GetSashVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowgetmaximumsizex">external documentation</a>. -doc "Gets the maximum window size in the x direction.". -spec getMaximumSizeX(This) -> integer() when This::wxSashWindow(). @@ -161,7 +170,6 @@ getMaximumSizeX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashWindow_GetMaximumSizeX), wxe_util:rec(?wxSashWindow_GetMaximumSizeX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowgetmaximumsizey">external documentation</a>. -doc "Gets the maximum window size in the y direction.". -spec getMaximumSizeY(This) -> integer() when This::wxSashWindow(). @@ -170,7 +178,6 @@ getMaximumSizeY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashWindow_GetMaximumSizeY), wxe_util:rec(?wxSashWindow_GetMaximumSizeY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowgetminimumsizex">external documentation</a>. -doc "Gets the minimum window size in the x direction.". -spec getMinimumSizeX(This) -> integer() when This::wxSashWindow(). @@ -179,7 +186,6 @@ getMinimumSizeX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashWindow_GetMinimumSizeX), wxe_util:rec(?wxSashWindow_GetMinimumSizeX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowgetminimumsizey">external documentation</a>. -doc "Gets the minimum window size in the y direction.". -spec getMinimumSizeY(This) -> integer() when This::wxSashWindow(). @@ -188,7 +194,6 @@ getMinimumSizeY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSashWindow_GetMinimumSizeY), wxe_util:rec(?wxSashWindow_GetMinimumSizeY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowsetmaximumsizex">external documentation</a>. -doc "Sets the maximum window size in the x direction.". -spec setMaximumSizeX(This, Min) -> 'ok' when This::wxSashWindow(), Min::integer(). @@ -197,7 +202,6 @@ setMaximumSizeX(#wx_ref{type=ThisT}=This,Min) ?CLASS(ThisT,wxSashWindow), wxe_util:queue_cmd(This,Min,?get_env(),?wxSashWindow_SetMaximumSizeX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowsetmaximumsizey">external documentation</a>. -doc "Sets the maximum window size in the y direction.". -spec setMaximumSizeY(This, Min) -> 'ok' when This::wxSashWindow(), Min::integer(). @@ -206,7 +210,6 @@ setMaximumSizeY(#wx_ref{type=ThisT}=This,Min) ?CLASS(ThisT,wxSashWindow), wxe_util:queue_cmd(This,Min,?get_env(),?wxSashWindow_SetMaximumSizeY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowsetminimumsizex">external documentation</a>. -doc "Sets the minimum window size in the x direction.". -spec setMinimumSizeX(This, Min) -> 'ok' when This::wxSashWindow(), Min::integer(). @@ -215,7 +218,6 @@ setMinimumSizeX(#wx_ref{type=ThisT}=This,Min) ?CLASS(ThisT,wxSashWindow), wxe_util:queue_cmd(This,Min,?get_env(),?wxSashWindow_SetMinimumSizeX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowsetminimumsizey">external documentation</a>. -doc "Sets the minimum window size in the y direction.". -spec setMinimumSizeY(This, Min) -> 'ok' when This::wxSashWindow(), Min::integer(). @@ -224,13 +226,12 @@ setMinimumSizeY(#wx_ref{type=ThisT}=This,Min) ?CLASS(ThisT,wxSashWindow), wxe_util:queue_cmd(This,Min,?get_env(),?wxSashWindow_SetMinimumSizeY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsashwindow.html#wxsashwindowsetsashvisible">external documentation</a>. -%%<br /> Edge = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -doc """ Call this function to make a sash visible or invisible on a particular edge. See: `getSashVisible/2` """. +%% Edge = ?wxSASH_TOP | ?wxSASH_RIGHT | ?wxSASH_BOTTOM | ?wxSASH_LEFT | ?wxSASH_NONE -spec setSashVisible(This, Edge, Visible) -> 'ok' when This::wxSashWindow(), Edge::wx:wx_enum(), Visible::boolean(). setSashVisible(#wx_ref{type=ThisT}=This,Edge,Visible) @@ -238,561 +239,377 @@ setSashVisible(#wx_ref{type=ThisT}=This,Edge,Visible) ?CLASS(ThisT,wxSashWindow), wxe_util:queue_cmd(This,Edge,Visible,?get_env(),?wxSashWindow_SetSashVisible). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxSashWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSashWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxScreenDC.erl b/lib/wx/src/gen/wxScreenDC.erl index c9b77b5df929..b8dff63309eb 100644 --- a/lib/wx/src/gen/wxScreenDC.erl +++ b/lib/wx/src/gen/wxScreenDC.erl @@ -20,21 +20,31 @@ -module(wxScreenDC). -moduledoc """ -Functions for wxScreenDC class +A `m:wxScreenDC` can be used to paint on the screen. -A `m:wxScreenDC` can be used to paint on the screen. This should normally be -constructed as a temporary stack object; don't store a `m:wxScreenDC` object. +This should normally be constructed as a temporary stack object; don't store a `m:wxScreenDC` +object. -When using multiple monitors, `m:wxScreenDC` corresponds to the entire virtual -screen composed of all of them. Notice that coordinates on `m:wxScreenDC` can be -negative in this case, see `wxDisplay:getGeometry/1` for more. +When using multiple monitors, `m:wxScreenDC` corresponds to the entire virtual screen +composed of all of them. Notice that coordinates on `m:wxScreenDC` can be negative in this +case, see `wxDisplay:getGeometry/1` for more. -See: `m:wxDC`, `m:wxMemoryDC`, `m:wxPaintDC`, `m:wxClientDC`, `m:wxWindowDC` +See: +* `m:wxDC` -This class is derived (and can use functions) from: `m:wxDC` +* `m:wxMemoryDC` -wxWidgets docs: -[wxScreenDC](https://docs.wxwidgets.org/3.1/classwx_screen_d_c.html) +* `m:wxPaintDC` + +* `m:wxClientDC` + +* `m:wxWindowDC` + +This class is derived, and can use functions, from: + +* `m:wxDC` + +wxWidgets docs: [wxScreenDC](https://docs.wxwidgets.org/3.2/classwx_screen_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/0]). @@ -63,299 +73,204 @@ wxWidgets docs: -type wxScreenDC() :: wx:wx_object(). -export_type([wxScreenDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscreendc.html#wxscreendcwxscreendc">external documentation</a>. -doc "Constructor.". -spec new() -> wxScreenDC(). new() -> wxe_util:queue_cmd(?get_env(), ?wxScreenDC_new), wxe_util:rec(?wxScreenDC_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxScreenDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxScreenDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxScrollBar.erl b/lib/wx/src/gen/wxScrollBar.erl index 672c86ee1ede..8ce2aa583753 100644 --- a/lib/wx/src/gen/wxScrollBar.erl +++ b/lib/wx/src/gen/wxScrollBar.erl @@ -20,76 +20,102 @@ -module(wxScrollBar). -moduledoc """ -Functions for wxScrollBar class - -A `m:wxScrollBar` is a control that represents a horizontal or vertical -scrollbar. - -It is distinct from the two scrollbars that some windows provide automatically, -but the two types of scrollbar share the way events are received. - -Remark: A scrollbar has the following main attributes: range, thumb size, page -size, and position. The range is the total number of units associated with the -view represented by the scrollbar. For a table with 15 columns, the range would -be 15. The thumb size is the number of units that are currently visible. For the -table example, the window might be sized so that only 5 columns are currently -visible, in which case the application would set the thumb size to 5. When the -thumb size becomes the same as or greater than the range, the scrollbar will be -automatically hidden on most platforms. The page size is the number of units -that the scrollbar should scroll by, when 'paging' through the data. This value -is normally the same as the thumb size length, because it is natural to assume -that the visible window size defines a page. The scrollbar position is the -current thumb position. Most applications will find it convenient to provide a -function called AdjustScrollbars() which can be called initially, from an OnSize -event handler, and whenever the application data changes in size. It will adjust -the view, object and page size according to the size of the window and the size -of the data. - -Styles +A `m:wxScrollBar` is a control that represents a horizontal or vertical scrollbar. + +It is distinct from the two scrollbars that some windows provide automatically, but the +two types of scrollbar share the way events are received. + +Remark: A scrollbar has the following main attributes: range, thumb size, page size, and +position. The range is the total number of units associated with the view represented by +the scrollbar. For a table with 15 columns, the range would be 15. The thumb size is the +number of units that are currently visible. For the table example, the window might be +sized so that only 5 columns are currently visible, in which case the application would +set the thumb size to 5. When the thumb size becomes the same as or greater than the +range, the scrollbar will be automatically hidden on most platforms. The page size is the +number of units that the scrollbar should scroll by, when 'paging' through the data. This +value is normally the same as the thumb size length, because it is natural to assume that +the visible window size defines a page. The scrollbar position is the current thumb +position. Most applications will find it convenient to provide a function called +AdjustScrollbars() which can be called initially, from an OnSize event handler, and +whenever the application data changes in size. It will adjust the view, object and page +size according to the size of the window and the size of the data. + +## Styles This class supports the following styles: +* wxSB_HORIZONTAL: Specifies a horizontal scrollbar. + +* wxSB_VERTICAL: Specifies a vertical scrollbar. + The difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED -The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the -thumb using the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is -also followed by an EVT_SCROLL_CHANGED event). +The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the thumb using +the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is also followed by an +EVT_SCROLL_CHANGED event). -The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the -thumb position, and when clicking next to the thumb (In all these cases the +The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the thumb +position, and when clicking next to the thumb (In all these cases the EVT_SCROLL_THUMBRELEASE event does not happen). -In short, the EVT_SCROLL_CHANGED event is triggered when scrolling/moving has -finished independently of the way it had started. Please see the -page_samples_widgets ("Slider" page) to see the difference between -EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. +In short, the EVT_SCROLL_CHANGED event is triggered when scrolling/moving has finished +independently of the way it had started. Please see the page_samples_widgets ("Slider" +page) to see the difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. See: -[Overview scrolling](https://docs.wxwidgets.org/3.1/overview_scrolling.html#overview_scrolling), -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxScrolled` (not implemented in wx) +* [Overview scrolling](https://docs.wxwidgets.org/3.2/overview_scrolling.html#overview_scrolling) + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxScrollBar](https://docs.wxwidgets.org/3.1/classwx_scroll_bar.html) +wxWidgets docs: [wxScrollBar](https://docs.wxwidgets.org/3.2/classwx_scroll_bar.html) ## Events -Event types emitted from this class: [`scroll_top`](`m:wxScrollEvent`), -[`scroll_bottom`](`m:wxScrollEvent`), [`scroll_lineup`](`m:wxScrollEvent`), -[`scroll_linedown`](`m:wxScrollEvent`), [`scroll_pageup`](`m:wxScrollEvent`), -[`scroll_pagedown`](`m:wxScrollEvent`), -[`scroll_thumbtrack`](`m:wxScrollEvent`), -[`scroll_thumbrelease`](`m:wxScrollEvent`), -[`scroll_changed`](`m:wxScrollEvent`), [`scroll_top`](`m:wxScrollEvent`), -[`scroll_bottom`](`m:wxScrollEvent`), [`scroll_lineup`](`m:wxScrollEvent`), -[`scroll_linedown`](`m:wxScrollEvent`), [`scroll_pageup`](`m:wxScrollEvent`), -[`scroll_pagedown`](`m:wxScrollEvent`), -[`scroll_thumbtrack`](`m:wxScrollEvent`), -[`scroll_thumbrelease`](`m:wxScrollEvent`), -[`scroll_changed`](`m:wxScrollEvent`) +Event types emitted from this class: + +* [`scroll_top`](`m:wxScrollEvent`) + +* [`scroll_bottom`](`m:wxScrollEvent`) + +* [`scroll_lineup`](`m:wxScrollEvent`) + +* [`scroll_linedown`](`m:wxScrollEvent`) + +* [`scroll_pageup`](`m:wxScrollEvent`) + +* [`scroll_pagedown`](`m:wxScrollEvent`) + +* [`scroll_thumbtrack`](`m:wxScrollEvent`) + +* [`scroll_thumbrelease`](`m:wxScrollEvent`) + +* [`scroll_changed`](`m:wxScrollEvent`) + +* [`scroll_top`](`m:wxScrollEvent`) + +* [`scroll_bottom`](`m:wxScrollEvent`) + +* [`scroll_lineup`](`m:wxScrollEvent`) + +* [`scroll_linedown`](`m:wxScrollEvent`) + +* [`scroll_pageup`](`m:wxScrollEvent`) + +* [`scroll_pagedown`](`m:wxScrollEvent`) + +* [`scroll_thumbtrack`](`m:wxScrollEvent`) + +* [`scroll_thumbrelease`](`m:wxScrollEvent`) + +* [`scroll_changed`](`m:wxScrollEvent`) """. -include("wxe.hrl"). -export([create/3,create/4,destroy/1,getPageSize/1,getRange/1,getThumbPosition/1, @@ -136,21 +162,19 @@ Event types emitted from this class: [`scroll_top`](`m:wxScrollEvent`), -type wxScrollBar() :: wx:wx_object(). -export_type([wxScrollBar/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbarwxscrollbar">external documentation</a>. -doc "Default constructor.". -spec new() -> wxScrollBar(). new() -> wxe_util:queue_cmd(?get_env(), ?wxScrollBar_new_0), wxe_util:rec(?wxScrollBar_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxScrollBar() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -158,11 +182,10 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbarwxscrollbar">external documentation</a>. -doc """ Constructor, creating and showing a scrollbar. -See: `create/4`, `wxValidator` (not implemented in wx) +See: `create/4` """. -spec new(Parent, Id, [Option]) -> wxScrollBar() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -182,7 +205,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxScrollBar_new_3), wxe_util:rec(?wxScrollBar_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxScrollBar(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -190,7 +213,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbarcreate">external documentation</a>. -doc """ Scrollbar creation function called by the scrollbar constructor. @@ -215,7 +237,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxScrollBar_Create), wxe_util:rec(?wxScrollBar_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbargetrange">external documentation</a>. -doc """ Returns the length of the scrollbar. @@ -228,12 +249,11 @@ getRange(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollBar_GetRange), wxe_util:rec(?wxScrollBar_GetRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbargetpagesize">external documentation</a>. -doc """ Returns the page size of the scrollbar. -This is the number of scroll units that will be scrolled when the user pages up -or down. Often it is the same as the thumb size. +This is the number of scroll units that will be scrolled when the user pages up or down. +Often it is the same as the thumb size. See: `setScrollbar/6` """. @@ -244,7 +264,6 @@ getPageSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollBar_GetPageSize), wxe_util:rec(?wxScrollBar_GetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbargetthumbposition">external documentation</a>. -doc """ Returns the current position of the scrollbar thumb. @@ -257,7 +276,6 @@ getThumbPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollBar_GetThumbPosition), wxe_util:rec(?wxScrollBar_GetThumbPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbargetthumbsize">external documentation</a>. -doc """ Returns the thumb or 'view' size. @@ -270,7 +288,6 @@ getThumbSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollBar_GetThumbSize), wxe_util:rec(?wxScrollBar_GetThumbSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbarsetthumbposition">external documentation</a>. -doc """ Sets the position of the scrollbar. @@ -283,7 +300,7 @@ setThumbPosition(#wx_ref{type=ThisT}=This,ViewStart) ?CLASS(ThisT,wxScrollBar), wxe_util:queue_cmd(This,ViewStart,?get_env(),?wxScrollBar_SetThumbPosition). -%% @equiv setScrollbar(This,Position,ThumbSize,Range,PageSize, []) +-doc(#{equiv => setScrollbar(This,Position,ThumbSize,Range,PageSize, [])}). -spec setScrollbar(This, Position, ThumbSize, Range, PageSize) -> 'ok' when This::wxScrollBar(), Position::integer(), ThumbSize::integer(), Range::integer(), PageSize::integer(). @@ -291,22 +308,19 @@ setScrollbar(This,Position,ThumbSize,Range,PageSize) when is_record(This, wx_ref),is_integer(Position),is_integer(ThumbSize),is_integer(Range),is_integer(PageSize) -> setScrollbar(This,Position,ThumbSize,Range,PageSize, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollbar.html#wxscrollbarsetscrollbar">external documentation</a>. -doc """ Sets the scrollbar properties. -Remark: Let's say you wish to display 50 lines of text, using the same font. The -window is sized so that you can only see 16 lines at a time. You would use: The -page size is 1 less than the thumb size so that the last line of the previous -page will be visible on the next page, to help orient the user. Note that with -the window at this size, the thumb position can never go above 50 minus 16, -or 34. You can determine how many lines are currently visible by dividing the -current view size by the character height in pixels. When defining your own -scrollbar behaviour, you will always need to recalculate the scrollbar settings -when the window size changes. You could therefore put your scrollbar -calculations and `setScrollbar/6` call into a function named AdjustScrollbars, -which can be called initially and also from a `m:wxSizeEvent` event handler -function. +Remark: Let's say you wish to display 50 lines of text, using the same font. The window +is sized so that you can only see 16 lines at a time. You would use: The page size is 1 +less than the thumb size so that the last line of the previous page will be visible on the +next page, to help orient the user. Note that with the window at this size, the thumb +position can never go above 50 minus 16, or 34. You can determine how many lines are +currently visible by dividing the current view size by the character height in pixels. +When defining your own scrollbar behaviour, you will always need to recalculate the +scrollbar settings when the window size changes. You could therefore put your scrollbar +calculations and `setScrollbar/6` call into a function named AdjustScrollbars, which can be called +initially and also from a `m:wxSizeEvent` event handler function. """. -spec setScrollbar(This, Position, ThumbSize, Range, PageSize, [Option]) -> 'ok' when This::wxScrollBar(), Position::integer(), ThumbSize::integer(), Range::integer(), PageSize::integer(), @@ -319,556 +333,374 @@ setScrollbar(#wx_ref{type=ThisT}=This,Position,ThumbSize,Range,PageSize, Options Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Position,ThumbSize,Range,PageSize, Opts,?get_env(),?wxScrollBar_SetScrollbar). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the scrollbar.". +-doc "Destroys the object". -spec destroy(This::wxScrollBar()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxScrollBar), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxScrollEvent.erl b/lib/wx/src/gen/wxScrollEvent.erl index ef04d97aca96..2ad4ad0b8158 100644 --- a/lib/wx/src/gen/wxScrollEvent.erl +++ b/lib/wx/src/gen/wxScrollEvent.erl @@ -20,48 +20,53 @@ -module(wxScrollEvent). -moduledoc """ -Functions for wxScrollEvent class +A scroll event holds information about events sent from stand-alone scrollbars (see `m:wxScrollBar`) +and sliders (see `m:wxSlider`). -A scroll event holds information about events sent from stand-alone scrollbars -(see `m:wxScrollBar`) and sliders (see `m:wxSlider`). - -Note that scrolled windows send the `m:wxScrollWinEvent` which does not derive -from `m:wxCommandEvent`, but from `m:wxEvent` directly - don't confuse these two -kinds of events and use the event table macros mentioned below only for the -scrollbar-like controls. +Note that scrolled windows send the `m:wxScrollWinEvent` which does not derive from `m:wxCommandEvent`, +but from `m:wxEvent` directly - don't confuse these two kinds of events and use the event +table macros mentioned below only for the scrollbar-like controls. The difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED -The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the -thumb using the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is -also followed by an EVT_SCROLL_CHANGED event). +The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the thumb using +the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is also followed by an +EVT_SCROLL_CHANGED event). -The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the -thumb position, and when clicking next to the thumb (In all these cases the +The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the thumb +position, and when clicking next to the thumb (In all these cases the EVT_SCROLL_THUMBRELEASE event does not happen). -In short, the EVT_SCROLL_CHANGED event is triggered when scrolling/ moving has -finished independently of the way it had started. Please see the -page_samples_widgets ("Slider" page) to see the difference between -EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. +In short, the EVT_SCROLL_CHANGED event is triggered when scrolling/ moving has finished +independently of the way it had started. Please see the page_samples_widgets ("Slider" +page) to see the difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. + +Remark: Note that unless specifying a scroll control identifier, you will need to test +for scrollbar orientation with `getOrientation/1`, since horizontal and vertical scroll events are processed +using the same event handler. + +See: +* `m:wxScrollBar` + +* `m:wxSlider` -Remark: Note that unless specifying a scroll control identifier, you will need -to test for scrollbar orientation with `getOrientation/1`, since horizontal and -vertical scroll events are processed using the same event handler. +* `m:wxSpinButton` -See: `m:wxScrollBar`, `m:wxSlider`, `m:wxSpinButton`, `m:wxScrollWinEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* `m:wxScrollWinEvent` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -wxWidgets docs: -[wxScrollEvent](https://docs.wxwidgets.org/3.1/classwx_scroll_event.html) +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxScrollEvent](https://docs.wxwidgets.org/3.2/classwx_scroll_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxScrollEventType`](`t:wxScrollEventType/0`) -to subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxScrollEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getOrientation/1,getPosition/1]). @@ -76,17 +81,12 @@ to subscribe to events of this type. -include("wx.hrl"). -type wxScrollEventType() :: 'scroll_top' | 'scroll_bottom' | 'scroll_lineup' | 'scroll_linedown' | 'scroll_pageup' | 'scroll_pagedown' | 'scroll_thumbtrack' | 'scroll_thumbrelease' | 'scroll_changed'. -export_type([wxScrollEvent/0, wxScroll/0, wxScrollEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollevent.html#wxscrolleventgetorientation">external documentation</a>. --doc """ -Returns wxHORIZONTAL or wxVERTICAL, depending on the orientation of the -scrollbar. -""". +-doc "Returns wxHORIZONTAL or wxVERTICAL, depending on the orientation of the scrollbar.". -spec getOrientation(This) -> integer() when This::wxScrollEvent(). getOrientation(#wx_ref{type=ThisT}=This) -> @@ -94,7 +94,6 @@ getOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollEvent_GetOrientation), wxe_util:rec(?wxScrollEvent_GetOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollevent.html#wxscrolleventgetposition">external documentation</a>. -doc "Returns the position of the scrollbar.". -spec getPosition(This) -> integer() when This::wxScrollEvent(). @@ -104,58 +103,40 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxScrollEvent_GetPosition). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxScrollWinEvent.erl b/lib/wx/src/gen/wxScrollWinEvent.erl index 2c1898d63538..8d571756e2e8 100644 --- a/lib/wx/src/gen/wxScrollWinEvent.erl +++ b/lib/wx/src/gen/wxScrollWinEvent.erl @@ -20,26 +20,25 @@ -module(wxScrollWinEvent). -moduledoc """ -Functions for wxScrollWinEvent class - A scroll event holds information about events sent from scrolling windows. -Note that you can use the EVT_SCROLLWIN\* macros for intercepting scroll window -events from the receiving window. +Note that you can use the EVT_SCROLLWIN* macros for intercepting scroll window events +from the receiving window. + +See: +* `m:wxScrollEvent` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: `m:wxScrollEvent`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxScrollWinEvent](https://docs.wxwidgets.org/3.1/classwx_scroll_win_event.html) +wxWidgets docs: [wxScrollWinEvent](https://docs.wxwidgets.org/3.2/classwx_scroll_win_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxScrollWinEventType`](`t:wxScrollWinEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxScrollWinEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getOrientation/1,getPosition/1]). @@ -52,16 +51,11 @@ this type. -include("wx.hrl"). -type wxScrollWinEventType() :: 'scrollwin_top' | 'scrollwin_bottom' | 'scrollwin_lineup' | 'scrollwin_linedown' | 'scrollwin_pageup' | 'scrollwin_pagedown' | 'scrollwin_thumbtrack' | 'scrollwin_thumbrelease'. -export_type([wxScrollWinEvent/0, wxScrollWin/0, wxScrollWinEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollwinevent.html#wxscrollwineventgetorientation">external documentation</a>. --doc """ -Returns wxHORIZONTAL or wxVERTICAL, depending on the orientation of the -scrollbar. -""". +-doc "Returns wxHORIZONTAL or wxVERTICAL, depending on the orientation of the scrollbar.". -spec getOrientation(This) -> integer() when This::wxScrollWinEvent(). getOrientation(#wx_ref{type=ThisT}=This) -> @@ -69,12 +63,11 @@ getOrientation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrollWinEvent_GetOrientation), wxe_util:rec(?wxScrollWinEvent_GetOrientation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrollwinevent.html#wxscrollwineventgetposition">external documentation</a>. -doc """ Returns the position of the scrollbar for the thumb track and release events. -Note that this field can't be used for the other events, you need to query the -window itself for the current position in that case. +Note that this field can't be used for the other events, you need to query the window +itself for the current position in that case. """. -spec getPosition(This) -> integer() when This::wxScrollWinEvent(). @@ -84,30 +77,21 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxScrollWinEvent_GetPosition). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxScrolledWindow.erl b/lib/wx/src/gen/wxScrolledWindow.erl index 077b22f2697f..fc3b3f4e92a4 100644 --- a/lib/wx/src/gen/wxScrolledWindow.erl +++ b/lib/wx/src/gen/wxScrolledWindow.erl @@ -20,113 +20,128 @@ -module(wxScrolledWindow). -moduledoc """ -The wxScrolled (not implemented in wx) class manages scrolling for its client -area, transforming the coordinates according to the scrollbar positions, and -setting the scroll positions, thumb sizes and ranges according to the area in -view. +The `wxScrolled` (not implemented in wx) class manages scrolling for its client area, +transforming the coordinates according to the scrollbar positions, and setting the scroll +positions, thumb sizes and ranges according to the area in view. -There are two commonly used (but not the only possible\!) specializations of -this class: +There are two commonly used (but not the only possible!) specializations of this class: -Note: See `wxScrolled::Create()` (not implemented in wx) if you want to use -`wxScrolled` (not implemented in wx) with a custom class. +* ?wxScrolledWindow, aka wxScrolled<wxPanel>, is equivalent to ?wxScrolledWindow from +earlier versions. Derived from `m:wxPanel`, it shares `m:wxPanel`'s behaviour with regard +to TAB traversal and focus handling. Use this if the scrolled window will have child controls. + +* ?wxScrolledCanvas, aka wxScrolled<wxWindow>, derives from `m:wxWindow` and so doesn't +handle children specially. This is suitable e.g. for implementing scrollable controls such +as tree or list controls. + +Note: See `wxScrolled::Create()` (not implemented in wx) if you want to use `wxScrolled` +(not implemented in wx) with a custom class. Starting from version 2.4 of wxWidgets, there are several ways to use a -?wxScrolledWindow (and now `wxScrolled` (not implemented in wx)). In particular, -there are three ways to set the size of the scrolling area: - -One way is to set the scrollbars directly using a call to `setScrollbars/6`. -This is the way it used to be in any previous version of wxWidgets and it will -be kept for backwards compatibility. - -An additional method of manual control, which requires a little less computation -of your own, is to set the total size of the scrolling area by calling either -`wxWindow:setVirtualSize/3`, or `wxWindow:fitInside/1`, and setting the -scrolling increments for it by calling `setScrollRate/3`. Scrolling in some -orientation is enabled by setting a non-zero increment for it. - -The most automatic and newest way is to simply let sizers determine the -scrolling area. This is now the default when you set an interior sizer into a -`wxScrolled` (not implemented in wx) with `wxWindow:setSizer/3`. The scrolling -area will be set to the size requested by the sizer and the scrollbars will be -assigned for each orientation according to the need for them and the scrolling -increment set by `setScrollRate/3`. As above, scrolling is only enabled in -orientations with a non-zero increment. You can influence the minimum size of -the scrolled area controlled by a sizer by calling -wxWindow::SetVirtualSizeHints(). (Calling `setScrollbars/6` has analogous -effects in wxWidgets 2.4 - in later versions it may not continue to override the -sizer.) - -Note that if maximum size hints are still supported by -wxWindow::SetVirtualSizeHints(), use them at your own dire risk. They may or may -not have been removed for 2.4, but it really only makes sense to set minimum -size hints here. We should probably replace wxWindow::SetVirtualSizeHints() with -wxWindow::SetMinVirtualSize() or similar and remove it entirely in future. - -As with all windows, an application can draw onto a `wxScrolled` (not -implemented in wx) using a device context. - -You have the option of handling the OnPaint handler or overriding the -`wxScrolled::OnDraw()` (not implemented in wx) function, which is passed a -pre-scrolled device context (prepared by `doPrepareDC/2`). - -If you don't wish to calculate your own scrolling, you must call `doPrepareDC/2` -when not drawing from within `OnDraw()` (not implemented in wx), to set the -device origin for the device context according to the current scroll position. - -A `wxScrolled` (not implemented in wx) will normally scroll itself and therefore -its child windows as well. It might however be desired to scroll a different -window than itself: e.g. when designing a spreadsheet, you will normally only -have to scroll the (usually white) cell area, whereas the (usually grey) label -area will scroll very differently. For this special purpose, you can call -`setTargetWindow/2` which means that pressing the scrollbars will scroll a -different window. - -Note that the underlying system knows nothing about scrolling coordinates, so -that all system functions (mouse events, expose events, refresh calls etc) as -well as the position of subwindows are relative to the "physical" origin of the -scrolled window. If the user insert a child window at position (10,10) and -scrolls the window down 100 pixels (moving the child window out of the visible -area), the child window will report a position of (10,-90). - -Styles +?wxScrolledWindow (and now `wxScrolled` (not implemented in wx)). In particular, there are +three ways to set the size of the scrolling area: + +One way is to set the scrollbars directly using a call to `setScrollbars/6`. This is the way it used to be +in any previous version of wxWidgets and it will be kept for backwards compatibility. + +An additional method of manual control, which requires a little less computation of your +own, is to set the total size of the scrolling area by calling either `wxWindow:setVirtualSize/3`, or `wxWindow:fitInside/1`, and setting +the scrolling increments for it by calling `setScrollRate/3`. Scrolling in some orientation is enabled by +setting a non-zero increment for it. + +The most automatic and newest way is to simply let sizers determine the scrolling area. +This is now the default when you set an interior sizer into a `wxScrolled` (not +implemented in wx) with `wxWindow:setSizer/3`. The scrolling area will be set to the size requested by the +sizer and the scrollbars will be assigned for each orientation according to the need for +them and the scrolling increment set by `setScrollRate/3`. As above, scrolling is only enabled in +orientations with a non-zero increment. You can influence the minimum size of the scrolled +area controlled by a sizer by calling wxWindow::SetVirtualSizeHints(). (Calling `setScrollbars/6` has +analogous effects in wxWidgets 2.4 - in later versions it may not continue to override the sizer.) + +Note that if maximum size hints are still supported by wxWindow::SetVirtualSizeHints(), +use them at your own dire risk. They may or may not have been removed for 2.4, but it +really only makes sense to set minimum size hints here. We should probably replace +wxWindow::SetVirtualSizeHints() with wxWindow::SetMinVirtualSize() or similar and remove +it entirely in future. + +As with all windows, an application can draw onto a `wxScrolled` (not implemented in wx) +using a device context. + +You have the option of handling the OnPaint handler or overriding the `wxScrolled::OnDraw()` +(not implemented in wx) function, which is passed a pre-scrolled device context (prepared +by `doPrepareDC/2`). + +If you don't wish to calculate your own scrolling, you must call `doPrepareDC/2` when not drawing from +within `OnDraw()` (not implemented in wx), to set the device origin for the device context +according to the current scroll position. + +A `wxScrolled` (not implemented in wx) will normally scroll itself and therefore its +child windows as well. It might however be desired to scroll a different window than +itself: e.g. when designing a spreadsheet, you will normally only have to scroll the +(usually white) cell area, whereas the (usually grey) label area will scroll very +differently. For this special purpose, you can call `setTargetWindow/2` which means that pressing the +scrollbars will scroll a different window. + +Note that the underlying system knows nothing about scrolling coordinates, so that all +system functions (mouse events, expose events, refresh calls etc) as well as the position +of subwindows are relative to the "physical" origin of the scrolled window. If the user +insert a child window at position (10,10) and scrolls the window down 100 pixels (moving +the child window out of the visible area), the child window will report a position of (10,-90). + +## Styles This class supports the following styles: -Note: Don't confuse wxScrollWinEvents generated by this class with -`m:wxScrollEvent` objects generated by `m:wxScrollBar` and `m:wxSlider`. +* wxHSCROLL: If this style is specified and ?wxVSCROLL isn't, the window will be scrollable +only in horizontal direction (by default, i.e. if neither this style nor ?wxVSCROLL is +specified, it scrolls in both directions). + +* wxVSCROLL: If this style is specified and ?wxHSCROLL isn't, the window will be scrollable +only in vertical direction (by default, i.e. if neither this style nor ?wxHSCROLL is +specified, it scrolls in both directions). + +* wxALWAYS_SHOW_SB: Since wxWidgets 2.9.5, specifying this style makes the window always +show its scrollbars, even if they are not used. See `ShowScrollbars()` (not implemented in +wx). + +* wxRETAINED: Uses a backing pixmap to speed refreshes. Motif only. -Remark: Use `wxScrolled` (not implemented in wx) for applications where the user -scrolls by a fixed amount, and where a 'page' can be interpreted to be the -current visible portion of the window. For more sophisticated applications, use -the `wxScrolled` (not implemented in wx) implementation as a guide to build your -own scroll behaviour or use `wxVScrolledWindow` (not implemented in wx) or its -variants. +See: +* `m:wxScrollBar` -Since: The `wxScrolled` (not implemented in wx) template exists since version -2.9.0. In older versions, only ?wxScrolledWindow (equivalent of -wxScrolled<wxPanel>) was available. +* `m:wxClientDC` -See: `m:wxScrollBar`, `m:wxClientDC`, `m:wxPaintDC`, `wxVScrolledWindow` (not -implemented in wx), `wxHScrolledWindow` (not implemented in wx), -`wxHVScrolledWindow` (not implemented in wx) +* `m:wxPaintDC` -This class is derived (and can use functions) from: `m:wxPanel` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxScrolledWindow](https://docs.wxwidgets.org/3.1/classwx_scrolled_window.html) +* `m:wxPanel` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxScrolledWindow](https://docs.wxwidgets.org/3.2/classwx_scrolled_window.html) ## Events -Event types emitted from this class: [`scrollwin_top`](`m:wxScrollWinEvent`), -[`scrollwin_bottom`](`m:wxScrollWinEvent`), -[`scrollwin_lineup`](`m:wxScrollWinEvent`), -[`scrollwin_linedown`](`m:wxScrollWinEvent`), -[`scrollwin_pageup`](`m:wxScrollWinEvent`), -[`scrollwin_pagedown`](`m:wxScrollWinEvent`), -[`scrollwin_thumbtrack`](`m:wxScrollWinEvent`), -[`scrollwin_thumbrelease`](`m:wxScrollWinEvent`) +Event types emitted from this class: + +* [`scrollwin_top`](`m:wxScrollWinEvent`) + +* [`scrollwin_bottom`](`m:wxScrollWinEvent`) + +* [`scrollwin_lineup`](`m:wxScrollWinEvent`) + +* [`scrollwin_linedown`](`m:wxScrollWinEvent`) + +* [`scrollwin_pageup`](`m:wxScrollWinEvent`) + +* [`scrollwin_pagedown`](`m:wxScrollWinEvent`) + +* [`scrollwin_thumbtrack`](`m:wxScrollWinEvent`) + +* [`scrollwin_thumbrelease`](`m:wxScrollWinEvent`) """. -include("wxe.hrl"). -export([calcScrolledPosition/2,calcScrolledPosition/3,calcUnscrolledPosition/2, @@ -177,21 +192,19 @@ Event types emitted from this class: [`scrollwin_top`](`m:wxScrollWinEvent`), -type wxScrolledWindow() :: wx:wx_object(). -export_type([wxScrolledWindow/0]). -%% @hidden -doc false. parent_class(wxPanel) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowwxscrolledwindow">external documentation</a>. -doc "Default constructor.". -spec new() -> wxScrolledWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxScrolledWindow_new_0), wxe_util:rec(?wxScrolledWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxScrolledWindow() when Parent::wxWindow:wxWindow(). @@ -199,12 +212,11 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowwxscrolledwindow">external documentation</a>. -doc """ Constructor. -Remark: The window is initially created without visible scrollbars. Call -`setScrollbars/6` to specify how big the virtual window size should be. +Remark: The window is initially created without visible scrollbars. Call `setScrollbars/6` to specify how +big the virtual window size should be. """. -spec new(Parent, [Option]) -> wxScrolledWindow() when Parent::wxWindow:wxWindow(), @@ -224,7 +236,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxScrolledWindow_new_2), wxe_util:rec(?wxScrolledWindow_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowcalcscrolledposition">external documentation</a>. +-doc "". -spec calcScrolledPosition(This, Pt) -> {X::integer(), Y::integer()} when This::wxScrolledWindow(), Pt::{X::integer(), Y::integer()}. calcScrolledPosition(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) @@ -233,14 +245,12 @@ calcScrolledPosition(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxScrolledWindow_CalcScrolledPosition_1), wxe_util:rec(?wxScrolledWindow_CalcScrolledPosition_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowcalcscrolledposition">external documentation</a>. -doc """ Translates the logical coordinates to the device ones. -For example, if a window is scrolled 10 pixels to the bottom, the device -coordinates of the origin are (0, 0) (as always), but the logical coordinates -are (0, 10) and so the call to CalcScrolledPosition(0, 10, xx, yy) will return 0 -in yy. +For example, if a window is scrolled 10 pixels to the bottom, the device coordinates of +the origin are (0, 0) (as always), but the logical coordinates are (0, 10) and so the call +to CalcScrolledPosition(0, 10, xx, yy) will return 0 in yy. See: `calcUnscrolledPosition/3` """. @@ -252,7 +262,7 @@ calcScrolledPosition(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxScrolledWindow_CalcScrolledPosition_4), wxe_util:rec(?wxScrolledWindow_CalcScrolledPosition_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowcalcunscrolledposition">external documentation</a>. +-doc "". -spec calcUnscrolledPosition(This, Pt) -> {X::integer(), Y::integer()} when This::wxScrolledWindow(), Pt::{X::integer(), Y::integer()}. calcUnscrolledPosition(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) @@ -261,14 +271,12 @@ calcUnscrolledPosition(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxScrolledWindow_CalcUnscrolledPosition_1), wxe_util:rec(?wxScrolledWindow_CalcUnscrolledPosition_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowcalcunscrolledposition">external documentation</a>. -doc """ Translates the device coordinates to the logical ones. -For example, if a window is scrolled 10 pixels to the bottom, the device -coordinates of the origin are (0, 0) (as always), but the logical coordinates -are (0, 10) and so the call to CalcUnscrolledPosition(0, 0, xx, yy) will return -10 in yy. +For example, if a window is scrolled 10 pixels to the bottom, the device coordinates of +the origin are (0, 0) (as always), but the logical coordinates are (0, 10) and so the call +to CalcUnscrolledPosition(0, 0, xx, yy) will return 10 in yy. See: `calcScrolledPosition/3` """. @@ -280,19 +288,16 @@ calcUnscrolledPosition(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxScrolledWindow_CalcUnscrolledPosition_4), wxe_util:rec(?wxScrolledWindow_CalcUnscrolledPosition_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowenablescrolling">external documentation</a>. -doc """ Enable or disable use of `wxWindow:scrollWindow/4` for scrolling. -By default, when a scrolled window is logically scrolled, -`wxWindow:scrollWindow/4` is called on the underlying window which scrolls the -window contents and only invalidates the part of the window newly brought into -view. If false is passed as an argument, then this "physical scrolling" is -disabled and the window is entirely invalidated whenever it is scrolled by -calling `wxWindow:refresh/2`. +By default, when a scrolled window is logically scrolled, `wxWindow:scrollWindow/4` is called on the underlying +window which scrolls the window contents and only invalidates the part of the window newly +brought into view. If false is passed as an argument, then this "physical scrolling" is +disabled and the window is entirely invalidated whenever it is scrolled by calling `wxWindow:refresh/2`. -It should be rarely necessary to disable physical scrolling, so this method -shouldn't be called in normal circumstances. +It should be rarely necessary to disable physical scrolling, so this method shouldn't be +called in normal circumstances. """. -spec enableScrolling(This, XScrolling, YScrolling) -> 'ok' when This::wxScrolledWindow(), XScrolling::boolean(), YScrolling::boolean(). @@ -301,14 +306,15 @@ enableScrolling(#wx_ref{type=ThisT}=This,XScrolling,YScrolling) ?CLASS(ThisT,wxScrolledWindow), wxe_util:queue_cmd(This,XScrolling,YScrolling,?get_env(),?wxScrolledWindow_EnableScrolling). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowgetscrollpixelsperunit">external documentation</a>. -doc """ -Get the number of pixels per scroll unit (line), in each direction, as set by -`setScrollbars/6`. +Get the number of pixels per scroll unit (line), in each direction, as set by `setScrollbars/6`. A value of zero indicates no scrolling in that direction. -See: `setScrollbars/6`, `wxWindow:getVirtualSize/1` +See: +* `setScrollbars/6` + +* `wxWindow:getVirtualSize/1` """. -spec getScrollPixelsPerUnit(This) -> {XUnit::integer(), YUnit::integer()} when This::wxScrolledWindow(). @@ -317,11 +323,7 @@ getScrollPixelsPerUnit(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrolledWindow_GetScrollPixelsPerUnit), wxe_util:rec(?wxScrolledWindow_GetScrollPixelsPerUnit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowgetviewstart">external documentation</a>. --doc """ -This is a simple overload of GetViewStart(int*,int*); see that function for more -info. -""". +-doc "This is a simple overload of GetViewStart(int\*,int\*); see that function for more info.". -spec getViewStart(This) -> {X::integer(), Y::integer()} when This::wxScrolledWindow(). getViewStart(#wx_ref{type=ThisT}=This) -> @@ -329,25 +331,21 @@ getViewStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxScrolledWindow_GetViewStart), wxe_util:rec(?wxScrolledWindow_GetViewStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowdopreparedc">external documentation</a>. -doc """ Call this function to prepare the device context for drawing a scrolled image. -It sets the device origin according to the current scroll position. -`doPrepareDC/2` is called automatically within the default `wxEVT_PAINT` event -handler, so your `OnDraw()` (not implemented in wx) override will be passed an -already 'pre-scrolled' device context. However, if you wish to draw from outside -of `OnDraw()` (not implemented in wx) (e.g. from your own `wxEVT_PAINT` -handler), you must call this function yourself. +It sets the device origin according to the current scroll position. `doPrepareDC/2` is called +automatically within the default `wxEVT_PAINT` event handler, so your `OnDraw()` (not +implemented in wx) override will be passed an already 'pre-scrolled' device context. +However, if you wish to draw from outside of `OnDraw()` (not implemented in wx) (e.g. from +your own `wxEVT_PAINT` handler), you must call this function yourself. For example: -Notice that the function sets the origin by moving it relatively to the current -origin position, so you shouldn't change the origin before calling -`doPrepareDC/2` or, if you do, reset it to (0, 0) later. If you call -`doPrepareDC/2` immediately after device context creation, as in the example -above, this problem doesn't arise, of course, so it is customary to do it like -this. +Notice that the function sets the origin by moving it relatively to the current origin +position, so you shouldn't change the origin before calling `doPrepareDC/2` or, if you do, reset it to +(0, 0) later. If you call `doPrepareDC/2` immediately after device context creation, as in the example +above, this problem doesn't arise, of course, so it is customary to do it like this. """. -spec doPrepareDC(This, Dc) -> 'ok' when This::wxScrolledWindow(), Dc::wxDC:wxDC(). @@ -356,13 +354,11 @@ doPrepareDC(#wx_ref{type=ThisT}=This,#wx_ref{type=DcT}=Dc) -> ?CLASS(DcT,wxDC), wxe_util:queue_cmd(This,Dc,?get_env(),?wxScrolledWindow_DoPrepareDC). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowpreparedc">external documentation</a>. -doc """ -This function is for backwards compatibility only and simply calls -`doPrepareDC/2` now. +This function is for backwards compatibility only and simply calls `doPrepareDC/2` now. -Notice that it is not called by the default paint event handle (`doPrepareDC/2` -is), so overriding this method in your derived class is useless. +Notice that it is not called by the default paint event handle (`doPrepareDC/2` is), so overriding this +method in your derived class is useless. """. -spec prepareDC(This, Dc) -> 'ok' when This::wxScrolledWindow(), Dc::wxDC:wxDC(). @@ -371,8 +367,7 @@ prepareDC(#wx_ref{type=ThisT}=This,#wx_ref{type=DcT}=Dc) -> ?CLASS(DcT,wxDC), wxe_util:queue_cmd(This,Dc,?get_env(),?wxScrolledWindow_PrepareDC). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowscroll">external documentation</a>. --doc "This is an overload of `scroll/3`; see that function for more info.". +-doc "This is an overload of `scroll/3`;see that function for more info.". -spec scroll(This, Pt) -> 'ok' when This::wxScrolledWindow(), Pt::{X::integer(), Y::integer()}. scroll(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) @@ -380,16 +375,17 @@ scroll(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) ?CLASS(ThisT,wxScrolledWindow), wxe_util:queue_cmd(This,Pt,?get_env(),?wxScrolledWindow_Scroll_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowscroll">external documentation</a>. -doc """ Scrolls a window so the view start is at the given point. -Remark: The positions are in scroll units, not pixels, so to convert to pixels -you will have to multiply by the number of pixels per scroll increment. If -either parameter is ?wxDefaultCoord (-1), that position will be ignored (no -change in that direction). +Remark: The positions are in scroll units, not pixels, so to convert to pixels you will +have to multiply by the number of pixels per scroll increment. If either parameter is +?wxDefaultCoord (-1), that position will be ignored (no change in that direction). + +See: +* `setScrollbars/6` -See: `setScrollbars/6`, `getScrollPixelsPerUnit/1` +* `getScrollPixelsPerUnit/1` """. -spec scroll(This, X, Y) -> 'ok' when This::wxScrolledWindow(), X::integer(), Y::integer(). @@ -398,7 +394,7 @@ scroll(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxScrolledWindow), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxScrolledWindow_Scroll_2). -%% @equiv setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, []) +-doc(#{equiv => setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, [])}). -spec setScrollbars(This, PixelsPerUnitX, PixelsPerUnitY, NoUnitsX, NoUnitsY) -> 'ok' when This::wxScrolledWindow(), PixelsPerUnitX::integer(), PixelsPerUnitY::integer(), NoUnitsX::integer(), NoUnitsY::integer(). @@ -406,28 +402,24 @@ setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY) when is_record(This, wx_ref),is_integer(PixelsPerUnitX),is_integer(PixelsPerUnitY),is_integer(NoUnitsX),is_integer(NoUnitsY) -> setScrollbars(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowsetscrollbars">external documentation</a>. -doc """ Sets up vertical and/or horizontal scrollbars. -The first pair of parameters give the number of pixels per 'scroll step', i.e. -amount moved when the up or down scroll arrows are pressed. The second pair -gives the length of scrollbar in scroll steps, which sets the size of the -virtual window. +The first pair of parameters give the number of pixels per 'scroll step', i.e. amount +moved when the up or down scroll arrows are pressed. The second pair gives the length of +scrollbar in scroll steps, which sets the size of the virtual window. `xPos` and `yPos` optionally specify a position to scroll to immediately. -For example, the following gives a window horizontal and vertical scrollbars -with 20 pixels per scroll step, and a size of 50 steps (1000 pixels) in each -direction: +For example, the following gives a window horizontal and vertical scrollbars with 20 +pixels per scroll step, and a size of 50 steps (1000 pixels) in each direction: -`wxScrolled` (not implemented in wx) manages the page size itself, using the -current client window size as the page size. +`wxScrolled` (not implemented in wx) manages the page size itself, using the current +client window size as the page size. -Note that for more sophisticated scrolling applications, for example where -scroll steps may be variable according to the position in the document, it will -be necessary to derive a new class from `m:wxWindow`, overriding OnSize() and -adjusting the scrollbars appropriately. +Note that for more sophisticated scrolling applications, for example where scroll steps +may be variable according to the position in the document, it will be necessary to derive +a new class from `m:wxWindow`, overriding OnSize() and adjusting the scrollbars appropriately. See: `wxWindow:setVirtualSize/3` """. @@ -446,7 +438,6 @@ setScrollbars(#wx_ref{type=ThisT}=This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,No Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,PixelsPerUnitX,PixelsPerUnitY,NoUnitsX,NoUnitsY, Opts,?get_env(),?wxScrolledWindow_SetScrollbars). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowsetscrollrate">external documentation</a>. -doc """ Set the horizontal and vertical scrolling increment only. @@ -459,21 +450,19 @@ setScrollRate(#wx_ref{type=ThisT}=This,Xstep,Ystep) ?CLASS(ThisT,wxScrolledWindow), wxe_util:queue_cmd(This,Xstep,Ystep,?get_env(),?wxScrolledWindow_SetScrollRate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxscrolledwindow.html#wxscrolledwindowsettargetwindow">external documentation</a>. -doc """ -Call this function to tell `wxScrolled` (not implemented in wx) to perform the -actual scrolling on a different window (and not on itself). - -This method is useful when only a part of the window should be scrolled. A -typical example is a control consisting of a fixed header and the scrollable -contents window: the scrollbars are attached to the main window itself, hence -it, and not the contents window must be derived from `wxScrolled` (not -implemented in wx), but only the contents window scrolls when the scrollbars are -used. To implement such setup, you need to call this method with the contents -window as argument. - -Notice that if this method is used, `GetSizeAvailableForScrollTarget()` (not -implemented in wx) method must be overridden. +Call this function to tell `wxScrolled` (not implemented in wx) to perform the actual +scrolling on a different window (and not on itself). + +This method is useful when only a part of the window should be scrolled. A typical +example is a control consisting of a fixed header and the scrollable contents window: the +scrollbars are attached to the main window itself, hence it, and not the contents window +must be derived from `wxScrolled` (not implemented in wx), but only the contents window +scrolls when the scrollbars are used. To implement such setup, you need to call this +method with the contents window as argument. + +Notice that if this method is used, `GetSizeAvailableForScrollTarget()` (not implemented +in wx) method must be overridden. """. -spec setTargetWindow(This, Window) -> 'ok' when This::wxScrolledWindow(), Window::wxWindow:wxWindow(). @@ -482,565 +471,380 @@ setTargetWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxWindow), wxe_util:queue_cmd(This,Window,?get_env(),?wxScrolledWindow_SetTargetWindow). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxScrolledWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxScrolledWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxPanel -%% @hidden -doc false. setFocusIgnoringChildren(This) -> wxPanel:setFocusIgnoringChildren(This). -%% @hidden -doc false. initDialog(This) -> wxPanel:initDialog(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSetCursorEvent.erl b/lib/wx/src/gen/wxSetCursorEvent.erl index 6132564e0f2f..0ff98bef8b93 100644 --- a/lib/wx/src/gen/wxSetCursorEvent.erl +++ b/lib/wx/src/gen/wxSetCursorEvent.erl @@ -20,27 +20,27 @@ -module(wxSetCursorEvent). -moduledoc """ -Functions for wxSetCursorEvent class +A `m:wxSetCursorEvent` is generated from `m:wxWindow` when the mouse cursor is about to +be set as a result of mouse motion. -A `m:wxSetCursorEvent` is generated from `m:wxWindow` when the mouse cursor is -about to be set as a result of mouse motion. +This event gives the application the chance to perform specific mouse cursor processing +based on the current position of the mouse within the window. Use `setCursor/2` to specify the cursor +you want to be displayed. -This event gives the application the chance to perform specific mouse cursor -processing based on the current position of the mouse within the window. Use -`setCursor/2` to specify the cursor you want to be displayed. +See: +* `wx_misc:setCursor/1` -See: `wx_misc:setCursor/1`, `wxWindow:setCursor/2` +* `wxWindow:setCursor/2` -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxSetCursorEvent](https://docs.wxwidgets.org/3.1/classwx_set_cursor_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxSetCursorEvent](https://docs.wxwidgets.org/3.2/classwx_set_cursor_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxSetCursorEventType`](`t:wxSetCursorEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxSetCursorEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getCursor/1,getX/1,getY/1,hasCursor/1,setCursor/2]). @@ -53,12 +53,10 @@ this type. -include("wx.hrl"). -type wxSetCursorEventType() :: 'set_cursor'. -export_type([wxSetCursorEvent/0, wxSetCursor/0, wxSetCursorEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsetcursorevent.html#wxsetcursoreventgetcursor">external documentation</a>. -doc "Returns a reference to the cursor specified by this event.". -spec getCursor(This) -> wxCursor:wxCursor() when This::wxSetCursorEvent(). @@ -67,7 +65,6 @@ getCursor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSetCursorEvent_GetCursor), wxe_util:rec(?wxSetCursorEvent_GetCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsetcursorevent.html#wxsetcursoreventgetx">external documentation</a>. -doc "Returns the X coordinate of the mouse in client coordinates.". -spec getX(This) -> integer() when This::wxSetCursorEvent(). @@ -76,7 +73,6 @@ getX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSetCursorEvent_GetX), wxe_util:rec(?wxSetCursorEvent_GetX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsetcursorevent.html#wxsetcursoreventgety">external documentation</a>. -doc "Returns the Y coordinate of the mouse in client coordinates.". -spec getY(This) -> integer() when This::wxSetCursorEvent(). @@ -85,12 +81,11 @@ getY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSetCursorEvent_GetY), wxe_util:rec(?wxSetCursorEvent_GetY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsetcursorevent.html#wxsetcursoreventhascursor">external documentation</a>. -doc """ Returns true if the cursor specified by this event is a valid cursor. -Remark: You cannot specify wxNullCursor with this event, as it is not considered -a valid cursor. +Remark: You cannot specify wxNullCursor with this event, as it is not considered a valid +cursor. """. -spec hasCursor(This) -> boolean() when This::wxSetCursorEvent(). @@ -99,7 +94,6 @@ hasCursor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSetCursorEvent_HasCursor), wxe_util:rec(?wxSetCursorEvent_HasCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsetcursorevent.html#wxsetcursoreventsetcursor">external documentation</a>. -doc "Sets the cursor associated with this event.". -spec setCursor(This, Cursor) -> 'ok' when This::wxSetCursorEvent(), Cursor::wxCursor:wxCursor(). @@ -109,30 +103,21 @@ setCursor(#wx_ref{type=ThisT}=This,#wx_ref{type=CursorT}=Cursor) -> wxe_util:queue_cmd(This,Cursor,?get_env(),?wxSetCursorEvent_SetCursor). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxShowEvent.erl b/lib/wx/src/gen/wxShowEvent.erl index 499c7cb2212d..257422f702fe 100644 --- a/lib/wx/src/gen/wxShowEvent.erl +++ b/lib/wx/src/gen/wxShowEvent.erl @@ -20,27 +20,29 @@ -module(wxShowEvent). -moduledoc """ -Functions for wxShowEvent class +An event being sent when the window is shown or hidden. -An event being sent when the window is shown or hidden. The event is triggered -by calls to `wxWindow:show/2`, and any user action showing a previously hidden -window or vice versa (if allowed by the current platform and/or window manager). -Notice that the event is not triggered when the application is iconized -(minimized) or restored under wxMSW. +The event is triggered by calls to `wxWindow:show/2`, and any user action showing a previously hidden +window or vice versa (if allowed by the current platform and/or window manager). Notice +that the event is not triggered when the application is iconized (minimized) or restored +under wxMSW. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`wxWindow:show/2`, `wxWindow:isShown/1` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvent` +* `wxWindow:show/2` -wxWidgets docs: -[wxShowEvent](https://docs.wxwidgets.org/3.1/classwx_show_event.html) +* `wxWindow:isShown/1` + +This class is derived, and can use functions, from: + +* `m:wxEvent` + +wxWidgets docs: [wxShowEvent](https://docs.wxwidgets.org/3.2/classwx_show_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxShowEventType`](`t:wxShowEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxShowEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([isShown/1,setShow/2]). @@ -53,12 +55,10 @@ subscribe to events of this type. -include("wx.hrl"). -type wxShowEventType() :: 'show'. -export_type([wxShowEvent/0, wxShow/0, wxShowEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxshowevent.html#wxshoweventsetshow">external documentation</a>. -doc "Set whether the windows was shown or hidden.". -spec setShow(This, Show) -> 'ok' when This::wxShowEvent(), Show::boolean(). @@ -67,7 +67,6 @@ setShow(#wx_ref{type=ThisT}=This,Show) ?CLASS(ThisT,wxShowEvent), wxe_util:queue_cmd(This,Show,?get_env(),?wxShowEvent_SetShow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxshowevent.html#wxshoweventisshown">external documentation</a>. -doc "Return true if the window has been shown, false if it has been hidden.". -spec isShown(This) -> boolean() when This::wxShowEvent(). @@ -77,30 +76,21 @@ isShown(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxShowEvent_IsShown). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSingleChoiceDialog.erl b/lib/wx/src/gen/wxSingleChoiceDialog.erl index 7b047d9f4e62..b85472fa73f1 100644 --- a/lib/wx/src/gen/wxSingleChoiceDialog.erl +++ b/lib/wx/src/gen/wxSingleChoiceDialog.erl @@ -20,25 +20,37 @@ -module(wxSingleChoiceDialog). -moduledoc """ -Functions for wxSingleChoiceDialog class +This class represents a dialog that shows a list of strings, and allows the user to +select one. -This class represents a dialog that shows a list of strings, and allows the user -to select one. Double-clicking on a list item is equivalent to single-clicking -and then pressing OK. +Double-clicking on a list item is equivalent to single-clicking and then pressing OK. -Styles +## Styles This class supports the following styles: +* wxOK: Show an OK button. + +* wxCANCEL: Show a Cancel button. + +* wxCENTRE: Centre the message. + See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_singlechoice), -`m:wxMultiChoiceDialog` +* [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_singlechoice) + +* `m:wxMultiChoiceDialog` + +This class is derived, and can use functions, from: + +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxSingleChoiceDialog](https://docs.wxwidgets.org/3.1/classwx_single_choice_dialog.html) +wxWidgets docs: [wxSingleChoiceDialog](https://docs.wxwidgets.org/3.2/classwx_single_choice_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getSelection/1,getStringSelection/1,new/4,new/5,setSelection/2]). @@ -90,7 +102,6 @@ wxWidgets docs: -type wxSingleChoiceDialog() :: wx:wx_object(). -export_type([wxSingleChoiceDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -98,7 +109,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Message,Caption,Choices, []) +-doc(#{equiv => new(Parent,Message,Caption,Choices, [])}). -spec new(Parent, Message, Caption, Choices) -> wxSingleChoiceDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(), Caption::unicode:chardata(), Choices::[unicode:chardata()]. @@ -106,10 +117,9 @@ new(Parent,Message,Caption,Choices) when is_record(Parent, wx_ref),?is_chardata(Message),?is_chardata(Caption),is_list(Choices) -> new(Parent,Message,Caption,Choices, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsinglechoicedialog.html#wxsinglechoicedialogwxsinglechoicedialog">external documentation</a>. -doc """ -Constructor, taking an array of `wxString` (not implemented in wx) choices and -optional client data. +Constructor, taking an array of `wxString` (not implemented in wx) choices and optional +client data. Remark: Use `wxDialog:showModal/1` to show the dialog. """. @@ -131,7 +141,6 @@ new(#wx_ref{type=ParentT}=Parent,Message,Caption,Choices, Options) wxe_util:queue_cmd(Parent,Message_UC,Caption_UC,Choices_UCA, Opts,?get_env(),?wxSingleChoiceDialog_new), wxe_util:rec(?wxSingleChoiceDialog_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsinglechoicedialog.html#wxsinglechoicedialoggetselection">external documentation</a>. -doc "Returns the index of selected item.". -spec getSelection(This) -> integer() when This::wxSingleChoiceDialog(). @@ -140,7 +149,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSingleChoiceDialog_GetSelection), wxe_util:rec(?wxSingleChoiceDialog_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsinglechoicedialog.html#wxsinglechoicedialoggetstringselection">external documentation</a>. -doc "Returns the selected string.". -spec getStringSelection(This) -> unicode:charlist() when This::wxSingleChoiceDialog(). @@ -149,7 +157,6 @@ getStringSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSingleChoiceDialog_GetStringSelection), wxe_util:rec(?wxSingleChoiceDialog_GetStringSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsinglechoicedialog.html#wxsinglechoicedialogsetselection">external documentation</a>. -doc "Sets the index of the initially selected item.". -spec setSelection(This, Selection) -> 'ok' when This::wxSingleChoiceDialog(), Selection::integer(). @@ -158,659 +165,443 @@ setSelection(#wx_ref{type=ThisT}=This,Selection) ?CLASS(ThisT,wxSingleChoiceDialog), wxe_util:queue_cmd(This,Selection,?get_env(),?wxSingleChoiceDialog_SetSelection). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxSingleChoiceDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSingleChoiceDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSizeEvent.erl b/lib/wx/src/gen/wxSizeEvent.erl index 1c779aeac4c4..0db3a06c1551 100644 --- a/lib/wx/src/gen/wxSizeEvent.erl +++ b/lib/wx/src/gen/wxSizeEvent.erl @@ -20,41 +20,38 @@ -module(wxSizeEvent). -moduledoc """ -Functions for wxSizeEvent class - A size event holds information about size change events of `m:wxWindow`. The EVT_SIZE handler function will be called when the window has been resized. -You may wish to use this for frames to resize their child windows as -appropriate. +You may wish to use this for frames to resize their child windows as appropriate. + +Note that the size passed is of the whole window: call `wxWindow:getClientSize/1` for the area which may be used by +the application. + +When a window is resized, usually only a small part of the window is damaged and you may +only need to repaint that area. However, if your drawing depends on the size of the +window, you may need to clear the DC explicitly and repaint the whole window. In which +case, you may need to call `wxWindow:refresh/2` to invalidate the entire window. -Note that the size passed is of the whole window: call -`wxWindow:getClientSize/1` for the area which may be used by the application. +`Important` : Sizers (see overview_sizer ) rely on size events to function correctly. +Therefore, in a sizer-based layout, do not forget to call Skip on all size events you +catch (and don't catch size events at all when you don't need to). -When a window is resized, usually only a small part of the window is damaged and -you may only need to repaint that area. However, if your drawing depends on the -size of the window, you may need to clear the DC explicitly and repaint the -whole window. In which case, you may need to call `wxWindow:refresh/2` to -invalidate the entire window. +See: +* {Width,Height} -`Important` : Sizers ( see overview_sizer ) rely on size events to function -correctly. Therefore, in a sizer-based layout, do not forget to call Skip on all -size events you catch (and don't catch size events at all when you don't need -to). +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -See: \{Width,Height\}, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxSizeEvent](https://docs.wxwidgets.org/3.1/classwx_size_event.html) +wxWidgets docs: [wxSizeEvent](https://docs.wxwidgets.org/3.2/classwx_size_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxSizeEventType`](`t:wxSizeEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxSizeEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getRect/1,getSize/1]). @@ -67,19 +64,16 @@ subscribe to events of this type. -include("wx.hrl"). -type wxSizeEventType() :: 'size'. -export_type([wxSizeEvent/0, wxSize/0, wxSizeEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeevent.html#wxsizeeventgetsize">external documentation</a>. -doc """ Returns the entire size of the window generating the size change event. -This is the new total size of the window, i.e. the same size as would be -returned by `wxWindow:getSize/1` if it were called now. Use -`wxWindow:getClientSize/1` if you catch this event in a top level window such as -`m:wxFrame` to find the size available for the window contents. +This is the new total size of the window, i.e. the same size as would be returned by `wxWindow:getSize/1` if +it were called now. Use `wxWindow:getClientSize/1` if you catch this event in a top level window such as `m:wxFrame` +to find the size available for the window contents. """. -spec getSize(This) -> {W::integer(), H::integer()} when This::wxSizeEvent(). @@ -88,7 +82,7 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizeEvent_GetSize), wxe_util:rec(?wxSizeEvent_GetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeevent.html#wxsizeeventgetrect">external documentation</a>. +-doc "". -spec getRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxSizeEvent(). getRect(#wx_ref{type=ThisT}=This) -> @@ -97,30 +91,21 @@ getRect(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxSizeEvent_GetRect). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSizer.erl b/lib/wx/src/gen/wxSizer.erl index 5e7a58a83509..952ade4ace37 100644 --- a/lib/wx/src/gen/wxSizer.erl +++ b/lib/wx/src/gen/wxSizer.erl @@ -20,61 +20,53 @@ -module(wxSizer). -moduledoc """ -Functions for wxSizer class - -`m:wxSizer` is the abstract base class used for laying out subwindows in a -window. You cannot use `m:wxSizer` directly; instead, you will have to use one -of the sizer classes derived from it. Currently there are `m:wxBoxSizer`, -`m:wxStaticBoxSizer`, `m:wxGridSizer`, `m:wxFlexGridSizer`, `wxWrapSizer` (not -implemented in wx) and `m:wxGridBagSizer`. - -The layout algorithm used by sizers in wxWidgets is closely related to layout in -other GUI toolkits, such as Java's AWT, the GTK toolkit or the Qt toolkit. It is -based upon the idea of the individual subwindows reporting their minimal -required size and their ability to get stretched if the size of the parent -window has changed. - -This will most often mean that the programmer does not set the original size of -a dialog in the beginning, rather the dialog will be assigned a sizer and this -sizer will be queried about the recommended size. The sizer in turn will query -its children, which can be normal windows, empty space or other sizers, so that -a hierarchy of sizers can be constructed. Note that `m:wxSizer` does not derive -from `m:wxWindow` and thus does not interfere with tab ordering and requires -very little resources compared to a real window on screen. - -What makes sizers so well fitted for use in wxWidgets is the fact that every -control reports its own minimal size and the algorithm can handle differences in -font sizes or different window (dialog item) sizes on different platforms -without problems. If e.g. the standard font as well as the overall design of -Motif widgets requires more space than on Windows, the initial dialog size will -automatically be bigger on Motif than on Windows. - -Sizers may also be used to control the layout of custom drawn items on the -window. The `add/4`, `insert/5`, and `prepend/4` functions return a pointer to -the newly added `m:wxSizerItem`. Just add empty space of the desired size and -attributes, and then use the `wxSizerItem:getRect/1` method to determine where -the drawing operations should take place. - -Please notice that sizers, like child windows, are owned by the library and will -be deleted by it which implies that they must be allocated on the heap. However -if you create a sizer and do not add it to another sizer or window, the library -wouldn't be able to delete such an orphan sizer and in this, and only this, case -it should be deleted explicitly. +`m:wxSizer` is the abstract base class used for laying out subwindows in a window. + +You cannot use `m:wxSizer` directly; instead, you will have to use one of the sizer +classes derived from it. Currently there are `m:wxBoxSizer`, `m:wxStaticBoxSizer`, `m:wxGridSizer`, `m:wxFlexGridSizer`, `wxWrapSizer` +(not implemented in wx) and `m:wxGridBagSizer`. + +The layout algorithm used by sizers in wxWidgets is closely related to layout in other +GUI toolkits, such as Java's AWT, the GTK toolkit or the Qt toolkit. It is based upon the +idea of the individual subwindows reporting their minimal required size and their ability +to get stretched if the size of the parent window has changed. + +This will most often mean that the programmer does not set the original size of a dialog +in the beginning, rather the dialog will be assigned a sizer and this sizer will be +queried about the recommended size. The sizer in turn will query its children, which can +be normal windows, empty space or other sizers, so that a hierarchy of sizers can be +constructed. Note that `m:wxSizer` does not derive from `m:wxWindow` and thus does not +interfere with tab ordering and requires very little resources compared to a real window +on screen. + +What makes sizers so well fitted for use in wxWidgets is the fact that every control +reports its own minimal size and the algorithm can handle differences in font sizes or +different window (dialog item) sizes on different platforms without problems. If e.g. the +standard font as well as the overall design of Motif widgets requires more space than on +Windows, the initial dialog size will automatically be bigger on Motif than on Windows. + +Sizers may also be used to control the layout of custom drawn items on the window. The `add/4`, `insert/5`, +and `prepend/4` functions return a pointer to the newly added `m:wxSizerItem`. Just add empty space +of the desired size and attributes, and then use the `wxSizerItem:getRect/1` method to determine where the +drawing operations should take place. + +Please notice that sizers, like child windows, are owned by the library and will be +deleted by it which implies that they must be allocated on the heap. However if you create +a sizer and do not add it to another sizer or window, the library wouldn't be able to +delete such an orphan sizer and in this, and only this, case it should be deleted explicitly. wxSizer flags -The "flag" argument accepted by `m:wxSizerItem` constructors and other -functions, e.g. `add/4`, is an OR-combination of the following flags. Two main -behaviours are defined using these flags. One is the border around a window: the -border parameter determines the border width whereas the flags given here -determine which side(s) of the item that the border will be added. The other -flags determine how the sizer item behaves when the space allotted to the sizer -changes, and is somewhat dependent on the specific kind of sizer used. +The "flag" argument accepted by `m:wxSizerItem` constructors and other functions, e.g. `add/4`, +is an OR-combination of the following flags. Two main behaviours are defined using these +flags. One is the border around a window: the border parameter determines the border width +whereas the flags given here determine which side(s) of the item that the border will be +added. The other flags determine how the sizer item behaves when the space allotted to the +sizer changes, and is somewhat dependent on the specific kind of sizer used. -See: -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer) +See: [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) -wxWidgets docs: [wxSizer](https://docs.wxwidgets.org/3.1/classwx_sizer.html) +wxWidgets docs: [wxSizer](https://docs.wxwidgets.org/3.2/classwx_sizer.html) """. -include("wxe.hrl"). -export([add/2,add/3,add/4,addSpacer/2,addStretchSpacer/1,addStretchSpacer/2, @@ -91,11 +83,10 @@ wxWidgets docs: [wxSizer](https://docs.wxwidgets.org/3.1/classwx_sizer.html) -type wxSizer() :: wx:wx_object(). -export_type([wxSizer/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv add(This,Window, []) +-doc(#{equiv => add(This,Window, [])}). -spec add(This, Window) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(). @@ -103,23 +94,11 @@ add(This,Window) when is_record(This, wx_ref),is_record(Window, wx_ref) -> add(This,Window, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizeradd">external documentation</a>. -%% <br /> Also:<br /> -%% add(This, Window, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Flags::wxSizerFlags:wxSizerFlags();<br /> -%% (This, Window, [Option]) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(),<br /> -%% Option :: {'proportion', integer()}<br /> -%% | {'flag', integer()}<br /> -%% | {'border', integer()}<br /> -%% | {'userData', wx:wx_object()}.<br /> -%% -doc """ Appends a child to the sizer. -`m:wxSizer` itself is an abstract class, but the parameters are equivalent in -the derived classes that you will instantiate to use it so they are described -here: +`m:wxSizer` itself is an abstract class, but the parameters are equivalent in the derived +classes that you will instantiate to use it so they are described here: """. -spec add(This, Width, Height) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Width::integer(), Height::integer(); @@ -166,11 +145,6 @@ add(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizer_Add_2_1), wxe_util:rec(?wxSizer_Add_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizeradd">external documentation</a>. -%% <br /> Also:<br /> -%% add(This, Width, Height, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Width::integer(), Height::integer(), Flags::wxSizerFlags:wxSizerFlags().<br /> -%% -doc "Appends a spacer child to the sizer.". -spec add(This, Width, Height, [Option]) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Width::integer(), Height::integer(), @@ -198,10 +172,9 @@ add(#wx_ref{type=ThisT}=This,Width,Height,#wx_ref{type=FlagsT}=Flags) wxe_util:queue_cmd(This,Width,Height,Flags,?get_env(),?wxSizer_Add_3_1), wxe_util:rec(?wxSizer_Add_3_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizeraddspacer">external documentation</a>. -doc """ -This base function adds non-stretchable space to both the horizontal and -vertical orientation of the sizer. +This base function adds non-stretchable space to both the horizontal and vertical +orientation of the sizer. More readable way of calling: @@ -215,7 +188,7 @@ addSpacer(#wx_ref{type=ThisT}=This,Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxSizer_AddSpacer), wxe_util:rec(?wxSizer_AddSpacer). -%% @equiv addStretchSpacer(This, []) +-doc(#{equiv => addStretchSpacer(This, [])}). -spec addStretchSpacer(This) -> wxSizerItem:wxSizerItem() when This::wxSizer(). @@ -223,7 +196,6 @@ addStretchSpacer(This) when is_record(This, wx_ref) -> addStretchSpacer(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizeraddstretchspacer">external documentation</a>. -doc """ Adds stretchable space to the sizer. @@ -241,7 +213,6 @@ addStretchSpacer(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxSizer_AddStretchSpacer), wxe_util:rec(?wxSizer_AddStretchSpacer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizercalcmin">external documentation</a>. -doc """ This method is abstract and has to be overwritten by any derived class. @@ -254,7 +225,7 @@ calcMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizer_CalcMin), wxe_util:rec(?wxSizer_CalcMin). -%% @equiv clear(This, []) +-doc(#{equiv => clear(This, [])}). -spec clear(This) -> 'ok' when This::wxSizer(). @@ -262,15 +233,14 @@ clear(This) when is_record(This, wx_ref) -> clear(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerclear">external documentation</a>. -doc """ Detaches all children from the sizer. If `delete_windows` is true then child windows will also be deleted. -Notice that child sizers are always deleted, as a general consequence of the -principle that sizers own their sizer children, but don't own their window -children (because they are already owned by their parent windows). +Notice that child sizers are always deleted, as a general consequence of the principle +that sizers own their sizer children, but don't own their window children (because they +are already owned by their parent windows). """. -spec clear(This, [Option]) -> 'ok' when This::wxSizer(), @@ -283,17 +253,12 @@ clear(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxSizer_Clear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerdetach">external documentation</a>. -%% <br /> Also:<br /> -%% detach(This, Index) -> boolean() when<br /> -%% This::wxSizer(), Index::integer().<br /> -%% -doc """ Detach a item at position `index` from the sizer without destroying it. -This method does not cause any layout or resizing to take place, call `layout/1` -to update the layout "on screen" after detaching a child from the sizer. Returns -true if the child item was found and detached, false otherwise. +This method does not cause any layout or resizing to take place, call `layout/1` to update the +layout "on screen" after detaching a child from the sizer. Returns true if the child item +was found and detached, false otherwise. See: `remove/2` """. @@ -318,19 +283,14 @@ detach(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxSizer_Detach_1_1), wxe_util:rec(?wxSizer_Detach_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerfit">external documentation</a>. -doc """ -Tell the sizer to resize the `window` so that its client area matches the -sizer's minimal size (`ComputeFittingClientSize()` (not implemented in wx) is -called to determine it). +Tell the sizer to resize the `window` so that its client area matches the sizer's minimal +size (`ComputeFittingClientSize()` (not implemented in wx) is called to determine it). This is commonly done in the constructor of the window itself, see sample in the description of `m:wxBoxSizer`. Return: The new window size. - -See: `ComputeFittingClientSize()` (not implemented in wx), -`ComputeFittingWindowSize()` (not implemented in wx) """. -spec fit(This, Window) -> {W::integer(), H::integer()} when This::wxSizer(), Window::wxWindow:wxWindow(). @@ -340,8 +300,7 @@ fit(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(This,Window,?get_env(),?wxSizer_Fit), wxe_util:rec(?wxSizer_Fit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerfitinside">external documentation</a>. --doc "See: `fitInside/2`.". +-doc "Equivalent to: `fitInside/2`". -spec setVirtualSizeHints(This, Window) -> 'ok' when This::wxSizer(), Window::wxWindow:wxWindow(). @@ -349,16 +308,18 @@ setVirtualSizeHints(This,Window) when is_record(This, wx_ref),is_record(Window, wx_ref) -> fitInside(This,Window). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerfitinside">external documentation</a>. -doc """ -Tell the sizer to resize the virtual size of the `window` to match the sizer's -minimal size. +Tell the sizer to resize the virtual size of the `window` to match the sizer's minimal +size. This will not alter the on screen size of the window, but may cause the -addition/removal/alteration of scrollbars required to view the virtual area in -windows which manage it. +addition/removal/alteration of scrollbars required to view the virtual area in windows +which manage it. + +See: +* `wxScrolledWindow:setScrollbars/6` -See: `wxScrolledWindow:setScrollbars/6`, `setVirtualSizeHints/2` +* `setVirtualSizeHints/2` """. -spec fitInside(This, Window) -> 'ok' when This::wxSizer(), Window::wxWindow:wxWindow(). @@ -367,7 +328,7 @@ fitInside(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxWindow), wxe_util:queue_cmd(This,Window,?get_env(),?wxSizer_FitInside). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetchildren">external documentation</a>. +-doc "". -spec getChildren(This) -> [wxSizerItem:wxSizerItem()] when This::wxSizer(). getChildren(#wx_ref{type=ThisT}=This) -> @@ -375,16 +336,10 @@ getChildren(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizer_GetChildren), wxe_util:rec(?wxSizer_GetChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetitem">external documentation</a>. -%% <br /> Also:<br /> -%% getItem(This, Index) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Index::integer().<br /> -%% -doc """ Finds `m:wxSizerItem` which is located in the sizer at position `index`. -Use parameter `recursive` to search in subsizers too. Returns pointer to item or -NULL. +Use parameter `recursive` to search in subsizers too. Returns pointer to item or NULL. """. -spec getItem(This, Window) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); @@ -400,12 +355,10 @@ getItem(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxSizer_GetItem_1), wxe_util:rec(?wxSizer_GetItem_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetitem">external documentation</a>. -doc """ Finds `m:wxSizerItem` which holds the given `window`. -Use parameter `recursive` to search in subsizers too. Returns pointer to item or -NULL. +Use parameter `recursive` to search in subsizers too. Returns pointer to item or NULL. """. -spec getItem(This, Window, [Option]) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), @@ -426,7 +379,6 @@ getItem(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizer_GetItem_2), wxe_util:rec(?wxSizer_GetItem_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetsize">external documentation</a>. -doc "Returns the current size of the sizer.". -spec getSize(This) -> {W::integer(), H::integer()} when This::wxSizer(). @@ -435,7 +387,6 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizer_GetSize), wxe_util:rec(?wxSizer_GetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetposition">external documentation</a>. -doc "Returns the current position of the sizer.". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxSizer(). @@ -444,16 +395,14 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizer_GetPosition), wxe_util:rec(?wxSizer_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizergetminsize">external documentation</a>. -doc """ Returns the minimal size of the sizer. -This is either the combined minimal size of all the children and their borders -or the minimal size set by `setMinSize/3`, depending on which is bigger. Note -that the returned value is client size, not window size. In particular, if you -use the value to set toplevel window's minimal or actual size, use -`wxWindow::SetMinClientSize()` (not implemented in wx) or -`wxWindow:setClientSize/3`, not `wxWindow:setMinSize/2` or `wxWindow:setSize/6`. +This is either the combined minimal size of all the children and their borders or the +minimal size set by `setMinSize/3`, depending on which is bigger. Note that the returned value is client +size, not window size. In particular, if you use the value to set toplevel window's +minimal or actual size, use `wxWindow::SetMinClientSize()` (not implemented in wx) or `wxWindow:setClientSize/3`, +not `wxWindow:setMinSize/2` or `wxWindow:setSize/6`. """. -spec getMinSize(This) -> {W::integer(), H::integer()} when This::wxSizer(). @@ -462,20 +411,18 @@ getMinSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizer_GetMinSize), wxe_util:rec(?wxSizer_GetMinSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerhide">external documentation</a>. -%% <br /> Also:<br /> -%% hide(This, Index) -> boolean() when<br /> -%% This::wxSizer(), Index::integer().<br /> -%% -doc """ Hides the item at position `index`. To make a sizer item disappear, use `hide/3` followed by `layout/1`. -Use parameter `recursive` to hide elements found in subsizers. Returns true if -the child item was found, false otherwise. +Use parameter `recursive` to hide elements found in subsizers. Returns true if the child +item was found, false otherwise. -See: `isShown/2`, `show/3` +See: +* `isShown/2` + +* `show/3` """. -spec hide(This, Window) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); @@ -491,16 +438,18 @@ hide(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxSizer_Hide_1), wxe_util:rec(?wxSizer_Hide_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerhide">external documentation</a>. -doc """ Hides the child `window`. To make a sizer item disappear, use `hide/3` followed by `layout/1`. -Use parameter `recursive` to hide elements found in subsizers. Returns true if -the child item was found, false otherwise. +Use parameter `recursive` to hide elements found in subsizers. Returns true if the child +item was found, false otherwise. -See: `isShown/2`, `show/3` +See: +* `isShown/2` + +* `show/3` """. -spec hide(This, Window, [Option]) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), @@ -521,7 +470,7 @@ hide(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizer_Hide_2), wxe_util:rec(?wxSizer_Hide_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerinsert">external documentation</a>. +-doc "". -spec insert(This, Index, Item) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Index::integer(), Item::wxSizerItem:wxSizerItem(). insert(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=ItemT}=Item) @@ -531,17 +480,6 @@ insert(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=ItemT}=Item) wxe_util:queue_cmd(This,Index,Item,?get_env(),?wxSizer_Insert_2), wxe_util:rec(?wxSizer_Insert_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerinsert">external documentation</a>. -%% <br /> Also:<br /> -%% insert(This, Index, Window, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Index::integer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Flags::wxSizerFlags:wxSizerFlags();<br /> -%% (This, Index, Window, [Option]) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Index::integer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(),<br /> -%% Option :: {'proportion', integer()}<br /> -%% | {'flag', integer()}<br /> -%% | {'border', integer()}<br /> -%% | {'userData', wx:wx_object()}.<br /> -%% -doc """ Insert a child into the sizer before any existing item at `index`. @@ -593,11 +531,6 @@ insert(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(This,Index,wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizer_Insert_3_1), wxe_util:rec(?wxSizer_Insert_3_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerinsert">external documentation</a>. -%% <br /> Also:<br /> -%% insert(This, Index, Width, Height, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Index::integer(), Width::integer(), Height::integer(), Flags::wxSizerFlags:wxSizerFlags().<br /> -%% -doc """ Insert a child into the sizer before any existing item at `index`. @@ -629,7 +562,6 @@ insert(#wx_ref{type=ThisT}=This,Index,Width,Height,#wx_ref{type=FlagsT}=Flags) wxe_util:queue_cmd(This,Index,Width,Height,Flags,?get_env(),?wxSizer_Insert_4_1), wxe_util:rec(?wxSizer_Insert_4_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerinsertspacer">external documentation</a>. -doc """ Inserts non-stretchable space to the sizer. @@ -643,7 +575,7 @@ insertSpacer(#wx_ref{type=ThisT}=This,Index,Size) wxe_util:queue_cmd(This,Index,Size,?get_env(),?wxSizer_InsertSpacer), wxe_util:rec(?wxSizer_InsertSpacer). -%% @equiv insertStretchSpacer(This,Index, []) +-doc(#{equiv => insertStretchSpacer(This,Index, [])}). -spec insertStretchSpacer(This, Index) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Index::integer(). @@ -651,7 +583,6 @@ insertStretchSpacer(This,Index) when is_record(This, wx_ref),is_integer(Index) -> insertStretchSpacer(This,Index, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerinsertstretchspacer">external documentation</a>. -doc """ Inserts stretchable space to the sizer. @@ -669,15 +600,15 @@ insertStretchSpacer(#wx_ref{type=ThisT}=This,Index, Options) wxe_util:queue_cmd(This,Index, Opts,?get_env(),?wxSizer_InsertStretchSpacer), wxe_util:rec(?wxSizer_InsertStretchSpacer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerisshown">external documentation</a>. -%% <br /> Also:<br /> -%% isShown(This, Index) -> boolean() when<br /> -%% This::wxSizer(), Index::integer().<br /> -%% -doc """ Returns true if the item at `index` is shown. -See: `hide/3`, `show/3`, `wxSizerItem:isShown/1` +See: +* `hide/3` + +* `show/3` + +* `wxSizerItem:isShown/1` """. -spec isShown(This, Window) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); @@ -700,8 +631,7 @@ isShown(#wx_ref{type=ThisT}=This,Index) wxe_util:queue_cmd(This,Index,?get_env(),?wxSizer_IsShown_1_1), wxe_util:rec(?wxSizer_IsShown_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerlayout">external documentation</a>. --doc "See: `layout/1`.". +-doc "Equivalent to: `layout/1`". -spec recalcSizes(This) -> 'ok' when This::wxSizer(). @@ -709,11 +639,10 @@ recalcSizes(This) when is_record(This, wx_ref) -> layout(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerlayout">external documentation</a>. -doc """ -Call this to force layout of the children anew, e.g. after having added a child -to or removed a child (window, other sizer or space) from the sizer while -keeping the current dimension. +Call this to force layout of the children anew, e.g. after having added a child to or +removed a child (window, other sizer or space) from the sizer while keeping the current +dimension. """. -spec layout(This) -> 'ok' when This::wxSizer(). @@ -721,7 +650,7 @@ layout(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,?get_env(),?wxSizer_Layout). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerprepend">external documentation</a>. +-doc "". -spec prepend(This, Item) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Item::wxSizerItem:wxSizerItem(). prepend(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> @@ -730,20 +659,9 @@ prepend(#wx_ref{type=ThisT}=This,#wx_ref{type=ItemT}=Item) -> wxe_util:queue_cmd(This,Item,?get_env(),?wxSizer_Prepend_1), wxe_util:rec(?wxSizer_Prepend_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerprepend">external documentation</a>. -%% <br /> Also:<br /> -%% prepend(This, Window, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Flags::wxSizerFlags:wxSizerFlags();<br /> -%% (This, Window, [Option]) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(),<br /> -%% Option :: {'proportion', integer()}<br /> -%% | {'flag', integer()}<br /> -%% | {'border', integer()}<br /> -%% | {'userData', wx:wx_object()}.<br /> -%% -doc """ -Same as `add/4`, but prepends the items to the beginning of the list of items -(windows, subsizers or spaces) owned by this sizer. +Same as `add/4`, but prepends the items to the beginning of the list of items (windows, +subsizers or spaces) owned by this sizer. """. -spec prepend(This, Width, Height) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Width::integer(), Height::integer(); @@ -790,14 +708,9 @@ prepend(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(This,wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizer_Prepend_2_1), wxe_util:rec(?wxSizer_Prepend_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerprepend">external documentation</a>. -%% <br /> Also:<br /> -%% prepend(This, Width, Height, Flags) -> wxSizerItem:wxSizerItem() when<br /> -%% This::wxSizer(), Width::integer(), Height::integer(), Flags::wxSizerFlags:wxSizerFlags().<br /> -%% -doc """ -Same as `add/4`, but prepends the items to the beginning of the list of items -(windows, subsizers or spaces) owned by this sizer. +Same as `add/4`, but prepends the items to the beginning of the list of items (windows, +subsizers or spaces) owned by this sizer. """. -spec prepend(This, Width, Height, [Option]) -> wxSizerItem:wxSizerItem() when This::wxSizer(), Width::integer(), Height::integer(), @@ -825,7 +738,6 @@ prepend(#wx_ref{type=ThisT}=This,Width,Height,#wx_ref{type=FlagsT}=Flags) wxe_util:queue_cmd(This,Width,Height,Flags,?get_env(),?wxSizer_Prepend_3_1), wxe_util:rec(?wxSizer_Prepend_3_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerprependspacer">external documentation</a>. -doc """ Prepends non-stretchable space to the sizer. @@ -839,7 +751,7 @@ prependSpacer(#wx_ref{type=ThisT}=This,Size) wxe_util:queue_cmd(This,Size,?get_env(),?wxSizer_PrependSpacer), wxe_util:rec(?wxSizer_PrependSpacer). -%% @equiv prependStretchSpacer(This, []) +-doc(#{equiv => prependStretchSpacer(This, [])}). -spec prependStretchSpacer(This) -> wxSizerItem:wxSizerItem() when This::wxSizer(). @@ -847,7 +759,6 @@ prependStretchSpacer(This) when is_record(This, wx_ref) -> prependStretchSpacer(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerprependstretchspacer">external documentation</a>. -doc """ Prepends stretchable space to the sizer. @@ -865,17 +776,11 @@ prependStretchSpacer(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxSizer_PrependStretchSpacer), wxe_util:rec(?wxSizer_PrependStretchSpacer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerremove">external documentation</a>. -%% <br /> Also:<br /> -%% remove(This, Sizer) -> boolean() when<br /> -%% This::wxSizer(), Sizer::wxSizer().<br /> -%% -doc """ Removes a sizer child from the sizer and destroys it. -Note: This method does not cause any layout or resizing to take place, call -`layout/1` to update the layout "on screen" after removing a child from the -sizer. +Note: This method does not cause any layout or resizing to take place, call `layout/1` to update +the layout "on screen" after removing a child from the sizer. Return: true if the child item was found and removed, false otherwise. """. @@ -894,21 +799,15 @@ remove(#wx_ref{type=ThisT}=This,#wx_ref{type=SizerT}=Sizer) -> wxe_util:queue_cmd(This,Sizer,?get_env(),?wxSizer_Remove_1_1), wxe_util:rec(?wxSizer_Remove_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerreplace">external documentation</a>. -%% <br /> Also:<br /> -%% replace(This, Index, Newitem) -> boolean() when<br /> -%% This::wxSizer(), Index::integer(), Newitem::wxSizerItem:wxSizerItem().<br /> -%% -doc """ -Detaches the given item at position `index` from the sizer and replaces it with -the given `m:wxSizerItem` `newitem`. +Detaches the given item at position `index` from the sizer and replaces it with the given `m:wxSizerItem` +`newitem`. -The detached child is deleted `only` if it is a sizer or a spacer (but not if it -is a `m:wxWindow` because windows are owned by their parent window, not the -sizer). +The detached child is deleted `only` if it is a sizer or a spacer (but not if it is a `m:wxWindow` +because windows are owned by their parent window, not the sizer). -This method does not cause any layout or resizing to take place, call `layout/1` -to update the layout "on screen" after replacing a child from the sizer. +This method does not cause any layout or resizing to take place, call `layout/1` to update the +layout "on screen" after replacing a child from the sizer. Returns true if the child item was found and removed, false otherwise. """. @@ -927,18 +826,16 @@ replace(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=NewitemT}=Newitem) wxe_util:queue_cmd(This,Index,Newitem,?get_env(),?wxSizer_Replace_2), wxe_util:rec(?wxSizer_Replace_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizerreplace">external documentation</a>. -doc """ -Detaches the given `oldwin` from the sizer and replaces it with the given -`newwin`. +Detaches the given `oldwin` from the sizer and replaces it with the given `newwin`. -The detached child window is `not` deleted (because windows are owned by their -parent window, not the sizer). +The detached child window is `not` deleted (because windows are owned by their parent +window, not the sizer). Use parameter `recursive` to search the given element recursively in subsizers. -This method does not cause any layout or resizing to take place, call `layout/1` -to update the layout "on screen" after replacing a child from the sizer. +This method does not cause any layout or resizing to take place, call `layout/1` to update the +layout "on screen" after replacing a child from the sizer. Returns true if the child item was found and removed, false otherwise. """. @@ -968,10 +865,9 @@ replace(#wx_ref{type=ThisT}=This,#wx_ref{type=OldwinT}=Oldwin,#wx_ref{type=Newwi wxe_util:queue_cmd(This,wx:typeCast(Oldwin, OldwinType),wx:typeCast(Newwin, NewwinType), Opts,?get_env(),?wxSizer_Replace_3), wxe_util:rec(?wxSizer_Replace_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetdimension">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setDimension(This, Pos, Size) -> 'ok' when This::wxSizer(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}. @@ -980,11 +876,10 @@ setDimension(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,Pos,Size,?get_env(),?wxSizer_SetDimension_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetdimension">external documentation</a>. -doc """ -Call this to force the sizer to take the given dimension and thus force the -items owned by the sizer to resize themselves according to the rules defined by -the parameter in the `add/4` and `prepend/4` methods. +Call this to force the sizer to take the given dimension and thus force the items owned +by the sizer to resize themselves according to the rules defined by the parameter in the `add/4` +and `prepend/4` methods. """. -spec setDimension(This, X, Y, Width, Height) -> 'ok' when This::wxSizer(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -993,14 +888,12 @@ setDimension(#wx_ref{type=ThisT}=This,X,Y,Width,Height) ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,X,Y,Width,Height,?get_env(),?wxSizer_SetDimension_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetminsize">external documentation</a>. -doc """ Call this to give the sizer a minimal size. -Normally, the sizer will calculate its minimal size based purely on how much -space its children need. After calling this method `getMinSize/1` will return -either the minimal size as requested by its children or the minimal size set -here, depending on which is bigger. +Normally, the sizer will calculate its minimal size based purely on how much space its +children need. After calling this method `getMinSize/1` will return either the minimal size as requested +by its children or the minimal size set here, depending on which is bigger. """. -spec setMinSize(This, Size) -> 'ok' when This::wxSizer(), Size::{W::integer(), H::integer()}. @@ -1009,10 +902,9 @@ setMinSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,Size,?get_env(),?wxSizer_SetMinSize_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetminsize">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setMinSize(This, Width, Height) -> 'ok' when This::wxSizer(), Width::integer(), Height::integer(). @@ -1021,11 +913,7 @@ setMinSize(#wx_ref{type=ThisT}=This,Width,Height) ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,Width,Height,?get_env(),?wxSizer_SetMinSize_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetitemminsize">external documentation</a>. -%% <br /> Also:<br /> -%% setItemMinSize(This, Index, Size) -> boolean() when<br /> -%% This::wxSizer(), Index::integer(), Size::{W::integer(), H::integer()}.<br /> -%% +-doc "". -spec setItemMinSize(This, Window, Size) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Size::{W::integer(), H::integer()}; (This, Index, Size) -> boolean() when @@ -1048,11 +936,7 @@ setItemMinSize(#wx_ref{type=ThisT}=This,Index,{SizeW,SizeH} = Size) wxe_util:queue_cmd(This,Index,Size,?get_env(),?wxSizer_SetItemMinSize_2_1), wxe_util:rec(?wxSizer_SetItemMinSize_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetitemminsize">external documentation</a>. -%% <br /> Also:<br /> -%% setItemMinSize(This, Index, Width, Height) -> boolean() when<br /> -%% This::wxSizer(), Index::integer(), Width::integer(), Height::integer().<br /> -%% +-doc "". -spec setItemMinSize(This, Window, Width, Height) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Width::integer(), Height::integer(); (This, Index, Width, Height) -> boolean() when @@ -1075,18 +959,16 @@ setItemMinSize(#wx_ref{type=ThisT}=This,Index,Width,Height) wxe_util:queue_cmd(This,Index,Width,Height,?get_env(),?wxSizer_SetItemMinSize_3_1), wxe_util:rec(?wxSizer_SetItemMinSize_3_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizersetsizehints">external documentation</a>. -doc """ -This method first calls `fit/2` and then `setSizeHints/2` on the `window` passed -to it. +This method first calls `fit/2` and then `setSizeHints/2` on the `window` passed to it. -This only makes sense when `window` is actually a `m:wxTopLevelWindow` such as a -`m:wxFrame` or a `m:wxDialog`, since SetSizeHints only has any effect in these -classes. It does nothing in normal windows or controls. +This only makes sense when `window` is actually a `m:wxTopLevelWindow` such as a `m:wxFrame` +or a `m:wxDialog`, since SetSizeHints only has any effect in these classes. It does +nothing in normal windows or controls. -This method is implicitly used by `wxWindow:setSizerAndFit/3` which is commonly -invoked in the constructor of a toplevel window itself (see the sample in the -description of `m:wxBoxSizer`) if the toplevel window is resizable. +This method is implicitly used by `wxWindow:setSizerAndFit/3` which is commonly invoked in the constructor of a +toplevel window itself (see the sample in the description of `m:wxBoxSizer`) if the +toplevel window is resizable. """. -spec setSizeHints(This, Window) -> 'ok' when This::wxSizer(), Window::wxWindow:wxWindow(). @@ -1095,13 +977,7 @@ setSizeHints(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxWindow), wxe_util:queue_cmd(This,Window,?get_env(),?wxSizer_SetSizeHints). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizershow">external documentation</a>. -%% <br /> Also:<br /> -%% show(This, Index) -> boolean() when<br /> -%% This::wxSizer(), Index::integer();<br /> -%% (This, Show) -> 'ok' when<br /> -%% This::wxSizer(), Show::boolean().<br /> -%% +-doc "". -spec show(This, Window) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(); (This, Index) -> boolean() when @@ -1121,12 +997,6 @@ show(#wx_ref{type=ThisT}=This,Show) ?CLASS(ThisT,wxSizer), wxe_util:queue_cmd(This,Show,?get_env(),?wxSizer_Show_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizershow">external documentation</a>. -%% <br /> Also:<br /> -%% show(This, Index, [Option]) -> boolean() when<br /> -%% This::wxSizer(), Index::integer(),<br /> -%% Option :: {'show', boolean()}.<br /> -%% -doc """ Shows the item at `index`. @@ -1134,7 +1004,10 @@ To make a sizer item disappear or reappear, use `show/3` followed by `layout/1`. Returns true if the child item was found, false otherwise. -See: `hide/3`, `isShown/2` +See: +* `hide/3` + +* `isShown/2` """. -spec show(This, Window, [Option]) -> boolean() when This::wxSizer(), Window::wxWindow:wxWindow() | wxSizer:wxSizer(), @@ -1168,7 +1041,6 @@ show(#wx_ref{type=ThisT}=This,Index, Options) wxe_util:queue_cmd(This,Index, Opts,?get_env(),?wxSizer_Show_2_1), wxe_util:rec(?wxSizer_Show_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizer.html#wxsizershowitems">external documentation</a>. -doc "Show or hide all items managed by the sizer.". -spec showItems(This, Show) -> 'ok' when This::wxSizer(), Show::boolean(). diff --git a/lib/wx/src/gen/wxSizerFlags.erl b/lib/wx/src/gen/wxSizerFlags.erl index 9e0e7c5d8313..495de7033e07 100644 --- a/lib/wx/src/gen/wxSizerFlags.erl +++ b/lib/wx/src/gen/wxSizerFlags.erl @@ -20,28 +20,23 @@ -module(wxSizerFlags). -moduledoc """ -Functions for wxSizerFlags class - Container for sizer items flags providing readable names for them. -Normally, when you add an item to a sizer via `wxSizer:add/4`, you have to -specify a lot of flags and parameters which can be unwieldy. This is where -`m:wxSizerFlags` comes in: it allows you to specify all parameters using the -named methods instead. For example, instead of +Normally, when you add an item to a sizer via `wxSizer:add/4`, you have to specify a lot of flags and +parameters which can be unwieldy. This is where `m:wxSizerFlags` comes in: it allows you +to specify all parameters using the named methods instead. For example, instead of you can now write -This is more readable and also allows you to create `m:wxSizerFlags` objects -which can be reused for several sizer items. +This is more readable and also allows you to create `m:wxSizerFlags` objects which can be +reused for several sizer items. -Note that by specification, all methods of `m:wxSizerFlags` return the -`m:wxSizerFlags` object itself to allowing chaining multiple methods calls like -in the examples above. +Note that by specification, all methods of `m:wxSizerFlags` return the `m:wxSizerFlags` +object itself to allowing chaining multiple methods calls like in the examples above. See: `m:wxSizer` -wxWidgets docs: -[wxSizerFlags](https://docs.wxwidgets.org/3.1/classwx_sizer_flags.html) +wxWidgets docs: [wxSizerFlags](https://docs.wxwidgets.org/3.2/classwx_sizer_flags.html) """. -include("wxe.hrl"). -export([align/2,border/1,border/2,border/3,center/1,centre/1,destroy/1,expand/1, @@ -52,17 +47,15 @@ wxWidgets docs: -type wxSizerFlags() :: wx:wx_object(). -export_type([wxSizerFlags/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxSizerFlags(). new() -> new([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagswxsizerflags">external documentation</a>. -doc "Creates the `m:wxSizer` with the proportion specified by `proportion`.". -spec new([Option]) -> wxSizerFlags() when Option :: {'proportion', integer()}. @@ -74,14 +67,17 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxSizerFlags_new), wxe_util:rec(?wxSizerFlags_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsalign">external documentation</a>. -doc """ Sets the alignment of this `m:wxSizerFlags` to `align`. This method replaces the previously set alignment with the specified one. -See: `Top()` (not implemented in wx), `left/1`, `right/1`, `Bottom()` (not -implemented in wx), `centre/1` +See: +* `left/1` + +* `right/1` + +* `centre/1` """. -spec align(This, Alignment) -> wxSizerFlags() when This::wxSizerFlags(), Alignment::integer(). @@ -91,7 +87,7 @@ align(#wx_ref{type=ThisT}=This,Alignment) wxe_util:queue_cmd(This,Alignment,?get_env(),?wxSizerFlags_Align), wxe_util:rec(?wxSizerFlags_Align). -%% @equiv border(This, []) +-doc(#{equiv => border(This, [])}). -spec border(This) -> wxSizerFlags() when This::wxSizerFlags(). @@ -99,10 +95,9 @@ border(This) when is_record(This, wx_ref) -> border(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsborder">external documentation</a>. -doc """ -Sets the `m:wxSizerFlags` to have a border with size as returned by -`GetDefaultBorder()` (not implemented in wx). +Sets the `m:wxSizerFlags` to have a border with size as returned by `GetDefaultBorder()` +(not implemented in wx). """. -spec border(This, [Option]) -> wxSizerFlags() when This::wxSizerFlags(), @@ -116,15 +111,13 @@ border(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxSizerFlags_Border_1), wxe_util:rec(?wxSizerFlags_Border_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsborder">external documentation</a>. -doc """ -Sets the `m:wxSizerFlags` to have a border of a number of pixels specified by -`borderinpixels` with the directions specified by `direction`. +Sets the `m:wxSizerFlags` to have a border of a number of pixels specified by `borderinpixels` +with the directions specified by `direction`. -Prefer to use the overload below or `DoubleBorder()` (not implemented in wx) or -`TripleBorder()` (not implemented in wx) versions instead of hard-coding the -border value in pixels to avoid too small borders on devices with high DPI -displays. +Prefer to use the overload below or `DoubleBorder()` (not implemented in wx) or `TripleBorder()` +(not implemented in wx) versions instead of hard-coding the border value in pixels to +avoid too small borders on devices with high DPI displays. """. -spec border(This, Direction, Borderinpixels) -> wxSizerFlags() when This::wxSizerFlags(), Direction::integer(), Borderinpixels::integer(). @@ -134,8 +127,7 @@ border(#wx_ref{type=ThisT}=This,Direction,Borderinpixels) wxe_util:queue_cmd(This,Direction,Borderinpixels,?get_env(),?wxSizerFlags_Border_2), wxe_util:rec(?wxSizerFlags_Border_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagscenter">external documentation</a>. --doc "See: `center/1`.". +-doc "Equivalent to: `center/1`". -spec centre(This) -> wxSizerFlags() when This::wxSizerFlags(). @@ -143,11 +135,7 @@ centre(This) when is_record(This, wx_ref) -> center(This). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagscenter">external documentation</a>. --doc """ -Sets the object of the `m:wxSizerFlags` to center itself in the area it is -given. -""". +-doc "Sets the object of the `m:wxSizerFlags` to center itself in the area it is given.". -spec center(This) -> wxSizerFlags() when This::wxSizerFlags(). center(#wx_ref{type=ThisT}=This) -> @@ -155,11 +143,7 @@ center(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerFlags_Center), wxe_util:rec(?wxSizerFlags_Center). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsexpand">external documentation</a>. --doc """ -Sets the object of the `m:wxSizerFlags` to expand to fill as much area as it -can. -""". +-doc "Sets the object of the `m:wxSizerFlags` to expand to fill as much area as it can.". -spec expand(This) -> wxSizerFlags() when This::wxSizerFlags(). expand(#wx_ref{type=ThisT}=This) -> @@ -167,9 +151,8 @@ expand(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerFlags_Expand), wxe_util:rec(?wxSizerFlags_Expand). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsleft">external documentation</a>. -doc """ -Aligns the object to the left, similar for `Align(wxALIGN_LEFT)`. +Aligns the object to the left, similar for `Align(wxALIGN\_LEFT)`. Unlike `align/2`, this method doesn't change the vertical alignment of the item. """. @@ -180,7 +163,6 @@ left(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerFlags_Left), wxe_util:rec(?wxSizerFlags_Left). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsproportion">external documentation</a>. -doc "Sets the proportion of this `m:wxSizerFlags` to `proportion`.". -spec proportion(This, Proportion) -> wxSizerFlags() when This::wxSizerFlags(), Proportion::integer(). @@ -190,9 +172,8 @@ proportion(#wx_ref{type=ThisT}=This,Proportion) wxe_util:queue_cmd(This,Proportion,?get_env(),?wxSizerFlags_Proportion), wxe_util:rec(?wxSizerFlags_Proportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizerflags.html#wxsizerflagsright">external documentation</a>. -doc """ -Aligns the object to the right, similar for `Align(wxALIGN_RIGHT)`. +Aligns the object to the right, similar for `Align(wxALIGN\_RIGHT)`. Unlike `align/2`, this method doesn't change the vertical alignment of the item. """. @@ -203,8 +184,7 @@ right(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerFlags_Right), wxe_util:rec(?wxSizerFlags_Right). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxSizerFlags()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSizerFlags), diff --git a/lib/wx/src/gen/wxSizerItem.erl b/lib/wx/src/gen/wxSizerItem.erl index f23416d24777..84f31093332d 100644 --- a/lib/wx/src/gen/wxSizerItem.erl +++ b/lib/wx/src/gen/wxSizerItem.erl @@ -20,17 +20,14 @@ -module(wxSizerItem). -moduledoc """ -Functions for wxSizerItem class +The `m:wxSizerItem` class is used to track the position, size and other attributes of +each item managed by a `m:wxSizer`. -The `m:wxSizerItem` class is used to track the position, size and other -attributes of each item managed by a `m:wxSizer`. +It is not usually necessary to use this class because the sizer elements can also be +identified by their positions or window or sizer pointers but sometimes it may be more +convenient to use it directly. -It is not usually necessary to use this class because the sizer elements can -also be identified by their positions or window or sizer pointers but sometimes -it may be more convenient to use it directly. - -wxWidgets docs: -[wxSizerItem](https://docs.wxwidgets.org/3.1/classwx_sizer_item.html) +wxWidgets docs: [wxSizerItem](https://docs.wxwidgets.org/3.2/classwx_sizer_item.html) """. -include("wxe.hrl"). -export([assignSizer/2,assignSpacer/2,assignSpacer/3,assignWindow/2,calcMin/1, @@ -45,11 +42,10 @@ wxWidgets docs: -type wxSizerItem() :: wx:wx_object(). -export_type([wxSizerItem/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Window, []) +-doc(#{equiv => new(Window, [])}). -spec new(Window) -> wxSizerItem() when Window::wxWindow:wxWindow() | wxSizer:wxSizer(). @@ -57,17 +53,7 @@ new(Window) when is_record(Window, wx_ref) -> new(Window, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemwxsizeritem">external documentation</a>. -%% <br /> Also:<br /> -%% new(Window, Flags) -> wxSizerItem() when<br /> -%% Window::wxWindow:wxWindow() | wxSizer:wxSizer(), Flags::wxSizerFlags:wxSizerFlags();<br /> -%% (Window, [Option]) -> wxSizerItem() when<br /> -%% Window::wxWindow:wxWindow() | wxSizer:wxSizer(),<br /> -%% Option :: {'proportion', integer()}<br /> -%% | {'flag', integer()}<br /> -%% | {'border', integer()}<br /> -%% | {'userData', wx:wx_object()}.<br /> -%% +-doc "". -spec new(Width, Height) -> wxSizerItem() when Width::integer(), Height::integer(); (Window, Flags) -> wxSizerItem() when @@ -111,7 +97,6 @@ new(#wx_ref{type=WindowT}=Window, Options) wxe_util:queue_cmd(wx:typeCast(Window, WindowType), Opts,?get_env(),?wxSizerItem_new_2_1), wxe_util:rec(?wxSizerItem_new_2_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemwxsizeritem">external documentation</a>. -doc "Construct a sizer item for tracking a spacer.". -spec new(Width, Height, [Option]) -> wxSizerItem() when Width::integer(), Height::integer(), @@ -130,11 +115,7 @@ new(Width,Height, Options) wxe_util:queue_cmd(Width,Height, Opts,?get_env(),?wxSizerItem_new_3), wxe_util:rec(?wxSizerItem_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemcalcmin">external documentation</a>. --doc """ -Calculates the minimum desired size for the item, including any space needed by -borders. -""". +-doc "Calculates the minimum desired size for the item, including any space needed by borders.". -spec calcMin(This) -> {W::integer(), H::integer()} when This::wxSizerItem(). calcMin(#wx_ref{type=ThisT}=This) -> @@ -142,7 +123,6 @@ calcMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_CalcMin), wxe_util:rec(?wxSizerItem_CalcMin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemdeletewindows">external documentation</a>. -doc "Destroy the window or the windows in a subsizer, depending on the type of item.". -spec deleteWindows(This) -> 'ok' when This::wxSizerItem(). @@ -150,7 +130,6 @@ deleteWindows(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_DeleteWindows). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemdetachsizer">external documentation</a>. -doc "Enable deleting the SizerItem without destroying the contained sizer.". -spec detachSizer(This) -> 'ok' when This::wxSizerItem(). @@ -158,7 +137,6 @@ detachSizer(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_DetachSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetborder">external documentation</a>. -doc "Return the border attribute.". -spec getBorder(This) -> integer() when This::wxSizerItem(). @@ -167,7 +145,6 @@ getBorder(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetBorder), wxe_util:rec(?wxSizerItem_GetBorder). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetflag">external documentation</a>. -doc """ Return the flags attribute. @@ -180,7 +157,6 @@ getFlag(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetFlag), wxe_util:rec(?wxSizerItem_GetFlag). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetminsize">external documentation</a>. -doc "Get the minimum size needed for the item.". -spec getMinSize(This) -> {W::integer(), H::integer()} when This::wxSizerItem(). @@ -189,7 +165,6 @@ getMinSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetMinSize), wxe_util:rec(?wxSizerItem_GetMinSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetposition">external documentation</a>. -doc "What is the current position of the item, as set in the last Layout.". -spec getPosition(This) -> {X::integer(), Y::integer()} when This::wxSizerItem(). @@ -198,7 +173,6 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetPosition), wxe_util:rec(?wxSizerItem_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetproportion">external documentation</a>. -doc "Get the proportion item attribute.". -spec getProportion(This) -> integer() when This::wxSizerItem(). @@ -207,7 +181,6 @@ getProportion(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetProportion), wxe_util:rec(?wxSizerItem_GetProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetratio">external documentation</a>. -doc "Get the ratio item attribute.". -spec getRatio(This) -> number() when This::wxSizerItem(). @@ -216,7 +189,6 @@ getRatio(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetRatio), wxe_util:rec(?wxSizerItem_GetRatio). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetrect">external documentation</a>. -doc "Get the rectangle of the item on the parent window, excluding borders.". -spec getRect(This) -> {X::integer(), Y::integer(), W::integer(), H::integer()} when This::wxSizerItem(). @@ -225,7 +197,6 @@ getRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetRect), wxe_util:rec(?wxSizerItem_GetRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetsize">external documentation</a>. -doc "Get the current size of the item, as set in the last Layout.". -spec getSize(This) -> {W::integer(), H::integer()} when This::wxSizerItem(). @@ -234,7 +205,6 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetSize), wxe_util:rec(?wxSizerItem_GetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetsizer">external documentation</a>. -doc """ If this item is tracking a sizer, return it. @@ -247,7 +217,6 @@ getSizer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetSizer), wxe_util:rec(?wxSizerItem_GetSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetspacer">external documentation</a>. -doc "If this item is tracking a spacer, return its size.". -spec getSpacer(This) -> {W::integer(), H::integer()} when This::wxSizerItem(). @@ -256,7 +225,6 @@ getSpacer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetSpacer), wxe_util:rec(?wxSizerItem_GetSpacer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetuserdata">external documentation</a>. -doc "Get the userData item attribute.". -spec getUserData(This) -> wx:wx_object() when This::wxSizerItem(). @@ -265,7 +233,6 @@ getUserData(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetUserData), wxe_util:rec(?wxSizerItem_GetUserData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemgetwindow">external documentation</a>. -doc """ If this item is tracking a window then return it. @@ -278,7 +245,6 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_GetWindow), wxe_util:rec(?wxSizerItem_GetWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemissizer">external documentation</a>. -doc "Is this item a sizer?". -spec isSizer(This) -> boolean() when This::wxSizerItem(). @@ -287,17 +253,16 @@ isSizer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_IsSizer), wxe_util:rec(?wxSizerItem_IsSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemisshown">external documentation</a>. -doc """ -Returns true if this item is a window or a spacer and it is shown or if this -item is a sizer and not all of its elements are hidden. +Returns true if this item is a window or a spacer and it is shown or if this item is a +sizer and not all of its elements are hidden. -In other words, for sizer items, all of the child elements must be hidden for -the sizer itself to be considered hidden. +In other words, for sizer items, all of the child elements must be hidden for the sizer +itself to be considered hidden. -As an exception, if the `wxRESERVE_SPACE_EVEN_IF_HIDDEN` flag was used for this -sizer item, then `isShown/1` always returns true for it (see -`wxSizerFlags::ReserveSpaceEvenIfHidden()` (not implemented in wx)). +As an exception, if the `wxRESERVE_SPACE_EVEN_IF_HIDDEN` flag was used for this sizer +item, then `isShown/1` always returns true for it (see `wxSizerFlags::ReserveSpaceEvenIfHidden()` +(not implemented in wx)). """. -spec isShown(This) -> boolean() when This::wxSizerItem(). @@ -306,7 +271,6 @@ isShown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_IsShown), wxe_util:rec(?wxSizerItem_IsShown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemisspacer">external documentation</a>. -doc "Is this item a spacer?". -spec isSpacer(This) -> boolean() when This::wxSizerItem(). @@ -315,7 +279,6 @@ isSpacer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_IsSpacer), wxe_util:rec(?wxSizerItem_IsSpacer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemiswindow">external documentation</a>. -doc "Is this item a window?". -spec isWindow(This) -> boolean() when This::wxSizerItem(). @@ -324,7 +287,6 @@ isWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSizerItem_IsWindow), wxe_util:rec(?wxSizerItem_IsWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetborder">external documentation</a>. -doc "Set the border item attribute.". -spec setBorder(This, Border) -> 'ok' when This::wxSizerItem(), Border::integer(). @@ -333,11 +295,9 @@ setBorder(#wx_ref{type=ThisT}=This,Border) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Border,?get_env(),?wxSizerItem_SetBorder). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetdimension">external documentation</a>. -doc """ -Set the position and size of the space allocated to the sizer, and adjust the -position and size of the item to be within that space taking alignment and -borders into account. +Set the position and size of the space allocated to the sizer, and adjust the position +and size of the item to be within that space taking alignment and borders into account. """. -spec setDimension(This, Pos, Size) -> 'ok' when This::wxSizerItem(), Pos::{X::integer(), Y::integer()}, Size::{W::integer(), H::integer()}. @@ -346,7 +306,6 @@ setDimension(#wx_ref{type=ThisT}=This,{PosX,PosY} = Pos,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Pos,Size,?get_env(),?wxSizerItem_SetDimension). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetflag">external documentation</a>. -doc "Set the flag item attribute.". -spec setFlag(This, Flag) -> 'ok' when This::wxSizerItem(), Flag::integer(). @@ -355,12 +314,10 @@ setFlag(#wx_ref{type=ThisT}=This,Flag) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Flag,?get_env(),?wxSizerItem_SetFlag). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetinitsize">external documentation</a>. -doc """ Sets the minimum size to be allocated for this item. -This is identical to `setMinSize/3`, prefer to use the other function, as its -name is more clear. +This is identical to `setMinSize/3`, prefer to use the other function, as its name is more clear. """. -spec setInitSize(This, X, Y) -> 'ok' when This::wxSizerItem(), X::integer(), Y::integer(). @@ -369,7 +326,6 @@ setInitSize(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxSizerItem_SetInitSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetminsize">external documentation</a>. -doc """ Sets the minimum size to be allocated for this item. @@ -382,10 +338,9 @@ setMinSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Size,?get_env(),?wxSizerItem_SetMinSize_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetminsize">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setMinSize(This, X, Y) -> 'ok' when This::wxSizerItem(), X::integer(), Y::integer(). @@ -394,7 +349,6 @@ setMinSize(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxSizerItem_SetMinSize_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetproportion">external documentation</a>. -doc "Set the proportion item attribute.". -spec setProportion(This, Proportion) -> 'ok' when This::wxSizerItem(), Proportion::integer(). @@ -403,11 +357,7 @@ setProportion(#wx_ref{type=ThisT}=This,Proportion) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Proportion,?get_env(),?wxSizerItem_SetProportion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetratio">external documentation</a>. -%% <br /> Also:<br /> -%% setRatio(This, Size) -> 'ok' when<br /> -%% This::wxSizerItem(), Size::{W::integer(), H::integer()}.<br /> -%% +-doc "". -spec setRatio(This, Ratio) -> 'ok' when This::wxSizerItem(), Ratio::number(); (This, Size) -> 'ok' when @@ -421,7 +371,6 @@ setRatio(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Size,?get_env(),?wxSizerItem_SetRatio_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemsetratio">external documentation</a>. -doc "Set the ratio item attribute.". -spec setRatio(This, Width, Height) -> 'ok' when This::wxSizerItem(), Width::integer(), Height::integer(). @@ -430,7 +379,6 @@ setRatio(#wx_ref{type=ThisT}=This,Width,Height) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Width,Height,?get_env(),?wxSizerItem_SetRatio_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemassignsizer">external documentation</a>. -doc """ Set the sizer tracked by this item. @@ -443,7 +391,6 @@ assignSizer(#wx_ref{type=ThisT}=This,#wx_ref{type=SizerT}=Sizer) -> ?CLASS(SizerT,wxSizer), wxe_util:queue_cmd(This,Sizer,?get_env(),?wxSizerItem_AssignSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemassignspacer">external documentation</a>. -doc """ Set the size of the spacer tracked by this item. @@ -456,7 +403,7 @@ assignSpacer(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Size,?get_env(),?wxSizerItem_AssignSpacer_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemassignspacer">external documentation</a>. +-doc "". -spec assignSpacer(This, W, H) -> 'ok' when This::wxSizerItem(), W::integer(), H::integer(). assignSpacer(#wx_ref{type=ThisT}=This,W,H) @@ -464,23 +411,20 @@ assignSpacer(#wx_ref{type=ThisT}=This,W,H) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,W,H,?get_env(),?wxSizerItem_AssignSpacer_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemassignwindow">external documentation</a>. -doc """ Set the window to be tracked by this item. -Note: This is a low-level method which is dangerous if used incorrectly, avoid -using it if possible, i.e. if higher level methods such as `wxSizer:replace/4` -can be used instead. +Note: This is a low-level method which is dangerous if used incorrectly, avoid using it +if possible, i.e. if higher level methods such as `wxSizer:replace/4` can be used instead. -If the sizer item previously contained a window, it is dissociated from the -sizer containing this sizer item (if any), but this object doesn't have the -pointer to the containing sizer and so it's the caller's responsibility to call -`wxWindow:setContainingSizer/2` on `window`. Failure to do this can result in -memory corruption when the window is destroyed later, so it is crucial to not -forget to do it. +If the sizer item previously contained a window, it is dissociated from the sizer +containing this sizer item (if any), but this object doesn't have the pointer to the +containing sizer and so it's the caller's responsibility to call `wxWindow:setContainingSizer/2` on `window`. Failure to +do this can result in memory corruption when the window is destroyed later, so it is +crucial to not forget to do it. -Also note that the previously contained window is `not` deleted, so it's also -the callers responsibility to do it, if necessary. +Also note that the previously contained window is `not` deleted, so it's also the callers +responsibility to do it, if necessary. """. -spec assignWindow(This, Window) -> 'ok' when This::wxSizerItem(), Window::wxWindow:wxWindow(). @@ -489,10 +433,9 @@ assignWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxWindow), wxe_util:queue_cmd(This,Window,?get_env(),?wxSizerItem_AssignWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsizeritem.html#wxsizeritemshow">external documentation</a>. -doc """ -Set the show item attribute, which sizers use to determine if the item is to be -made part of the layout or not. +Set the show item attribute, which sizers use to determine if the item is to be made part +of the layout or not. If the item is tracking a window then it is shown or hidden as needed. """. @@ -503,8 +446,7 @@ show(#wx_ref{type=ThisT}=This,Show) ?CLASS(ThisT,wxSizerItem), wxe_util:queue_cmd(This,Show,?get_env(),?wxSizerItem_Show). -%% @doc Destroys this object, do not use object again --doc "Deletes the user data and subsizer, if any.". +-doc "Destroys the object". -spec destroy(This::wxSizerItem()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSizerItem), diff --git a/lib/wx/src/gen/wxSlider.erl b/lib/wx/src/gen/wxSlider.erl index 85b19b8b1929..ae9bb524e60b 100644 --- a/lib/wx/src/gen/wxSlider.erl +++ b/lib/wx/src/gen/wxSlider.erl @@ -20,62 +20,123 @@ -module(wxSlider). -moduledoc """ -Functions for wxSlider class - -A slider is a control with a handle which can be pulled back and forth to change -the value. +A slider is a control with a handle which can be pulled back and forth to change the +value. On Windows, the track bar control is used. On GTK+, tick marks are only available for version 2.16 and later. -Slider generates the same events as `m:wxScrollBar` but in practice the most -convenient way to process `m:wxSlider` updates is by handling the -slider-specific `wxEVT_SLIDER` event which carries `m:wxCommandEvent` containing -just the latest slider position. +Slider generates the same events as `m:wxScrollBar` but in practice the most convenient +way to process `m:wxSlider` updates is by handling the slider-specific `wxEVT_SLIDER` +event which carries `m:wxCommandEvent` containing just the latest slider position. -Styles +## Styles This class supports the following styles: +* wxSL_HORIZONTAL: Displays the slider horizontally (this is the default). + +* wxSL_VERTICAL: Displays the slider vertically. + +* wxSL_AUTOTICKS: Displays tick marks (Windows, GTK+ 2.16 and later). + +* wxSL_MIN_MAX_LABELS: Displays minimum, maximum labels (new since wxWidgets 2.9.1). + +* wxSL_VALUE_LABEL: Displays value label (new since wxWidgets 2.9.1). + +* wxSL_LABELS: Displays minimum, maximum and value labels (same as wxSL_VALUE_LABEL and +wxSL_MIN_MAX_LABELS together). + +* wxSL_LEFT: Displays ticks on the left and forces the slider to be vertical (Windows and +GTK+ 3 only). + +* wxSL_RIGHT: Displays ticks on the right and forces the slider to be vertical. + +* wxSL_TOP: Displays ticks on the top (Windows and GTK+ 3 only). + +* wxSL_BOTTOM: Displays ticks on the bottom (this is the default). + +* wxSL_BOTH: Displays ticks on both sides of the slider. Windows only. + +* wxSL_SELRANGE: Displays a highlighted selection range. Windows only. + +* wxSL_INVERSE: Inverses the minimum and maximum endpoints on the slider. Not compatible +with wxSL_SELRANGE. Notice that `wxSL_LEFT`, `wxSL_TOP`, `wxSL_RIGHT` and `wxSL_BOTTOM` +specify the position of the slider ticks and that the slider labels, if any, are +positioned on the opposite side. So, to have a label on the left side of a vertical +slider, `wxSL_RIGHT` must be used (or none of these styles at all should be specified as +left and top are default positions for the vertical and horizontal sliders respectively). + The difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED -The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the -thumb using the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is -also followed by an EVT_SCROLL_CHANGED event). +The EVT_SCROLL_THUMBRELEASE event is only emitted when actually dragging the thumb using +the mouse and releasing it (This EVT_SCROLL_THUMBRELEASE event is also followed by an +EVT_SCROLL_CHANGED event). -The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the -thumb position, and when clicking next to the thumb (In all these cases the -EVT_SCROLL_THUMBRELEASE event does not happen). In short, the EVT_SCROLL_CHANGED -event is triggered when scrolling/ moving has finished independently of the way -it had started. Please see the page_samples_widgets ("Slider" page) to see the -difference between EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. +The EVT_SCROLL_CHANGED event also occurs when using the keyboard to change the thumb +position, and when clicking next to the thumb (In all these cases the +EVT_SCROLL_THUMBRELEASE event does not happen). In short, the EVT_SCROLL_CHANGED event is +triggered when scrolling/ moving has finished independently of the way it had started. +Please see the page_samples_widgets ("Slider" page) to see the difference between +EVT_SCROLL_THUMBRELEASE and EVT_SCROLL_CHANGED in action. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxScrollBar` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxScrollBar` + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: [wxSlider](https://docs.wxwidgets.org/3.1/classwx_slider.html) +wxWidgets docs: [wxSlider](https://docs.wxwidgets.org/3.2/classwx_slider.html) ## Events -Event types emitted from this class: [`scroll_top`](`m:wxScrollEvent`), -[`scroll_bottom`](`m:wxScrollEvent`), [`scroll_lineup`](`m:wxScrollEvent`), -[`scroll_linedown`](`m:wxScrollEvent`), [`scroll_pageup`](`m:wxScrollEvent`), -[`scroll_pagedown`](`m:wxScrollEvent`), -[`scroll_thumbtrack`](`m:wxScrollEvent`), -[`scroll_thumbrelease`](`m:wxScrollEvent`), -[`scroll_changed`](`m:wxScrollEvent`), [`scroll_top`](`m:wxScrollEvent`), -[`scroll_bottom`](`m:wxScrollEvent`), [`scroll_lineup`](`m:wxScrollEvent`), -[`scroll_linedown`](`m:wxScrollEvent`), [`scroll_pageup`](`m:wxScrollEvent`), -[`scroll_pagedown`](`m:wxScrollEvent`), -[`scroll_thumbtrack`](`m:wxScrollEvent`), -[`scroll_thumbrelease`](`m:wxScrollEvent`), -[`scroll_changed`](`m:wxScrollEvent`), -[`command_slider_updated`](`m:wxCommandEvent`) +Event types emitted from this class: + +* [`scroll_top`](`m:wxScrollEvent`) + +* [`scroll_bottom`](`m:wxScrollEvent`) + +* [`scroll_lineup`](`m:wxScrollEvent`) + +* [`scroll_linedown`](`m:wxScrollEvent`) + +* [`scroll_pageup`](`m:wxScrollEvent`) + +* [`scroll_pagedown`](`m:wxScrollEvent`) + +* [`scroll_thumbtrack`](`m:wxScrollEvent`) + +* [`scroll_thumbrelease`](`m:wxScrollEvent`) + +* [`scroll_changed`](`m:wxScrollEvent`) + +* [`scroll_top`](`m:wxScrollEvent`) + +* [`scroll_bottom`](`m:wxScrollEvent`) + +* [`scroll_lineup`](`m:wxScrollEvent`) + +* [`scroll_linedown`](`m:wxScrollEvent`) + +* [`scroll_pageup`](`m:wxScrollEvent`) + +* [`scroll_pagedown`](`m:wxScrollEvent`) + +* [`scroll_thumbtrack`](`m:wxScrollEvent`) + +* [`scroll_thumbrelease`](`m:wxScrollEvent`) + +* [`scroll_changed`](`m:wxScrollEvent`) + +* [`command_slider_updated`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/6,create/7,destroy/1,getLineSize/1,getMax/1,getMin/1,getPageSize/1, @@ -124,21 +185,19 @@ Event types emitted from this class: [`scroll_top`](`m:wxScrollEvent`), -type wxSlider() :: wx:wx_object(). -export_type([wxSlider/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxsliderwxslider">external documentation</a>. -doc "Default constructor.". -spec new() -> wxSlider(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSlider_new_0), wxe_util:rec(?wxSlider_new_0). -%% @equiv new(Parent,Id,Value,MinValue,MaxValue, []) +-doc(#{equiv => new(Parent,Id,Value,MinValue,MaxValue, [])}). -spec new(Parent, Id, Value, MinValue, MaxValue) -> wxSlider() when Parent::wxWindow:wxWindow(), Id::integer(), Value::integer(), MinValue::integer(), MaxValue::integer(). @@ -146,11 +205,10 @@ new(Parent,Id,Value,MinValue,MaxValue) when is_record(Parent, wx_ref),is_integer(Id),is_integer(Value),is_integer(MinValue),is_integer(MaxValue) -> new(Parent,Id,Value,MinValue,MaxValue, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxsliderwxslider">external documentation</a>. -doc """ Constructor, creating and showing a slider. -See: `create/7`, `wxValidator` (not implemented in wx) +See: `create/7` """. -spec new(Parent, Id, Value, MinValue, MaxValue, [Option]) -> wxSlider() when Parent::wxWindow:wxWindow(), Id::integer(), Value::integer(), MinValue::integer(), MaxValue::integer(), @@ -170,7 +228,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Value,MinValue,MaxValue, Options) wxe_util:queue_cmd(Parent,Id,Value,MinValue,MaxValue, Opts,?get_env(),?wxSlider_new_6), wxe_util:rec(?wxSlider_new_6). -%% @equiv create(This,Parent,Id,Value,MinValue,MaxValue, []) +-doc(#{equiv => create(This,Parent,Id,Value,MinValue,MaxValue, [])}). -spec create(This, Parent, Id, Value, MinValue, MaxValue) -> boolean() when This::wxSlider(), Parent::wxWindow:wxWindow(), Id::integer(), Value::integer(), MinValue::integer(), MaxValue::integer(). @@ -178,7 +236,6 @@ create(This,Parent,Id,Value,MinValue,MaxValue) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_integer(Value),is_integer(MinValue),is_integer(MaxValue) -> create(This,Parent,Id,Value,MinValue,MaxValue, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidercreate">external documentation</a>. -doc """ Used for two-step slider construction. @@ -203,7 +260,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Value,MinValue,M wxe_util:queue_cmd(This,Parent,Id,Value,MinValue,MaxValue, Opts,?get_env(),?wxSlider_Create), wxe_util:rec(?wxSlider_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetlinesize">external documentation</a>. -doc """ Returns the line size. @@ -216,11 +272,13 @@ getLineSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetLineSize), wxe_util:rec(?wxSlider_GetLineSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetmax">external documentation</a>. -doc """ Gets the maximum slider value. -See: `getMin/1`, `setRange/3` +See: +* `getMin/1` + +* `setRange/3` """. -spec getMax(This) -> integer() when This::wxSlider(). @@ -229,11 +287,13 @@ getMax(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetMax), wxe_util:rec(?wxSlider_GetMax). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetmin">external documentation</a>. -doc """ Gets the minimum slider value. -See: `getMin/1`, `setRange/3` +See: +* `getMin/1` + +* `setRange/3` """. -spec getMin(This) -> integer() when This::wxSlider(). @@ -242,7 +302,6 @@ getMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetMin), wxe_util:rec(?wxSlider_GetMin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetpagesize">external documentation</a>. -doc """ Returns the page size. @@ -255,7 +314,6 @@ getPageSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetPageSize), wxe_util:rec(?wxSlider_GetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetthumblength">external documentation</a>. -doc """ Returns the thumb length. @@ -270,11 +328,15 @@ getThumbLength(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetThumbLength), wxe_util:rec(?wxSlider_GetThumbLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidergetvalue">external documentation</a>. -doc """ Gets the current slider value. -See: `getMin/1`, `getMax/1`, `setValue/2` +See: +* `getMin/1` + +* `getMax/1` + +* `setValue/2` """. -spec getValue(This) -> integer() when This::wxSlider(). @@ -283,7 +345,6 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSlider_GetValue), wxe_util:rec(?wxSlider_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidersetlinesize">external documentation</a>. -doc """ Sets the line size for the slider. @@ -296,7 +357,6 @@ setLineSize(#wx_ref{type=ThisT}=This,LineSize) ?CLASS(ThisT,wxSlider), wxe_util:queue_cmd(This,LineSize,?get_env(),?wxSlider_SetLineSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidersetpagesize">external documentation</a>. -doc """ Sets the page size for the slider. @@ -309,11 +369,13 @@ setPageSize(#wx_ref{type=ThisT}=This,PageSize) ?CLASS(ThisT,wxSlider), wxe_util:queue_cmd(This,PageSize,?get_env(),?wxSlider_SetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidersetrange">external documentation</a>. -doc """ Sets the minimum and maximum slider values. -See: `getMin/1`, `getMax/1` +See: +* `getMin/1` + +* `getMax/1` """. -spec setRange(This, MinValue, MaxValue) -> 'ok' when This::wxSlider(), MinValue::integer(), MaxValue::integer(). @@ -322,7 +384,6 @@ setRange(#wx_ref{type=ThisT}=This,MinValue,MaxValue) ?CLASS(ThisT,wxSlider), wxe_util:queue_cmd(This,MinValue,MaxValue,?get_env(),?wxSlider_SetRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidersetthumblength">external documentation</a>. -doc """ Sets the slider thumb length. @@ -337,7 +398,6 @@ setThumbLength(#wx_ref{type=ThisT}=This,Len) ?CLASS(ThisT,wxSlider), wxe_util:queue_cmd(This,Len,?get_env(),?wxSlider_SetThumbLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxslider.html#wxslidersetvalue">external documentation</a>. -doc "Sets the slider position.". -spec setValue(This, Value) -> 'ok' when This::wxSlider(), Value::integer(). @@ -346,562 +406,378 @@ setValue(#wx_ref{type=ThisT}=This,Value) ?CLASS(ThisT,wxSlider), wxe_util:queue_cmd(This,Value,?get_env(),?wxSlider_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the slider.". +-doc "Destroys the object". -spec destroy(This::wxSlider()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSlider), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSpinButton.erl b/lib/wx/src/gen/wxSpinButton.erl index b0e9893681ee..f923668010b6 100644 --- a/lib/wx/src/gen/wxSpinButton.erl +++ b/lib/wx/src/gen/wxSpinButton.erl @@ -20,36 +20,52 @@ -module(wxSpinButton). -moduledoc """ -Functions for wxSpinButton class - A `m:wxSpinButton` has two small up and down (or left and right) arrow buttons. -It is often used next to a text control for increment and decrementing a value. -Portable programs should try to use `m:wxSpinCtrl` instead as `m:wxSpinButton` -is not implemented for all platforms but `m:wxSpinCtrl` is as it degenerates to -a simple `m:wxTextCtrl` on such platforms. +It is often used next to a text control for increment and decrementing a value. Portable +programs should try to use `m:wxSpinCtrl` instead as `m:wxSpinButton` is not implemented +for all platforms but `m:wxSpinCtrl` is as it degenerates to a simple `m:wxTextCtrl` on +such platforms. -Note: the range supported by this control (and `m:wxSpinCtrl`) depends on the -platform but is at least `-0x8000` to `0x7fff`. Under GTK and Win32 with -sufficiently new version of `comctrl32.dll` (at least 4.71 is required, 5.80 is -recommended) the full 32 bit range is supported. +Note: the range supported by this control (and `m:wxSpinCtrl`) depends on the platform +but is at least `-0x8000` to `0x7fff`. Under GTK and Win32 with sufficiently new version +of `comctrl32.dll` (at least 4.71 is required, 5.80 is recommended) the full 32 bit range +is supported. -Styles +## Styles This class supports the following styles: +* wxSP_HORIZONTAL: Specifies a horizontal spin button (note that this style is not +supported in wxGTK). + +* wxSP_VERTICAL: Specifies a vertical spin button. + +* wxSP_ARROW_KEYS: The user can use arrow keys to change the value. + +* wxSP_WRAP: The value wraps at the minimum and maximum. + See: `m:wxSpinCtrl` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxControl` -wxWidgets docs: -[wxSpinButton](https://docs.wxwidgets.org/3.1/classwx_spin_button.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxSpinButton](https://docs.wxwidgets.org/3.2/classwx_spin_button.html) ## Events -Event types emitted from this class: [`spin`](`m:wxSpinEvent`), -[`spin_up`](`m:wxSpinEvent`), [`spin_down`](`m:wxSpinEvent`) +Event types emitted from this class: + +* [`spin`](`m:wxSpinEvent`) + +* [`spin_up`](`m:wxSpinEvent`) + +* [`spin_down`](`m:wxSpinEvent`) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getMax/1,getMin/1,getValue/1,new/0,new/1, @@ -97,21 +113,19 @@ Event types emitted from this class: [`spin`](`m:wxSpinEvent`), -type wxSpinButton() :: wx:wx_object(). -export_type([wxSpinButton/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttonwxspinbutton">external documentation</a>. -doc "Default constructor.". -spec new() -> wxSpinButton(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSpinButton_new_0), wxe_util:rec(?wxSpinButton_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxSpinButton() when Parent::wxWindow:wxWindow(). @@ -119,7 +133,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttonwxspinbutton">external documentation</a>. -doc """ Constructor, creating and showing a spin button. @@ -143,7 +156,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxSpinButton_new_2), wxe_util:rec(?wxSpinButton_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxSpinButton(), Parent::wxWindow:wxWindow(). @@ -151,7 +164,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttoncreate">external documentation</a>. -doc """ Scrollbar creation function called by the spin button constructor. @@ -176,7 +188,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxSpinButton_Create), wxe_util:rec(?wxSpinButton_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttongetmax">external documentation</a>. -doc """ Returns the maximum permissible value. @@ -189,7 +200,6 @@ getMax(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinButton_GetMax), wxe_util:rec(?wxSpinButton_GetMax). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttongetmin">external documentation</a>. -doc """ Returns the minimum permissible value. @@ -202,7 +212,6 @@ getMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinButton_GetMin), wxe_util:rec(?wxSpinButton_GetMin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttongetvalue">external documentation</a>. -doc """ Returns the current spin button value. @@ -215,16 +224,18 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinButton_GetValue), wxe_util:rec(?wxSpinButton_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttonsetrange">external documentation</a>. -doc """ Sets the range of the spin button. -In portable code, `min` should be less than or equal to `max`. In wxMSW it is -possible to specify minimum greater than maximum and the native control supports -the same range as if they were reversed, but swaps the meaning of up and down -arrows, however this dubious feature is not supported on other platforms. +In portable code, `min` should be less than or equal to `max`. In wxMSW it is possible to +specify minimum greater than maximum and the native control supports the same range as if +they were reversed, but swaps the meaning of up and down arrows, however this dubious +feature is not supported on other platforms. + +See: +* `getMin/1` -See: `getMin/1`, `getMax/1` +* `getMax/1` """. -spec setRange(This, Min, Max) -> 'ok' when This::wxSpinButton(), Min::integer(), Max::integer(). @@ -233,7 +244,6 @@ setRange(#wx_ref{type=ThisT}=This,Min,Max) ?CLASS(ThisT,wxSpinButton), wxe_util:queue_cmd(This,Min,Max,?get_env(),?wxSpinButton_SetRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinbutton.html#wxspinbuttonsetvalue">external documentation</a>. -doc "Sets the value of the spin button.". -spec setValue(This, Value) -> 'ok' when This::wxSpinButton(), Value::integer(). @@ -242,562 +252,378 @@ setValue(#wx_ref{type=ThisT}=This,Value) ?CLASS(ThisT,wxSpinButton), wxe_util:queue_cmd(This,Value,?get_env(),?wxSpinButton_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroys the spin button control.". +-doc "Destroys the object". -spec destroy(This::wxSpinButton()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSpinButton), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSpinCtrl.erl b/lib/wx/src/gen/wxSpinCtrl.erl index 9977f07c8ca2..a052060cfc22 100644 --- a/lib/wx/src/gen/wxSpinCtrl.erl +++ b/lib/wx/src/gen/wxSpinCtrl.erl @@ -20,26 +20,47 @@ -module(wxSpinCtrl). -moduledoc """ -Functions for wxSpinCtrl class - `m:wxSpinCtrl` combines `m:wxTextCtrl` and `m:wxSpinButton` in one control. -Styles +## Styles This class supports the following styles: -See: `m:wxSpinButton`, `wxSpinCtrlDouble` (not implemented in wx), `m:wxControl` +* wxSP_ARROW_KEYS: The user can use arrow keys to change the value. + +* wxSP_WRAP: The value wraps at the minimum and maximum. + +* wxTE_PROCESS_ENTER: Indicates that the control should generate `wxEVT_TEXT_ENTER` events. +Using this style will prevent the user from using the Enter key for dialog navigation +(e.g. activating the default button in the dialog) under MSW. + +* wxALIGN_LEFT: Same as wxTE_LEFT for `m:wxTextCtrl`: the text is left aligned (this is the +default). + +* wxALIGN_CENTRE_HORIZONTAL: Same as wxTE_CENTRE for `m:wxTextCtrl`: the text is centered. + +* wxALIGN_RIGHT: Same as wxTE_RIGHT for `m:wxTextCtrl`: the text is right aligned. -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +See: +* `m:wxSpinButton` -wxWidgets docs: -[wxSpinCtrl](https://docs.wxwidgets.org/3.1/classwx_spin_ctrl.html) +* `m:wxControl` + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxSpinCtrl](https://docs.wxwidgets.org/3.2/classwx_spin_ctrl.html) ## Events Event types emitted from this class: -[`command_spinctrl_updated`](`m:wxSpinEvent`) + +* [`command_spinctrl_updated`](`m:wxSpinEvent`) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getMax/1,getMin/1,getValue/1,new/0,new/1, @@ -87,21 +108,19 @@ Event types emitted from this class: -type wxSpinCtrl() :: wx:wx_object(). -export_type([wxSpinCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlwxspinctrl">external documentation</a>. -doc "Default constructor.". -spec new() -> wxSpinCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSpinCtrl_new_0), wxe_util:rec(?wxSpinCtrl_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxSpinCtrl() when Parent::wxWindow:wxWindow(). @@ -109,16 +128,14 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlwxspinctrl">external documentation</a>. -doc """ Constructor, creating and showing a spin control. -If `value` is non-empty, it will be shown in the text entry part of the control -and if it has numeric value, the initial numeric value of the control, as -returned by `getValue/1` will also be determined by it instead of by `initial`. -Hence, it only makes sense to specify `initial` if `value` is an empty string or -is not convertible to a number, otherwise `initial` is simply ignored and the -number specified by `value` is used. +If `value` is non-empty, it will be shown in the text entry part of the control and if it +has numeric value, the initial numeric value of the control, as returned by `getValue/1` will also be +determined by it instead of by `initial`. Hence, it only makes sense to specify `initial` +if `value` is an empty string or is not convertible to a number, otherwise `initial` is +simply ignored and the number specified by `value` is used. See: `create/3` """. @@ -148,7 +165,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxSpinCtrl_new_2), wxe_util:rec(?wxSpinCtrl_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxSpinCtrl(), Parent::wxWindow:wxWindow(). @@ -156,7 +173,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlcreate">external documentation</a>. -doc """ Creation function called by the spin control constructor. @@ -189,19 +205,14 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxSpinCtrl_Create), wxe_util:rec(?wxSpinCtrl_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlsetvalue">external documentation</a>. -%% <br /> Also:<br /> -%% setValue(This, Text) -> 'ok' when<br /> -%% This::wxSpinCtrl(), Text::unicode:chardata().<br /> -%% -doc """ Sets the value of the spin control. It is recommended to use the overload taking an integer value instead. -Notice that, unlike `wxTextCtrl:setValue/2`, but like most of the other setter -methods in wxWidgets, calling this method does not generate any events as events -are only generated for the user actions. +Notice that, unlike `wxTextCtrl:setValue/2`, but like most of the other setter methods in wxWidgets, calling +this method does not generate any events as events are only generated for the user +actions. """. -spec setValue(This, Value) -> 'ok' when This::wxSpinCtrl(), Value::integer(); @@ -217,7 +228,6 @@ setValue(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxSpinCtrl_SetValue_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlgetvalue">external documentation</a>. -doc "Gets the value of the spin control.". -spec getValue(This) -> integer() when This::wxSpinCtrl(). @@ -226,17 +236,15 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinCtrl_GetValue), wxe_util:rec(?wxSpinCtrl_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlsetrange">external documentation</a>. -doc """ Sets range of allowable values. -Notice that calling this method may change the value of the control if it's not -inside the new valid range, e.g. it will become `minVal` if it is less than it -now. However no `wxEVT_SPINCTRL` event is generated, even if it the value does -change. +Notice that calling this method may change the value of the control if it's not inside +the new valid range, e.g. it will become `minVal` if it is less than it now. However no `wxEVT_SPINCTRL` +event is generated, even if it the value does change. -Note: Setting a range including negative values is silently ignored if current -base is set to 16. +Note: Setting a range including negative values is silently ignored if current base is +set to 16. """. -spec setRange(This, MinVal, MaxVal) -> 'ok' when This::wxSpinCtrl(), MinVal::integer(), MaxVal::integer(). @@ -245,15 +253,13 @@ setRange(#wx_ref{type=ThisT}=This,MinVal,MaxVal) ?CLASS(ThisT,wxSpinCtrl), wxe_util:queue_cmd(This,MinVal,MaxVal,?get_env(),?wxSpinCtrl_SetRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlsetselection">external documentation</a>. -doc """ -Select the text in the text part of the control between positions `from` -(inclusive) and `to` (exclusive). +Select the text in the text part of the control between positions `from` (inclusive) and `to` +(exclusive). This is similar to `wxTextCtrl:setSelection/3`. -Note: this is currently only implemented for Windows and generic versions of the -control. +Note: this is currently only implemented for Windows and generic versions of the control. """. -spec setSelection(This, From, To) -> 'ok' when This::wxSpinCtrl(), From::integer(), To::integer(). @@ -262,7 +268,6 @@ setSelection(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxSpinCtrl), wxe_util:queue_cmd(This,From,To,?get_env(),?wxSpinCtrl_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlgetmin">external documentation</a>. -doc "Gets minimal allowable value.". -spec getMin(This) -> integer() when This::wxSpinCtrl(). @@ -271,7 +276,6 @@ getMin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinCtrl_GetMin), wxe_util:rec(?wxSpinCtrl_GetMin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinctrl.html#wxspinctrlgetmax">external documentation</a>. -doc "Gets maximal allowable value.". -spec getMax(This) -> integer() when This::wxSpinCtrl(). @@ -280,562 +284,378 @@ getMax(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinCtrl_GetMax), wxe_util:rec(?wxSpinCtrl_GetMax). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxSpinCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSpinCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSpinEvent.erl b/lib/wx/src/gen/wxSpinEvent.erl index 05827e6fe78f..ee60ce83c5d7 100644 --- a/lib/wx/src/gen/wxSpinEvent.erl +++ b/lib/wx/src/gen/wxSpinEvent.erl @@ -20,23 +20,26 @@ -module(wxSpinEvent). -moduledoc """ -Functions for wxSpinEvent class +This event class is used for the events generated by `m:wxSpinButton` and `m:wxSpinCtrl`. -This event class is used for the events generated by `m:wxSpinButton` and -`m:wxSpinCtrl`. +See: +* `m:wxSpinButton` -See: `m:wxSpinButton`, and, `m:wxSpinCtrl` +* `m:wxSpinCtrl` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxSpinEvent](https://docs.wxwidgets.org/3.1/classwx_spin_event.html) +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxSpinEvent](https://docs.wxwidgets.org/3.2/classwx_spin_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxSpinEventType`](`t:wxSpinEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxSpinEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getPosition/1,setPosition/2]). @@ -51,14 +54,12 @@ subscribe to events of this type. -include("wx.hrl"). -type wxSpinEventType() :: 'command_spinctrl_updated' | 'spin_up' | 'spin_down' | 'spin'. -export_type([wxSpinEvent/0, wxSpin/0, wxSpinEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinevent.html#wxspineventgetposition">external documentation</a>. -doc "Retrieve the current spin button or control value.". -spec getPosition(This) -> integer() when This::wxSpinEvent(). @@ -67,7 +68,6 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSpinEvent_GetPosition), wxe_util:rec(?wxSpinEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxspinevent.html#wxspineventsetposition">external documentation</a>. -doc "Set the value associated with the event.". -spec setPosition(This, Pos) -> 'ok' when This::wxSpinEvent(), Pos::integer(). @@ -77,68 +77,47 @@ setPosition(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxSpinEvent_SetPosition). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSplashScreen.erl b/lib/wx/src/gen/wxSplashScreen.erl index 44feca7d98bd..2b5095dc26c3 100644 --- a/lib/wx/src/gen/wxSplashScreen.erl +++ b/lib/wx/src/gen/wxSplashScreen.erl @@ -20,21 +20,24 @@ -module(wxSplashScreen). -moduledoc """ -Functions for wxSplashScreen class +`m:wxSplashScreen` shows a window with a thin border, displaying a bitmap describing your +application. -`m:wxSplashScreen` shows a window with a thin border, displaying a bitmap -describing your application. - -Show it in application initialisation, and then either explicitly destroy it or -let it time-out. +Show it in application initialisation, and then either explicitly destroy it or let it time-out. Example usage: -This class is derived (and can use functions) from: `m:wxFrame` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxFrame` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` -wxWidgets docs: -[wxSplashScreen](https://docs.wxwidgets.org/3.1/classwx_splash_screen.html) +wxWidgets docs: [wxSplashScreen](https://docs.wxwidgets.org/3.2/classwx_splash_screen.html) """. -include("wxe.hrl"). -export([destroy/1,getSplashStyle/1,getTimeout/1,new/5,new/6]). @@ -89,7 +92,6 @@ wxWidgets docs: -type wxSplashScreen() :: wx:wx_object(). -export_type([wxSplashScreen/0]). -%% @hidden -doc false. parent_class(wxFrame) -> true; parent_class(wxTopLevelWindow) -> true; @@ -97,7 +99,7 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Bitmap,SplashStyle,Milliseconds,Parent,Id, []) +-doc(#{equiv => new(Bitmap,SplashStyle,Milliseconds,Parent,Id, [])}). -spec new(Bitmap, SplashStyle, Milliseconds, Parent, Id) -> wxSplashScreen() when Bitmap::wxBitmap:wxBitmap(), SplashStyle::integer(), Milliseconds::integer(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -105,13 +107,22 @@ new(Bitmap,SplashStyle,Milliseconds,Parent,Id) when is_record(Bitmap, wx_ref),is_integer(SplashStyle),is_integer(Milliseconds),is_record(Parent, wx_ref),is_integer(Id) -> new(Bitmap,SplashStyle,Milliseconds,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplashscreen.html#wxsplashscreenwxsplashscreen">external documentation</a>. -doc """ -Construct the splash screen passing a bitmap, a style, a timeout, a window id, -optional position and size, and a window style. +Construct the splash screen passing a bitmap, a style, a timeout, a window id, optional +position and size, and a window style. `splashStyle` is a bitlist of some of the following: +* wxSPLASH_CENTRE_ON_PARENT + +* wxSPLASH_CENTRE_ON_SCREEN + +* wxSPLASH_NO_CENTRE + +* wxSPLASH_TIMEOUT + +* wxSPLASH_NO_TIMEOUT + `milliseconds` is the timeout in milliseconds. """. -spec new(Bitmap, SplashStyle, Milliseconds, Parent, Id, [Option]) -> wxSplashScreen() when @@ -131,7 +142,6 @@ new(#wx_ref{type=BitmapT}=Bitmap,SplashStyle,Milliseconds,#wx_ref{type=ParentT}= wxe_util:queue_cmd(Bitmap,SplashStyle,Milliseconds,Parent,Id, Opts,?get_env(),?wxSplashScreen_new), wxe_util:rec(?wxSplashScreen_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplashscreen.html#wxsplashscreengetsplashstyle">external documentation</a>. -doc "Returns the splash style (see `new/6` for details).". -spec getSplashStyle(This) -> integer() when This::wxSplashScreen(). @@ -140,7 +150,6 @@ getSplashStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplashScreen_GetSplashStyle), wxe_util:rec(?wxSplashScreen_GetSplashStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplashscreen.html#wxsplashscreengettimeout">external documentation</a>. -doc "Returns the timeout in milliseconds.". -spec getTimeout(This) -> integer() when This::wxSplashScreen(). @@ -149,689 +158,463 @@ getTimeout(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplashScreen_GetTimeout), wxe_util:rec(?wxSplashScreen_GetTimeout). -%% @doc Destroys this object, do not use object again --doc "Destroys the splash screen.". +-doc "Destroys the object". -spec destroy(This::wxSplashScreen()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSplashScreen), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxFrame -%% @hidden -doc false. setToolBar(This,ToolBar) -> wxFrame:setToolBar(This,ToolBar). -%% @hidden -doc false. setStatusWidths(This,Widths_field) -> wxFrame:setStatusWidths(This,Widths_field). -%% @hidden -doc false. setStatusText(This,Text, Options) -> wxFrame:setStatusText(This,Text, Options). -%% @hidden -doc false. setStatusText(This,Text) -> wxFrame:setStatusText(This,Text). -%% @hidden -doc false. setStatusBarPane(This,N) -> wxFrame:setStatusBarPane(This,N). -%% @hidden -doc false. setStatusBar(This,StatusBar) -> wxFrame:setStatusBar(This,StatusBar). -%% @hidden -doc false. setMenuBar(This,MenuBar) -> wxFrame:setMenuBar(This,MenuBar). -%% @hidden -doc false. sendSizeEvent(This, Options) -> wxFrame:sendSizeEvent(This, Options). -%% @hidden -doc false. sendSizeEvent(This) -> wxFrame:sendSizeEvent(This). -%% @hidden -doc false. processCommand(This,Id) -> wxFrame:processCommand(This,Id). -%% @hidden -doc false. getToolBar(This) -> wxFrame:getToolBar(This). -%% @hidden -doc false. getStatusBarPane(This) -> wxFrame:getStatusBarPane(This). -%% @hidden -doc false. getStatusBar(This) -> wxFrame:getStatusBar(This). -%% @hidden -doc false. getMenuBar(This) -> wxFrame:getMenuBar(This). -%% @hidden -doc false. getClientAreaOrigin(This) -> wxFrame:getClientAreaOrigin(This). -%% @hidden -doc false. createToolBar(This, Options) -> wxFrame:createToolBar(This, Options). -%% @hidden -doc false. createToolBar(This) -> wxFrame:createToolBar(This). -%% @hidden -doc false. createStatusBar(This, Options) -> wxFrame:createStatusBar(This, Options). -%% @hidden -doc false. createStatusBar(This) -> wxFrame:createStatusBar(This). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxSplitterEvent.erl b/lib/wx/src/gen/wxSplitterEvent.erl index 73fb9df78544..fc992e256ba0 100644 --- a/lib/wx/src/gen/wxSplitterEvent.erl +++ b/lib/wx/src/gen/wxSplitterEvent.erl @@ -20,30 +20,32 @@ -module(wxSplitterEvent). -moduledoc """ -Functions for wxSplitterEvent class - This class represents the events generated by a splitter control. -Also there is only one event class, the data associated to the different events -is not the same and so not all accessor functions may be called for each event. -The documentation mentions the kind of event(s) for which the given accessor -function makes sense: calling it for other types of events will result in assert -failure (in debug mode) and will return meaningless results. +Also there is only one event class, the data associated to the different events is not +the same and so not all accessor functions may be called for each event. The documentation +mentions the kind of event(s) for which the given accessor function makes sense: calling +it for other types of events will result in assert failure (in debug mode) and will return +meaningless results. + +See: +* `m:wxSplitterWindow` + +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +This class is derived, and can use functions, from: + +* `m:wxNotifyEvent` -See: `m:wxSplitterWindow`, -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxSplitterEvent](https://docs.wxwidgets.org/3.1/classwx_splitter_event.html) +wxWidgets docs: [wxSplitterEvent](https://docs.wxwidgets.org/3.2/classwx_splitter_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxSplitterEventType`](`t:wxSplitterEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxSplitterEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getSashPosition/1,getWindowBeingRemoved/1,getX/1,getY/1,setSashPosition/2]). @@ -58,19 +60,17 @@ this type. -include("wx.hrl"). -type wxSplitterEventType() :: 'command_splitter_sash_pos_changed' | 'command_splitter_sash_pos_changing' | 'command_splitter_doubleclicked' | 'command_splitter_unsplit'. -export_type([wxSplitterEvent/0, wxSplitter/0, wxSplitterEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterevent.html#wxsplittereventgetsashposition">external documentation</a>. -doc """ Returns the new sash position. -May only be called while processing `wxEVT_SPLITTER_SASH_POS_CHANGING` and -`wxEVT_SPLITTER_SASH_POS_CHANGED` events. +May only be called while processing `wxEVT_SPLITTER_SASH_POS_CHANGING` and `wxEVT_SPLITTER_SASH_POS_CHANGED` +events. """. -spec getSashPosition(This) -> integer() when This::wxSplitterEvent(). @@ -79,7 +79,6 @@ getSashPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterEvent_GetSashPosition), wxe_util:rec(?wxSplitterEvent_GetSashPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterevent.html#wxsplittereventgetx">external documentation</a>. -doc """ Returns the x coordinate of the double-click point. @@ -92,7 +91,6 @@ getX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterEvent_GetX), wxe_util:rec(?wxSplitterEvent_GetX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterevent.html#wxsplittereventgety">external documentation</a>. -doc """ Returns the y coordinate of the double-click point. @@ -105,7 +103,6 @@ getY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterEvent_GetY), wxe_util:rec(?wxSplitterEvent_GetY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterevent.html#wxsplittereventgetwindowbeingremoved">external documentation</a>. -doc """ Returns a pointer to the window being removed when a splitter window is unsplit. @@ -118,18 +115,15 @@ getWindowBeingRemoved(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterEvent_GetWindowBeingRemoved), wxe_util:rec(?wxSplitterEvent_GetWindowBeingRemoved). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterevent.html#wxsplittereventsetsashposition">external documentation</a>. -doc """ -In the case of `wxEVT_SPLITTER_SASH_POS_CHANGED` events, sets the new sash -position. +In the case of `wxEVT\_SPLITTER\_SASH\_POS\_CHANGED` events, sets the new sash position. -In the case of `wxEVT_SPLITTER_SASH_POS_CHANGING` events, sets the new tracking -bar position so visual feedback during dragging will represent that change that -will actually take place. Set to -1 from the event handler code to prevent -repositioning. +In the case of `wxEVT_SPLITTER_SASH_POS_CHANGING` events, sets the new tracking bar +position so visual feedback during dragging will represent that change that will actually +take place. Set to -1 from the event handler code to prevent repositioning. -May only be called while processing `wxEVT_SPLITTER_SASH_POS_CHANGING` and -`wxEVT_SPLITTER_SASH_POS_CHANGED` events. +May only be called while processing `wxEVT_SPLITTER_SASH_POS_CHANGING` and `wxEVT_SPLITTER_SASH_POS_CHANGED` +events. """. -spec setSashPosition(This, Pos) -> 'ok' when This::wxSplitterEvent(), Pos::integer(). @@ -139,68 +133,47 @@ setSashPosition(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxSplitterEvent_SetSashPosition). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSplitterWindow.erl b/lib/wx/src/gen/wxSplitterWindow.erl index 85cf2c1d8004..0c716f7bfb28 100644 --- a/lib/wx/src/gen/wxSplitterWindow.erl +++ b/lib/wx/src/gen/wxSplitterWindow.erl @@ -20,31 +20,57 @@ -module(wxSplitterWindow). -moduledoc """ -Functions for wxSplitterWindow class +This class manages up to two subwindows. -This class manages up to two subwindows. The current view can be split into two -programmatically (perhaps from a menu command), and unsplit either -programmatically or via the `m:wxSplitterWindow` user interface. +The current view can be split into two programmatically (perhaps from a menu command), +and unsplit either programmatically or via the `m:wxSplitterWindow` user interface. -Styles +## Styles This class supports the following styles: -See: `m:wxSplitterEvent`, -[Overview splitterwindow](https://docs.wxwidgets.org/3.1/overview_splitterwindow.html#overview_splitterwindow) +* wxSP_3D: Draws a 3D effect border and sash. -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* wxSP_THIN_SASH: Draws a thin sash. -wxWidgets docs: -[wxSplitterWindow](https://docs.wxwidgets.org/3.1/classwx_splitter_window.html) +* wxSP_3DSASH: Draws a 3D effect sash (part of default style). + +* wxSP_3DBORDER: Synonym for wxSP_BORDER. + +* wxSP_BORDER: Draws a standard border. + +* wxSP_NOBORDER: No border (default). + +* wxSP_NO_XP_THEME: Under Windows, switches off the attempt to draw the splitter using +Windows theming, so the borders and sash will take on the pre-XP look. + +* wxSP_PERMIT_UNSPLIT: Always allow to unsplit, even with the minimum pane size other than +zero. + +* wxSP_LIVE_UPDATE: Don't draw XOR line but resize the child windows immediately. + +See: +* `m:wxSplitterEvent` + +* [Overview splitterwindow](https://docs.wxwidgets.org/3.2/overview_splitterwindow.html#overview_splitterwindow) + +This class is derived, and can use functions, from: + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxSplitterWindow](https://docs.wxwidgets.org/3.2/classwx_splitter_window.html) ## Events Event types emitted from this class: -[`command_splitter_sash_pos_changing`](`m:wxSplitterEvent`), -[`command_splitter_sash_pos_changed`](`m:wxSplitterEvent`), -[`command_splitter_unsplit`](`m:wxSplitterEvent`) + +* [`command_splitter_sash_pos_changing`](`m:wxSplitterEvent`) + +* [`command_splitter_sash_pos_changed`](`m:wxSplitterEvent`) + +* [`command_splitter_unsplit`](`m:wxSplitterEvent`) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getMinimumPaneSize/1,getSashGravity/1, @@ -96,20 +122,18 @@ Event types emitted from this class: -type wxSplitterWindow() :: wx:wx_object(). -export_type([wxSplitterWindow/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowwxsplitterwindow">external documentation</a>. -doc "Default constructor.". -spec new() -> wxSplitterWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxSplitterWindow_new_0), wxe_util:rec(?wxSplitterWindow_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxSplitterWindow() when Parent::wxWindow:wxWindow(). @@ -117,17 +141,22 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowwxsplitterwindow">external documentation</a>. -doc """ Constructor for creating the window. -Remark: After using this constructor, you must create either one or two -subwindows with the splitter window as parent, and then call one of -`initialize/2`, `splitVertically/4` and `splitHorizontally/4` in order to set -the pane(s). You can create two windows, with one hidden when not being shown; -or you can create and delete the second pane on demand. +Remark: After using this constructor, you must create either one or two subwindows with +the splitter window as parent, and then call one of `initialize/2`, `splitVertically/4` and `splitHorizontally/4` in order to set the pane(s). +You can create two windows, with one hidden when not being shown; or you can create and +delete the second pane on demand. + +See: +* `initialize/2` -See: `initialize/2`, `splitVertically/4`, `splitHorizontally/4`, `create/3` +* `splitVertically/4` + +* `splitHorizontally/4` + +* `create/3` """. -spec new(Parent, [Option]) -> wxSplitterWindow() when Parent::wxWindow:wxWindow(), @@ -147,7 +176,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxSplitterWindow_new_2), wxe_util:rec(?wxSplitterWindow_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxSplitterWindow(), Parent::wxWindow:wxWindow(). @@ -155,7 +184,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowcreate">external documentation</a>. -doc """ Creation function, for two-step construction. @@ -180,7 +208,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxSplitterWindow_Create), wxe_util:rec(?wxSplitterWindow_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetminimumpanesize">external documentation</a>. -doc """ Returns the current minimum pane size (defaults to zero). @@ -193,7 +220,6 @@ getMinimumPaneSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetMinimumPaneSize), wxe_util:rec(?wxSplitterWindow_GetMinimumPaneSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetsashgravity">external documentation</a>. -doc """ Returns the current sash gravity. @@ -206,7 +232,6 @@ getSashGravity(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetSashGravity), wxe_util:rec(?wxSplitterWindow_GetSashGravity). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetsashposition">external documentation</a>. -doc """ Returns the current sash position. @@ -219,13 +244,17 @@ getSashPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetSashPosition), wxe_util:rec(?wxSplitterWindow_GetSashPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetsplitmode">external documentation</a>. -%%<br /> Res = ?wxSPLIT_HORIZONTAL | ?wxSPLIT_VERTICAL -doc """ Gets the split mode. -See: `setSplitMode/2`, `splitVertically/4`, `splitHorizontally/4` +See: +* `setSplitMode/2` + +* `splitVertically/4` + +* `splitHorizontally/4` """. +%% Res = ?wxSPLIT_HORIZONTAL | ?wxSPLIT_VERTICAL -spec getSplitMode(This) -> wx:wx_enum() when This::wxSplitterWindow(). getSplitMode(#wx_ref{type=ThisT}=This) -> @@ -233,7 +262,6 @@ getSplitMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetSplitMode), wxe_util:rec(?wxSplitterWindow_GetSplitMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetwindow1">external documentation</a>. -doc "Returns the left/top or only pane.". -spec getWindow1(This) -> wxWindow:wxWindow() when This::wxSplitterWindow(). @@ -242,7 +270,6 @@ getWindow1(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetWindow1), wxe_util:rec(?wxSplitterWindow_GetWindow1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowgetwindow2">external documentation</a>. -doc "Returns the right/bottom pane.". -spec getWindow2(This) -> wxWindow:wxWindow() when This::wxSplitterWindow(). @@ -251,16 +278,18 @@ getWindow2(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_GetWindow2), wxe_util:rec(?wxSplitterWindow_GetWindow2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowinitialize">external documentation</a>. -doc """ Initializes the splitter window to have one pane. The child window is shown if it is currently hidden. -Remark: This should be called if you wish to initially view only a single pane -in the splitter window. +Remark: This should be called if you wish to initially view only a single pane in the +splitter window. -See: `splitVertically/4`, `splitHorizontally/4` +See: +* `splitVertically/4` + +* `splitHorizontally/4` """. -spec initialize(This, Window) -> 'ok' when This::wxSplitterWindow(), Window::wxWindow:wxWindow(). @@ -269,7 +298,6 @@ initialize(#wx_ref{type=ThisT}=This,#wx_ref{type=WindowT}=Window) -> ?CLASS(WindowT,wxWindow), wxe_util:queue_cmd(This,Window,?get_env(),?wxSplitterWindow_Initialize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowissplit">external documentation</a>. -doc "Returns true if the window is split, false otherwise.". -spec isSplit(This) -> boolean() when This::wxSplitterWindow(). @@ -278,21 +306,18 @@ isSplit(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_IsSplit), wxe_util:rec(?wxSplitterWindow_IsSplit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowreplacewindow">external documentation</a>. -doc """ -This function replaces one of the windows managed by the `m:wxSplitterWindow` -with another one. +This function replaces one of the windows managed by the `m:wxSplitterWindow` with +another one. -It is in general better to use it instead of calling `unsplit/2` and then -resplitting the window back because it will provoke much less flicker (if any). -It is valid to call this function whether the splitter has two windows or only -one. +It is in general better to use it instead of calling `unsplit/2` and then resplitting the window +back because it will provoke much less flicker (if any). It is valid to call this function +whether the splitter has two windows or only one. -Both parameters should be non-NULL and `winOld` must specify one of the windows -managed by the splitter. If the parameters are incorrect or the window couldn't -be replaced, false is returned. Otherwise the function will return true, but -please notice that it will not delete the replaced window and you may wish to do -it yourself. +Both parameters should be non-NULL and `winOld` must specify one of the windows managed +by the splitter. If the parameters are incorrect or the window couldn't be replaced, false +is returned. Otherwise the function will return true, but please notice that it will not +delete the replaced window and you may wish to do it yourself. See: `getMinimumPaneSize/1` """. @@ -305,22 +330,27 @@ replaceWindow(#wx_ref{type=ThisT}=This,#wx_ref{type=WinOldT}=WinOld,#wx_ref{type wxe_util:queue_cmd(This,WinOld,WinNew,?get_env(),?wxSplitterWindow_ReplaceWindow), wxe_util:rec(?wxSplitterWindow_ReplaceWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsetsashgravity">external documentation</a>. -doc """ Sets the sash gravity. -Remark: Gravity is real factor which controls position of sash while resizing -`m:wxSplitterWindow`. Gravity tells `m:wxSplitterWindow` how much will left/top -window grow while resizing. Example values: +Remark: Gravity is real factor which controls position of sash while resizing `m:wxSplitterWindow`. +Gravity tells `m:wxSplitterWindow` how much will left/top window grow while resizing. +Example values: + +* 0.0: only the bottom/right window is automatically resized + +* 0.5: both windows grow by equal size + +* 1.0: only left/top window grows Gravity should be a real value between 0.0 and 1.0. +Default value of sash gravity is 0.0. That value is compatible with previous (before +gravity was introduced) behaviour of `m:wxSplitterWindow`. -Notice that when sash gravity for a newly created splitter window, it is often -necessary to explicitly set the splitter size using `wxWindow:setSize/6` to -ensure that is big enough for its initial sash position. Otherwise, i.e. if the -window is created with the default tiny size and only resized to its correct -size later, the initial sash position will be affected by the gravity and -typically result in sash being at the rightmost position for the gravity of 1. -See the example code creating `m:wxSplitterWindow` in the splitter sample for -more details. +Notice that when sash gravity for a newly created splitter window, it is often necessary +to explicitly set the splitter size using `wxWindow:setSize/6` to ensure that is big enough for its initial +sash position. Otherwise, i.e. if the window is created with the default tiny size and +only resized to its correct size later, the initial sash position will be affected by the +gravity and typically result in sash being at the rightmost position for the gravity of 1. +See the example code creating `m:wxSplitterWindow` in the splitter sample for more details. See: `getSashGravity/1` """. @@ -331,7 +361,7 @@ setSashGravity(#wx_ref{type=ThisT}=This,Gravity) ?CLASS(ThisT,wxSplitterWindow), wxe_util:queue_cmd(This,Gravity,?get_env(),?wxSplitterWindow_SetSashGravity). -%% @equiv setSashPosition(This,Position, []) +-doc(#{equiv => setSashPosition(This,Position, [])}). -spec setSashPosition(This, Position) -> 'ok' when This::wxSplitterWindow(), Position::integer(). @@ -339,7 +369,6 @@ setSashPosition(This,Position) when is_record(This, wx_ref),is_integer(Position) -> setSashPosition(This,Position, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsetsashposition">external documentation</a>. -doc """ Sets the sash position. @@ -358,16 +387,14 @@ setSashPosition(#wx_ref{type=ThisT}=This,Position, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Position, Opts,?get_env(),?wxSplitterWindow_SetSashPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsetminimumpanesize">external documentation</a>. -doc """ Sets the minimum pane size. -Remark: The default minimum pane size is zero, which means that either pane can -be reduced to zero by dragging the sash, thus removing one of the panes. To -prevent this behaviour (and veto out-of-range sash dragging), set a minimum -size, for example 20 pixels. If the wxSP_PERMIT_UNSPLIT style is used when a -splitter window is created, the window may be unsplit even if minimum size is -non-zero. +Remark: The default minimum pane size is zero, which means that either pane can be +reduced to zero by dragging the sash, thus removing one of the panes. To prevent this +behaviour (and veto out-of-range sash dragging), set a minimum size, for example 20 +pixels. If the wxSP_PERMIT_UNSPLIT style is used when a splitter window is created, the +window may be unsplit even if minimum size is non-zero. See: `getMinimumPaneSize/1` """. @@ -378,13 +405,17 @@ setMinimumPaneSize(#wx_ref{type=ThisT}=This,PaneSize) ?CLASS(ThisT,wxSplitterWindow), wxe_util:queue_cmd(This,PaneSize,?get_env(),?wxSplitterWindow_SetMinimumPaneSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsetsplitmode">external documentation</a>. -doc """ Sets the split mode. Remark: Only sets the internal variable; does not update the display. -See: `getSplitMode/1`, `splitVertically/4`, `splitHorizontally/4` +See: +* `getSplitMode/1` + +* `splitVertically/4` + +* `splitHorizontally/4` """. -spec setSplitMode(This, Mode) -> 'ok' when This::wxSplitterWindow(), Mode::integer(). @@ -393,7 +424,7 @@ setSplitMode(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxSplitterWindow), wxe_util:queue_cmd(This,Mode,?get_env(),?wxSplitterWindow_SetSplitMode). -%% @equiv splitHorizontally(This,Window1,Window2, []) +-doc(#{equiv => splitHorizontally(This,Window1,Window2, [])}). -spec splitHorizontally(This, Window1, Window2) -> boolean() when This::wxSplitterWindow(), Window1::wxWindow:wxWindow(), Window2::wxWindow:wxWindow(). @@ -401,7 +432,6 @@ splitHorizontally(This,Window1,Window2) when is_record(This, wx_ref),is_record(Window1, wx_ref),is_record(Window2, wx_ref) -> splitHorizontally(This,Window1,Window2, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsplithorizontally">external documentation</a>. -doc """ Initializes the top and bottom panes of the splitter window. @@ -409,11 +439,16 @@ The child windows are shown if they are currently hidden. Return: true if successful, false otherwise (the window was already split). -Remark: This should be called if you wish to initially view two panes. It can -also be called at any subsequent time, but the application should check that the -window is not currently split using `isSplit/1`. +Remark: This should be called if you wish to initially view two panes. It can also be +called at any subsequent time, but the application should check that the window is not +currently split using `isSplit/1`. + +See: +* `splitVertically/4` + +* `isSplit/1` -See: `splitVertically/4`, `isSplit/1`, `unsplit/2` +* `unsplit/2` """. -spec splitHorizontally(This, Window1, Window2, [Option]) -> boolean() when This::wxSplitterWindow(), Window1::wxWindow:wxWindow(), Window2::wxWindow:wxWindow(), @@ -429,7 +464,7 @@ splitHorizontally(#wx_ref{type=ThisT}=This,#wx_ref{type=Window1T}=Window1,#wx_re wxe_util:queue_cmd(This,Window1,Window2, Opts,?get_env(),?wxSplitterWindow_SplitHorizontally), wxe_util:rec(?wxSplitterWindow_SplitHorizontally). -%% @equiv splitVertically(This,Window1,Window2, []) +-doc(#{equiv => splitVertically(This,Window1,Window2, [])}). -spec splitVertically(This, Window1, Window2) -> boolean() when This::wxSplitterWindow(), Window1::wxWindow:wxWindow(), Window2::wxWindow:wxWindow(). @@ -437,7 +472,6 @@ splitVertically(This,Window1,Window2) when is_record(This, wx_ref),is_record(Window1, wx_ref),is_record(Window2, wx_ref) -> splitVertically(This,Window1,Window2, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowsplitvertically">external documentation</a>. -doc """ Initializes the left and right panes of the splitter window. @@ -445,11 +479,16 @@ The child windows are shown if they are currently hidden. Return: true if successful, false otherwise (the window was already split). -Remark: This should be called if you wish to initially view two panes. It can -also be called at any subsequent time, but the application should check that the -window is not currently split using `isSplit/1`. +Remark: This should be called if you wish to initially view two panes. It can also be +called at any subsequent time, but the application should check that the window is not +currently split using `isSplit/1`. -See: `splitHorizontally/4`, `isSplit/1`, `unsplit/2` +See: +* `splitHorizontally/4` + +* `isSplit/1` + +* `unsplit/2` """. -spec splitVertically(This, Window1, Window2, [Option]) -> boolean() when This::wxSplitterWindow(), Window1::wxWindow:wxWindow(), Window2::wxWindow:wxWindow(), @@ -465,7 +504,7 @@ splitVertically(#wx_ref{type=ThisT}=This,#wx_ref{type=Window1T}=Window1,#wx_ref{ wxe_util:queue_cmd(This,Window1,Window2, Opts,?get_env(),?wxSplitterWindow_SplitVertically), wxe_util:rec(?wxSplitterWindow_SplitVertically). -%% @equiv unsplit(This, []) +-doc(#{equiv => unsplit(This, [])}). -spec unsplit(This) -> boolean() when This::wxSplitterWindow(). @@ -473,18 +512,21 @@ unsplit(This) when is_record(This, wx_ref) -> unsplit(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowunsplit">external documentation</a>. -doc """ Unsplits the window. Return: true if successful, false otherwise (the window was not split). -Remark: This call will not actually delete the pane being removed; it calls -`OnUnsplit()` (not implemented in wx) which can be overridden for the desired -behaviour. By default, the pane being removed is hidden. +Remark: This call will not actually delete the pane being removed; it calls `OnUnsplit()` +(not implemented in wx) which can be overridden for the desired behaviour. By default, the +pane being removed is hidden. + +See: +* `splitHorizontally/4` + +* `splitVertically/4` -See: `splitHorizontally/4`, `splitVertically/4`, `isSplit/1`, `OnUnsplit()` (not -implemented in wx) +* `isSplit/1` """. -spec unsplit(This, [Option]) -> boolean() when This::wxSplitterWindow(), @@ -498,15 +540,14 @@ unsplit(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxSplitterWindow_Unsplit), wxe_util:rec(?wxSplitterWindow_Unsplit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsplitterwindow.html#wxsplitterwindowupdatesize">external documentation</a>. -doc """ Causes any pending sizing of the sash and child panes to take place immediately. -Such resizing normally takes place in idle time, in order to wait for layout to -be completed. However, this can cause unacceptable flicker as the panes are -resized after the window has been shown. To work around this, you can perform -window layout (for example by sending a size event to the parent window), and -then call this function, before showing the top-level window. +Such resizing normally takes place in idle time, in order to wait for layout to be +completed. However, this can cause unacceptable flicker as the panes are resized after the +window has been shown. To work around this, you can perform window layout (for example by +sending a size event to the parent window), and then call this function, before showing +the top-level window. """. -spec updateSize(This) -> 'ok' when This::wxSplitterWindow(). @@ -514,561 +555,377 @@ updateSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxSplitterWindow), wxe_util:queue_cmd(This,?get_env(),?wxSplitterWindow_UpdateSize). -%% @doc Destroys this object, do not use object again --doc "Destroys the `m:wxSplitterWindow` and its children.". +-doc "Destroys the object". -spec destroy(This::wxSplitterWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxSplitterWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStaticBitmap.erl b/lib/wx/src/gen/wxStaticBitmap.erl index a1537f0e9ce2..011574b26916 100644 --- a/lib/wx/src/gen/wxStaticBitmap.erl +++ b/lib/wx/src/gen/wxStaticBitmap.erl @@ -20,28 +20,31 @@ -module(wxStaticBitmap). -moduledoc """ -Functions for wxStaticBitmap class +A static bitmap control displays a bitmap. -A static bitmap control displays a bitmap. Native implementations on some -platforms are only meant for display of the small icons in the dialog boxes. +Native implementations on some platforms are only meant for display of the small icons in +the dialog boxes. -If you want to display larger images portably, you may use generic -implementation wxGenericStaticBitmap declared in <wx/generic/statbmpg.h>. +If you want to display larger images portably, you may use generic implementation +wxGenericStaticBitmap declared in <wx/generic/statbmpg.h>. -Notice that for the best results, the size of the control should be the same as -the size of the image displayed in it, as happens by default if it's not resized -explicitly. Otherwise, behaviour depends on the platform: under MSW, the bitmap -is drawn centred inside the control, while elsewhere it is drawn at the origin -of the control. You can use `SetScaleMode()` (not implemented in wx) to control -how the image is scaled inside the control. +Notice that for the best results, the size of the control should be the same as the size +of the image displayed in it, as happens by default if it's not resized explicitly. +Otherwise, behaviour depends on the platform: under MSW, the bitmap is drawn centred +inside the control, while elsewhere it is drawn at the origin of the control. You can use `SetScaleMode()` +(not implemented in wx) to control how the image is scaled inside the control. See: `m:wxBitmap` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxStaticBitmap](https://docs.wxwidgets.org/3.1/classwx_static_bitmap.html) +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxStaticBitmap](https://docs.wxwidgets.org/3.2/classwx_static_bitmap.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getBitmap/1,new/0,new/3,new/4,setBitmap/2]). @@ -88,21 +91,19 @@ wxWidgets docs: -type wxStaticBitmap() :: wx:wx_object(). -export_type([wxStaticBitmap/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbitmap.html#wxstaticbitmapwxstaticbitmap">external documentation</a>. -doc "Default constructor.". -spec new() -> wxStaticBitmap(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStaticBitmap_new_0), wxe_util:rec(?wxStaticBitmap_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxStaticBitmap() when Parent::wxWindow:wxWindow(), Id::integer(), Label::wxBitmap:wxBitmap(). @@ -110,7 +111,6 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),is_record(Label, wx_ref) -> new(Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbitmap.html#wxstaticbitmapwxstaticbitmap">external documentation</a>. -doc """ Constructor, creating and showing a static bitmap control. @@ -133,7 +133,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,#wx_ref{type=LabelT}=Label, Options) wxe_util:queue_cmd(Parent,Id,Label, Opts,?get_env(),?wxStaticBitmap_new_4), wxe_util:rec(?wxStaticBitmap_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxStaticBitmap(), Parent::wxWindow:wxWindow(), Id::integer(), Label::wxBitmap:wxBitmap(). @@ -141,7 +141,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),is_record(Label, wx_ref) -> create(This,Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbitmap.html#wxstaticbitmapcreate">external documentation</a>. -doc """ Creation function, for two-step construction. @@ -165,12 +164,11 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,#wx_ref{type=Lab wxe_util:queue_cmd(This,Parent,Id,Label, Opts,?get_env(),?wxStaticBitmap_Create), wxe_util:rec(?wxStaticBitmap_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbitmap.html#wxstaticbitmapgetbitmap">external documentation</a>. -doc """ Returns the bitmap currently used in the control. -Notice that this method can be called even if `SetIcon()` (not implemented in -wx) had been used. +Notice that this method can be called even if `SetIcon()` (not implemented in wx) had +been used. See: `setBitmap/2` """. @@ -181,7 +179,6 @@ getBitmap(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStaticBitmap_GetBitmap), wxe_util:rec(?wxStaticBitmap_GetBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbitmap.html#wxstaticbitmapsetbitmap">external documentation</a>. -doc """ Sets the bitmap label. @@ -194,562 +191,378 @@ setBitmap(#wx_ref{type=ThisT}=This,#wx_ref{type=LabelT}=Label) -> ?CLASS(LabelT,wxBitmap), wxe_util:queue_cmd(This,Label,?get_env(),?wxStaticBitmap_SetBitmap). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxStaticBitmap()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStaticBitmap), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStaticBox.erl b/lib/wx/src/gen/wxStaticBox.erl index 6d060f612b71..6843072836b5 100644 --- a/lib/wx/src/gen/wxStaticBox.erl +++ b/lib/wx/src/gen/wxStaticBox.erl @@ -20,31 +20,36 @@ -module(wxStaticBox). -moduledoc """ -Functions for wxStaticBox class +A static box is a rectangle drawn around other windows to denote a logical grouping of +items. -A static box is a rectangle drawn around other windows to denote a logical -grouping of items. - -Note that while the previous versions required that windows appearing inside a -static box be created as its siblings (i.e. use the same parent as the static -box itself), since wxWidgets 2.9.1 it is also possible to create them as -children of `m:wxStaticBox` itself and you are actually encouraged to do it like -this if compatibility with the previous versions is not important. +Note that while the previous versions required that windows appearing inside a static box +be created as its siblings (i.e. use the same parent as the static box itself), since +wxWidgets 2.9.1 it is also possible to create them as children of `m:wxStaticBox` itself +and you are actually encouraged to do it like this if compatibility with the previous +versions is not important. So the new recommended way to create static box is: While the compatible - and now deprecated - way is -Also note that there is a specialized `m:wxSizer` class (`m:wxStaticBoxSizer`) -which can be used as an easier way to pack items into a static box. +Also note that there is a specialized `m:wxSizer` class (`m:wxStaticBoxSizer`) which can +be used as an easier way to pack items into a static box. + +See: +* `m:wxStaticText` + +* `m:wxStaticBoxSizer` -See: `m:wxStaticText`, `m:wxStaticBoxSizer` +This class is derived, and can use functions, from: -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxControl` -wxWidgets docs: -[wxStaticBox](https://docs.wxwidgets.org/3.1/classwx_static_box.html) +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxStaticBox](https://docs.wxwidgets.org/3.2/classwx_static_box.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,new/0,new/3,new/4]). @@ -91,21 +96,19 @@ wxWidgets docs: -type wxStaticBox() :: wx:wx_object(). -export_type([wxStaticBox/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbox.html#wxstaticboxwxstaticbox">external documentation</a>. -doc "Default constructor.". -spec new() -> wxStaticBox(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStaticBox_new_0), wxe_util:rec(?wxStaticBox_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxStaticBox() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -113,7 +116,6 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> new(Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbox.html#wxstaticboxwxstaticbox">external documentation</a>. -doc """ Constructor, creating and showing a static box. @@ -136,7 +138,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(Parent,Id,Label_UC, Opts,?get_env(),?wxStaticBox_new_4), wxe_util:rec(?wxStaticBox_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxStaticBox(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -144,7 +146,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> create(This,Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticbox.html#wxstaticboxcreate">external documentation</a>. -doc """ Creates the static box for two-step construction. @@ -168,581 +169,378 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(This,Parent,Id,Label_UC, Opts,?get_env(),?wxStaticBox_Create), wxe_util:rec(?wxStaticBox_Create). -%% @doc Destroys this object, do not use object again --doc """ -Constructor for a static box using the given window as label. - -This constructor takes a pointer to an arbitrary window (although usually a -`m:wxCheckBox` or a `m:wxRadioButton`) instead of just the usual text label and -puts this window at the top of the box at the place where the label would be -shown. - -The `label` window must be a non-null, fully created window and will become a -child of this `m:wxStaticBox`, i.e. it will be owned by this control and will be -deleted when the `m:wxStaticBox` itself is deleted. - -An example of creating a `m:wxStaticBox` with window as a label: - -Currently this constructor is only available in wxGTK and wxMSW, use -`wxHAS_WINDOW_LABEL_IN_STATIC_BOX` to check whether it can be used at -compile-time. - -Since: 3.1.1 Destructor, destroying the group box. -""". +-doc "Destroys the object". -spec destroy(This::wxStaticBox()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStaticBox), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStaticBoxSizer.erl b/lib/wx/src/gen/wxStaticBoxSizer.erl index b2acceb7628f..36d69edf714f 100644 --- a/lib/wx/src/gen/wxStaticBoxSizer.erl +++ b/lib/wx/src/gen/wxStaticBoxSizer.erl @@ -20,28 +20,35 @@ -module(wxStaticBoxSizer). -moduledoc """ -Functions for wxStaticBoxSizer class +`m:wxStaticBoxSizer` is a sizer derived from `m:wxBoxSizer` but adds a static box around +the sizer. -`m:wxStaticBoxSizer` is a sizer derived from `m:wxBoxSizer` but adds a static -box around the sizer. +The static box may be either created independently or the sizer may create it itself as a +convenience. In any case, the sizer owns the `m:wxStaticBox` control and will delete it in +the `m:wxStaticBoxSizer` destructor. -The static box may be either created independently or the sizer may create it -itself as a convenience. In any case, the sizer owns the `m:wxStaticBox` control -and will delete it in the `m:wxStaticBoxSizer` destructor. - -Note that since wxWidgets 2.9.1 you are encouraged to create the windows which -are added to `m:wxStaticBoxSizer` as children of `m:wxStaticBox` itself, see -this class documentation for more details. +Note that since wxWidgets 2.9.1 you are encouraged to create the windows which are added +to `m:wxStaticBoxSizer` as children of `m:wxStaticBox` itself, see this class +documentation for more details. Example of use of this class: -See: `m:wxSizer`, `m:wxStaticBox`, `m:wxBoxSizer`, -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer) +See: +* `m:wxSizer` + +* `m:wxStaticBox` + +* `m:wxBoxSizer` + +* [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) -This class is derived (and can use functions) from: `m:wxBoxSizer` `m:wxSizer` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxStaticBoxSizer](https://docs.wxwidgets.org/3.1/classwx_static_box_sizer.html) +* `m:wxBoxSizer` + +* `m:wxSizer` + +wxWidgets docs: [wxStaticBoxSizer](https://docs.wxwidgets.org/3.2/classwx_static_box_sizer.html) """. -include("wxe.hrl"). -export([destroy/1,getStaticBox/1,new/2,new/3]). @@ -59,17 +66,11 @@ wxWidgets docs: -type wxStaticBoxSizer() :: wx:wx_object(). -export_type([wxStaticBoxSizer/0]). -%% @hidden -doc false. parent_class(wxBoxSizer) -> true; parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticboxsizer.html#wxstaticboxsizerwxstaticboxsizer">external documentation</a>. -%% <br /> Also:<br /> -%% new(Box, Orient) -> wxStaticBoxSizer() when<br /> -%% Box::wxStaticBox:wxStaticBox(), Orient::integer().<br /> -%% -doc "This constructor uses an already existing static box.". -spec new(Orient, Parent) -> wxStaticBoxSizer() when Orient::integer(), Parent::wxWindow:wxWindow(); @@ -85,11 +86,7 @@ new(#wx_ref{type=BoxT}=Box,Orient) wxe_util:queue_cmd(Box,Orient,?get_env(),?wxStaticBoxSizer_new_2), wxe_util:rec(?wxStaticBoxSizer_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticboxsizer.html#wxstaticboxsizerwxstaticboxsizer">external documentation</a>. --doc """ -This constructor creates a new static box with the given label and parent -window. -""". +-doc "This constructor creates a new static box with the given label and parent window.". -spec new(Orient, Parent, [Option]) -> wxStaticBoxSizer() when Orient::integer(), Parent::wxWindow:wxWindow(), Option :: {'label', unicode:chardata()}. @@ -102,7 +99,6 @@ new(Orient,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Orient,Parent, Opts,?get_env(),?wxStaticBoxSizer_new_3), wxe_util:rec(?wxStaticBoxSizer_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticboxsizer.html#wxstaticboxsizergetstaticbox">external documentation</a>. -doc "Returns the static box associated with the sizer.". -spec getStaticBox(This) -> wxStaticBox:wxStaticBox() when This::wxStaticBoxSizer(). @@ -111,162 +107,111 @@ getStaticBox(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStaticBoxSizer_GetStaticBox), wxe_util:rec(?wxStaticBoxSizer_GetStaticBox). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxStaticBoxSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStaticBoxSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBoxSizer -%% @hidden -doc false. getOrientation(This) -> wxBoxSizer:getOrientation(This). %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. calcMin(This) -> wxSizer:calcMin(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). -%% @hidden -doc false. add(This,Width,Height, Options) -> wxSizer:add(This,Width,Height, Options). -%% @hidden -doc false. add(This,Width,Height) -> wxSizer:add(This,Width,Height). -%% @hidden -doc false. add(This,Window) -> wxSizer:add(This,Window). diff --git a/lib/wx/src/gen/wxStaticLine.erl b/lib/wx/src/gen/wxStaticLine.erl index 90dfc2e51042..231458ec8859 100644 --- a/lib/wx/src/gen/wxStaticLine.erl +++ b/lib/wx/src/gen/wxStaticLine.erl @@ -20,27 +20,32 @@ -module(wxStaticLine). -moduledoc """ -Functions for wxStaticLine class +A static line is just a line which may be used in a dialog to separate the groups of +controls. -A static line is just a line which may be used in a dialog to separate the -groups of controls. +The line may be only vertical or horizontal. Moreover, not all ports (notably not wxGTK) +support specifying the transversal direction of the line (e.g. height for a horizontal +line) so for maximal portability you should specify it as wxDefaultCoord. -The line may be only vertical or horizontal. Moreover, not all ports (notably -not wxGTK) support specifying the transversal direction of the line (e.g. height -for a horizontal line) so for maximal portability you should specify it as -wxDefaultCoord. - -Styles +## Styles This class supports the following styles: +* wxLI_HORIZONTAL: Creates a horizontal line. + +* wxLI_VERTICAL: Creates a vertical line. + See: `m:wxStaticBox` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` -wxWidgets docs: -[wxStaticLine](https://docs.wxwidgets.org/3.1/classwx_static_line.html) +wxWidgets docs: [wxStaticLine](https://docs.wxwidgets.org/3.2/classwx_static_line.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getDefaultSize/0,isVertical/1,new/0,new/1, @@ -88,21 +93,19 @@ wxWidgets docs: -type wxStaticLine() :: wx:wx_object(). -export_type([wxStaticLine/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticline.html#wxstaticlinewxstaticline">external documentation</a>. -doc "Default constructor.". -spec new() -> wxStaticLine(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStaticLine_new_0), wxe_util:rec(?wxStaticLine_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxStaticLine() when Parent::wxWindow:wxWindow(). @@ -110,7 +113,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticline.html#wxstaticlinewxstaticline">external documentation</a>. -doc """ Constructor, creating and showing a static line. @@ -134,7 +136,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxStaticLine_new_2), wxe_util:rec(?wxStaticLine_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxStaticLine(), Parent::wxWindow:wxWindow(). @@ -142,7 +144,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticline.html#wxstaticlinecreate">external documentation</a>. -doc """ Creates the static line for two-step construction. @@ -167,7 +168,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxStaticLine_Create), wxe_util:rec(?wxStaticLine_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticline.html#wxstaticlineisvertical">external documentation</a>. -doc "Returns true if the line is vertical, false if horizontal.". -spec isVertical(This) -> boolean() when This::wxStaticLine(). @@ -176,10 +176,9 @@ isVertical(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStaticLine_IsVertical), wxe_util:rec(?wxStaticLine_IsVertical). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstaticline.html#wxstaticlinegetdefaultsize">external documentation</a>. -doc """ -This static function returns the size which will be given to the smaller -dimension of the static line, i.e. +This static function returns the size which will be given to the smaller dimension of the +static line, i.e. its height for a horizontal line or its width for a vertical one. """. @@ -188,562 +187,378 @@ getDefaultSize() -> wxe_util:queue_cmd(?get_env(), ?wxStaticLine_GetDefaultSize), wxe_util:rec(?wxStaticLine_GetDefaultSize). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxStaticLine()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStaticLine), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStaticText.erl b/lib/wx/src/gen/wxStaticText.erl index 14158ab9abd2..851806d78130 100644 --- a/lib/wx/src/gen/wxStaticText.erl +++ b/lib/wx/src/gen/wxStaticText.erl @@ -20,25 +20,53 @@ -module(wxStaticText). -moduledoc """ -Functions for wxStaticText class - A static text control displays one or more lines of read-only text. -`m:wxStaticText` supports the three classic text alignments, label ellipsization -i.e. replacing parts of the text with the ellipsis ("...") if the label doesn't -fit into the provided space and also formatting markup with -`wxControl::SetLabelMarkup()` (not implemented in wx). -Styles +`m:wxStaticText` supports the three classic text alignments, label ellipsization i.e. +replacing parts of the text with the ellipsis ("...") if the label doesn't fit into the +provided space and also formatting markup with `wxControl::SetLabelMarkup()` (not +implemented in wx). + +## Styles This class supports the following styles: -See: `m:wxStaticBitmap`, `m:wxStaticBox` +* wxALIGN_LEFT: Align the text to the left. + +* wxALIGN_RIGHT: Align the text to the right. + +* wxALIGN_CENTRE_HORIZONTAL: Center the text (horizontally). + +* wxST_NO_AUTORESIZE: By default, the control will adjust its size to exactly fit to the +size of the text when `setLabel/2` is called. If this style flag is given, the control will not change +its size (this style is especially useful with controls which also have the `wxALIGN_RIGHT` +or the `wxALIGN_CENTRE_HORIZONTAL` style because otherwise they won't make sense any +longer after a call to `setLabel/2`). + +* wxST_ELLIPSIZE_START: If the labeltext width exceeds the control width, replace the +beginning of the label with an ellipsis; uses `wxControl::Ellipsize` (not implemented in +wx). + +* wxST_ELLIPSIZE_MIDDLE: If the label text width exceeds the control width, replace the +middle of the label with an ellipsis; uses `wxControl::Ellipsize` (not implemented in wx). + +* wxST_ELLIPSIZE_END: If the label text width exceeds the control width, replace the end of +the label with an ellipsis; uses `wxControl::Ellipsize` (not implemented in wx). + +See: +* `m:wxStaticBitmap` + +* `m:wxStaticBox` + +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxStaticText](https://docs.wxwidgets.org/3.1/classwx_static_text.html) +wxWidgets docs: [wxStaticText](https://docs.wxwidgets.org/3.2/classwx_static_text.html) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getLabel/1,new/0,new/3,new/4,setLabel/2,wrap/2]). @@ -84,21 +112,19 @@ wxWidgets docs: -type wxStaticText() :: wx:wx_object(). -export_type([wxStaticText/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextwxstatictext">external documentation</a>. -doc "Default constructor.". -spec new() -> wxStaticText(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStaticText_new_0), wxe_util:rec(?wxStaticText_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxStaticText() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -106,7 +132,6 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> new(Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextwxstatictext">external documentation</a>. -doc """ Constructor, creating and showing a text control. @@ -129,7 +154,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(Parent,Id,Label_UC, Opts,?get_env(),?wxStaticText_new_4), wxe_util:rec(?wxStaticText_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxStaticText(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -137,7 +162,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> create(This,Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextcreate">external documentation</a>. -doc """ Creation function, for two-step construction. @@ -161,18 +185,15 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(This,Parent,Id,Label_UC, Opts,?get_env(),?wxStaticText_Create), wxe_util:rec(?wxStaticText_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextgetlabel">external documentation</a>. -doc """ Returns the control's label, as it was passed to `wxControl:setLabel/2`. -Note that the returned string may contains mnemonics ("&" characters) if they -were passed to the `wxControl:setLabel/2` function; use `GetLabelText()` (not -implemented in wx) if they are undesired. +Note that the returned string may contains mnemonics ("&" characters) if they were passed +to the `wxControl:setLabel/2` function; use `GetLabelText()` (not implemented in wx) if they are undesired. -Also note that the returned string is always the string which was passed to -`wxControl:setLabel/2` but may be different from the string passed to -`SetLabelText()` (not implemented in wx) (since this last one escapes mnemonic -characters). +Also note that the returned string is always the string which was passed to `wxControl:setLabel/2` but may be +different from the string passed to `SetLabelText()` (not implemented in wx) (since this +last one escapes mnemonic characters). """. -spec getLabel(This) -> unicode:charlist() when This::wxStaticText(). @@ -181,13 +202,12 @@ getLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStaticText_GetLabel), wxe_util:rec(?wxStaticText_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextsetlabel">external documentation</a>. -doc """ Change the label shown in the control. -Notice that since wxWidgets 3.1.1 this function is guaranteed not to do anything -if the label didn't really change, so there is no benefit to checking if the new -label is different from the current one in the application code. +Notice that since wxWidgets 3.1.1 this function is guaranteed not to do anything if the +label didn't really change, so there is no benefit to checking if the new label is +different from the current one in the application code. See: `wxControl:setLabel/2` """. @@ -199,15 +219,14 @@ setLabel(#wx_ref{type=ThisT}=This,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Label_UC,?get_env(),?wxStaticText_SetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatictext.html#wxstatictextwrap">external documentation</a>. -doc """ -This functions wraps the controls label so that each of its lines becomes at -most `width` pixels wide if possible (the lines are broken at words boundaries -so it might not be the case if words are too long). +This functions wraps the controls label so that each of its lines becomes at most `width` +pixels wide if possible (the lines are broken at words boundaries so it might not be the +case if words are too long). -If `width` is negative, no wrapping is done. Note that this width is not -necessarily the total width of the control, since a few pixels for the border -(depending on the controls border style) may be added. +If `width` is negative, no wrapping is done. Note that this width is not necessarily the +total width of the control, since a few pixels for the border (depending on the controls +border style) may be added. Since: 2.6.2 """. @@ -218,8 +237,7 @@ wrap(#wx_ref{type=ThisT}=This,Width) ?CLASS(ThisT,wxStaticText), wxe_util:queue_cmd(This,Width,?get_env(),?wxStaticText_Wrap). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxStaticText()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStaticText), @@ -227,547 +245,366 @@ destroy(Obj=#wx_ref{type=Type}) -> ok. %% From wxControl %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStatusBar.erl b/lib/wx/src/gen/wxStatusBar.erl index eb7e3d81580f..141f0bca663d 100644 --- a/lib/wx/src/gen/wxStatusBar.erl +++ b/lib/wx/src/gen/wxStatusBar.erl @@ -20,37 +20,61 @@ -module(wxStatusBar). -moduledoc """ -Functions for wxStatusBar class +A status bar is a narrow window that can be placed along the bottom of a frame to give +small amounts of status information. -A status bar is a narrow window that can be placed along the bottom of a frame -to give small amounts of status information. It can contain one or more fields, -one or more of which can be variable length according to the size of the window. +It can contain one or more fields, one or more of which can be variable length according +to the size of the window. -`m:wxStatusBar` also maintains an independent stack of status texts for each -field (see `pushStatusText/3` and `popStatusText/2`). +`m:wxStatusBar` also maintains an independent stack of status texts for each field (see `pushStatusText/3` +and `popStatusText/2`). Note that in `m:wxStatusBar` context, the terms `pane` and `field` are synonyms. -Styles +## Styles This class supports the following styles: -Remark: It is possible to create controls and other windows on the status bar. -Position these windows from an OnSize() event handler. +* wxSTB_SIZEGRIP: Displays a gripper at the right-hand side of the status bar which can be +used to resize the parent window. -Remark: Notice that only the first 127 characters of a string will be shown in -status bar fields under Windows if a proper manifest indicating that the program -uses version 6 of common controls library is not used. This is a limitation of -the native control on these platforms. +* wxSTB_SHOW_TIPS: Displays tooltips for those panes whose status text has been +ellipsized/truncated because the status text doesn't fit the pane width. Note that this +style has effect only on wxGTK (with GTK+ >= 2.12) currently. -See: `wxStatusBarPane` (not implemented in wx), `m:wxFrame`, -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_statbar) +* wxSTB_ELLIPSIZE_START: Replace the beginning of the status texts with an ellipsis when +the status text widths exceed the status bar pane's widths (uses `wxControl::Ellipsize` +(not implemented in wx)). -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* wxSTB_ELLIPSIZE_MIDDLE: Replace the middle of the status texts with an ellipsis when the +status text widths exceed the status bar pane's widths (uses `wxControl::Ellipsize` (not +implemented in wx)). -wxWidgets docs: -[wxStatusBar](https://docs.wxwidgets.org/3.1/classwx_status_bar.html) +* wxSTB_ELLIPSIZE_END: Replace the end of the status texts with an ellipsis when the status +text widths exceed the status bar pane's widths (uses `wxControl::Ellipsize` (not +implemented in wx)). + +* wxSTB_DEFAULT_STYLE: The default style: includes `wxSTB_SIZEGRIP|wxSTB_SHOW_TIPS|wxSTB_ELLIPSIZE_END|wxFULL_REPAINT_ON_RESIZE`. + +Remark: It is possible to create controls and other windows on the status bar. Position +these windows from an OnSize() event handler. + +Remark: Notice that only the first 127 characters of a string will be shown in status bar +fields under Windows if a proper manifest indicating that the program uses version 6 of +common controls library is not used. This is a limitation of the native control on these platforms. + +See: +* `m:wxFrame` + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_statbar) + +This class is derived, and can use functions, from: + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxStatusBar](https://docs.wxwidgets.org/3.2/classwx_status_bar.html) """. -include("wxe.hrl"). -export([create/2,create/3,destroy/1,getFieldRect/2,getFieldsCount/1,getStatusText/1, @@ -100,20 +124,18 @@ wxWidgets docs: -type wxStatusBar() :: wx:wx_object(). -export_type([wxStatusBar/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarwxstatusbar">external documentation</a>. -doc "Default ctor.". -spec new() -> wxStatusBar(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStatusBar_new_0), wxe_util:rec(?wxStatusBar_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxStatusBar() when Parent::wxWindow:wxWindow(). @@ -121,7 +143,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarwxstatusbar">external documentation</a>. -doc """ Constructor, creating the window. @@ -141,7 +162,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxStatusBar_new_2), wxe_util:rec(?wxStatusBar_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxStatusBar(), Parent::wxWindow:wxWindow(). @@ -149,7 +170,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarcreate">external documentation</a>. -doc """ Creates the window, for two-step construction. @@ -170,13 +190,12 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxStatusBar_Create), wxe_util:rec(?wxStatusBar_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbargetfieldrect">external documentation</a>. -doc """ Returns the size and position of a field's internal bounding rectangle. Return: true if the field index is valid, false otherwise. -See: \{X,Y,W,H\} +See: {X,Y,W,H} """. -spec getFieldRect(This, I) -> Result when Result ::{Res ::boolean(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}}, @@ -187,7 +206,6 @@ getFieldRect(#wx_ref{type=ThisT}=This,I) wxe_util:queue_cmd(This,I,?get_env(),?wxStatusBar_GetFieldRect), wxe_util:rec(?wxStatusBar_GetFieldRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbargetfieldscount">external documentation</a>. -doc "Returns the number of fields in the status bar.". -spec getFieldsCount(This) -> integer() when This::wxStatusBar(). @@ -196,7 +214,7 @@ getFieldsCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStatusBar_GetFieldsCount), wxe_util:rec(?wxStatusBar_GetFieldsCount). -%% @equiv getStatusText(This, []) +-doc(#{equiv => getStatusText(This, [])}). -spec getStatusText(This) -> unicode:charlist() when This::wxStatusBar(). @@ -204,12 +222,10 @@ getStatusText(This) when is_record(This, wx_ref) -> getStatusText(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbargetstatustext">external documentation</a>. -doc """ Returns the string associated with a status bar field. -Return: The status field string if the field is valid, otherwise the empty -string. +Return: The status field string if the field is valid, otherwise the empty string. See: `setStatusText/3` """. @@ -225,7 +241,7 @@ getStatusText(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxStatusBar_GetStatusText), wxe_util:rec(?wxStatusBar_GetStatusText). -%% @equiv popStatusText(This, []) +-doc(#{equiv => popStatusText(This, [])}). -spec popStatusText(This) -> 'ok' when This::wxStatusBar(). @@ -233,15 +249,12 @@ popStatusText(This) when is_record(This, wx_ref) -> popStatusText(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarpopstatustext">external documentation</a>. -doc """ -Restores the text to the value it had before the last call to -`pushStatusText/3`. +Restores the text to the value it had before the last call to `pushStatusText/3`. -Notice that if `setStatusText/3` had been called in the meanwhile, -`popStatusText/2` will not change the text, i.e. it does not override explicit -changes to status text but only restores the saved text if it hadn't been -changed since. +Notice that if `setStatusText/3` had been called in the meanwhile, `popStatusText/2` will not change the text, i.e. it does +not override explicit changes to status text but only restores the saved text if it hadn't +been changed since. See: `pushStatusText/3` """. @@ -256,7 +269,7 @@ popStatusText(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxStatusBar_PopStatusText). -%% @equiv pushStatusText(This,String, []) +-doc(#{equiv => pushStatusText(This,String, [])}). -spec pushStatusText(This, String) -> 'ok' when This::wxStatusBar(), String::unicode:chardata(). @@ -264,10 +277,9 @@ pushStatusText(This,String) when is_record(This, wx_ref),?is_chardata(String) -> pushStatusText(This,String, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarpushstatustext">external documentation</a>. -doc """ -Saves the current field text in a per-field stack, and sets the field text to -the string passed as argument. +Saves the current field text in a per-field stack, and sets the field text to the string +passed as argument. See: `popStatusText/2` """. @@ -283,7 +295,7 @@ pushStatusText(#wx_ref{type=ThisT}=This,String, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,String_UC, Opts,?get_env(),?wxStatusBar_PushStatusText). -%% @equiv setFieldsCount(This,Number, []) +-doc(#{equiv => setFieldsCount(This,Number, [])}). -spec setFieldsCount(This, Number) -> 'ok' when This::wxStatusBar(), Number::integer(). @@ -291,7 +303,6 @@ setFieldsCount(This,Number) when is_record(This, wx_ref),is_integer(Number) -> setFieldsCount(This,Number, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarsetfieldscount">external documentation</a>. -doc "Sets the number of fields, and optionally the field widths.". -spec setFieldsCount(This, Number, [Option]) -> 'ok' when This::wxStatusBar(), Number::integer(), @@ -304,12 +315,11 @@ setFieldsCount(#wx_ref{type=ThisT}=This,Number, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Number, Opts,?get_env(),?wxStatusBar_SetFieldsCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarsetminheight">external documentation</a>. -doc """ Sets the minimal possible height for the status bar. -The real height may be bigger than the height specified here depending on the -size of the font used by the status bar. +The real height may be bigger than the height specified here depending on the size of the +font used by the status bar. """. -spec setMinHeight(This, Height) -> 'ok' when This::wxStatusBar(), Height::integer(). @@ -318,7 +328,7 @@ setMinHeight(#wx_ref{type=ThisT}=This,Height) ?CLASS(ThisT,wxStatusBar), wxe_util:queue_cmd(This,Height,?get_env(),?wxStatusBar_SetMinHeight). -%% @equiv setStatusText(This,Text, []) +-doc(#{equiv => setStatusText(This,Text, [])}). -spec setStatusText(This, Text) -> 'ok' when This::wxStatusBar(), Text::unicode:chardata(). @@ -326,20 +336,20 @@ setStatusText(This,Text) when is_record(This, wx_ref),?is_chardata(Text) -> setStatusText(This,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarsetstatustext">external documentation</a>. -doc """ Sets the status text for the `i-th` field. -The given text will replace the current text. The display of the status bar is -updated immediately, so there is no need to call `wxWindow:update/1` after -calling this function. +The given text will replace the current text. The display of the status bar is updated +immediately, so there is no need to call `wxWindow:update/1` after calling this function. -Note that if `pushStatusText/3` had been called before the new text will also -replace the last saved value to make sure that the next call to -`popStatusText/2` doesn't restore the old value, which was overwritten by the -call to this function. +Note that if `pushStatusText/3` had been called before the new text will also replace the last saved value +to make sure that the next call to `popStatusText/2` doesn't restore the old value, which was overwritten +by the call to this function. -See: `getStatusText/2`, `wxFrame:setStatusText/3` +See: +* `getStatusText/2` + +* `wxFrame:setStatusText/3` """. -spec setStatusText(This, Text, [Option]) -> 'ok' when This::wxStatusBar(), Text::unicode:chardata(), @@ -353,27 +363,28 @@ setStatusText(#wx_ref{type=ThisT}=This,Text, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Text_UC, Opts,?get_env(),?wxStatusBar_SetStatusText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarsetstatuswidths">external documentation</a>. -doc """ Sets the widths of the fields in the status line. -There are two types of fields: `fixed` widths and `variable` width fields. For -the fixed width fields you should specify their (constant) width in pixels. For -the variable width fields, specify a negative number which indicates how the -field should expand: the space left for all variable width fields is divided -between them according to the absolute value of this number. A variable width -field with width of -2 gets twice as much of it as a field with width -1 and so -on. +There are two types of fields: `fixed` widths and `variable` width fields. For the fixed +width fields you should specify their (constant) width in pixels. For the variable width +fields, specify a negative number which indicates how the field should expand: the space +left for all variable width fields is divided between them according to the absolute value +of this number. A variable width field with width of -2 gets twice as much of it as a +field with width -1 and so on. + +For example, to create one fixed width field of width 100 in the right part of the status +bar and two more fields which get 66% and 33% of the remaining space correspondingly, you +should use an array containing -2, -1 and 100. -For example, to create one fixed width field of width 100 in the right part of -the status bar and two more fields which get 66% and 33% of the remaining space -correspondingly, you should use an array containing -2, -1 and 100. +Remark: The widths of the variable fields are calculated from the total width of all +fields, minus the sum of widths of the non-variable fields, divided by the number of +variable fields. -Remark: The widths of the variable fields are calculated from the total width of -all fields, minus the sum of widths of the non-variable fields, divided by the -number of variable fields. +See: +* `setFieldsCount/3` -See: `setFieldsCount/3`, `wxFrame:setStatusWidths/2` +* `wxFrame:setStatusWidths/2` """. -spec setStatusWidths(This, Widths_field) -> 'ok' when This::wxStatusBar(), Widths_field::[integer()]. @@ -382,10 +393,9 @@ setStatusWidths(#wx_ref{type=ThisT}=This,Widths_field) ?CLASS(ThisT,wxStatusBar), wxe_util:queue_cmd(This,Widths_field,?get_env(),?wxStatusBar_SetStatusWidths). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstatusbar.html#wxstatusbarsetstatusstyles">external documentation</a>. -doc """ -Sets the styles of the fields in the status line which can make fields appear -flat or raised instead of the standard sunken 3D border. +Sets the styles of the fields in the status line which can make fields appear flat or +raised instead of the standard sunken 3D border. """. -spec setStatusStyles(This, Styles) -> 'ok' when This::wxStatusBar(), Styles::[integer()]. @@ -394,561 +404,377 @@ setStatusStyles(#wx_ref{type=ThisT}=This,Styles) ?CLASS(ThisT,wxStatusBar), wxe_util:queue_cmd(This,Styles,?get_env(),?wxStatusBar_SetStatusStyles). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxStatusBar()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStatusBar), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStdDialogButtonSizer.erl b/lib/wx/src/gen/wxStdDialogButtonSizer.erl index e490d25b7166..f9a15b018ad2 100644 --- a/lib/wx/src/gen/wxStdDialogButtonSizer.erl +++ b/lib/wx/src/gen/wxStdDialogButtonSizer.erl @@ -20,34 +20,38 @@ -module(wxStdDialogButtonSizer). -moduledoc """ -Functions for wxStdDialogButtonSizer class +This class creates button layouts which conform to the standard button spacing and +ordering defined by the platform or toolkit's user interface guidelines (if such things +exist). -This class creates button layouts which conform to the standard button spacing -and ordering defined by the platform or toolkit's user interface guidelines (if -such things exist). By using this class, you can ensure that all your standard -dialogs look correct on all major platforms. Currently it conforms to the -Windows, GTK+ and macOS human interface guidelines. +By using this class, you can ensure that all your standard dialogs look correct on all +major platforms. Currently it conforms to the Windows, GTK+ and macOS human interface guidelines. -When there aren't interface guidelines defined for a particular platform or -toolkit, `m:wxStdDialogButtonSizer` reverts to the Windows implementation. +When there aren't interface guidelines defined for a particular platform or toolkit, `m:wxStdDialogButtonSizer` +reverts to the Windows implementation. -To use this class, first add buttons to the sizer by calling `addButton/2` (or -`setAffirmativeButton/2`, `setNegativeButton/2` or `setCancelButton/2`) and then -call Realize in order to create the actual button layout used. Other than these -special operations, this sizer works like any other sizer. +To use this class, first add buttons to the sizer by calling `addButton/2` (or `setAffirmativeButton/2`, `setNegativeButton/2` or `setCancelButton/2`) and then call +Realize in order to create the actual button layout used. Other than these special +operations, this sizer works like any other sizer. -If you add a button with wxID_SAVE, on macOS the button will be renamed to -"Save" and the wxID_NO button will be renamed to "Don't Save" in accordance with -the macOS Human Interface Guidelines. +If you add a button with wxID_SAVE, on macOS the button will be renamed to "Save" and the +wxID_NO button will be renamed to "Don't Save" in accordance with the macOS Human +Interface Guidelines. -See: `m:wxSizer`, -[Overview sizer](https://docs.wxwidgets.org/3.1/overview_sizer.html#overview_sizer), -`wxDialog:createButtonSizer/2` +See: +* `m:wxSizer` -This class is derived (and can use functions) from: `m:wxBoxSizer` `m:wxSizer` +* [Overview sizer](https://docs.wxwidgets.org/3.2/overview_sizer.html#overview_sizer) -wxWidgets docs: -[wxStdDialogButtonSizer](https://docs.wxwidgets.org/3.1/classwx_std_dialog_button_sizer.html) +* `wxDialog:createButtonSizer/2` + +This class is derived, and can use functions, from: + +* `m:wxBoxSizer` + +* `m:wxSizer` + +wxWidgets docs: [wxStdDialogButtonSizer](https://docs.wxwidgets.org/3.2/classwx_std_dialog_button_sizer.html) """. -include("wxe.hrl"). -export([addButton/2,destroy/1,new/0,realize/1,setAffirmativeButton/2,setCancelButton/2, @@ -66,24 +70,39 @@ wxWidgets docs: -type wxStdDialogButtonSizer() :: wx:wx_object(). -export_type([wxStdDialogButtonSizer/0]). -%% @hidden -doc false. parent_class(wxBoxSizer) -> true; parent_class(wxSizer) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizerwxstddialogbuttonsizer">external documentation</a>. -doc "Constructor for a `m:wxStdDialogButtonSizer`.". -spec new() -> wxStdDialogButtonSizer(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStdDialogButtonSizer_new), wxe_util:rec(?wxStdDialogButtonSizer_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizeraddbutton">external documentation</a>. -doc """ Adds a button to the `m:wxStdDialogButtonSizer`. The `button` must have one of the following identifiers: + +* wxID_OK + +* wxID_YES + +* wxID_SAVE + +* wxID_APPLY + +* wxID_CLOSE + +* wxID_NO + +* wxID_CANCEL + +* wxID_HELP + +* wxID_CONTEXT_HELP """. -spec addButton(This, Button) -> 'ok' when This::wxStdDialogButtonSizer(), Button::wxButton:wxButton(). @@ -92,10 +111,9 @@ addButton(#wx_ref{type=ThisT}=This,#wx_ref{type=ButtonT}=Button) -> ?CLASS(ButtonT,wxButton), wxe_util:queue_cmd(This,Button,?get_env(),?wxStdDialogButtonSizer_AddButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizerrealize">external documentation</a>. -doc """ -Rearranges the buttons and applies proper spacing between buttons to make them -match the platform or toolkit's interface guidelines. +Rearranges the buttons and applies proper spacing between buttons to make them match the +platform or toolkit's interface guidelines. """. -spec realize(This) -> 'ok' when This::wxStdDialogButtonSizer(). @@ -103,12 +121,10 @@ realize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStdDialogButtonSizer), wxe_util:queue_cmd(This,?get_env(),?wxStdDialogButtonSizer_Realize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizersetaffirmativebutton">external documentation</a>. -doc """ Sets the affirmative button for the sizer. -This allows you to use identifiers other than the standard identifiers outlined -above. +This allows you to use identifiers other than the standard identifiers outlined above. """. -spec setAffirmativeButton(This, Button) -> 'ok' when This::wxStdDialogButtonSizer(), Button::wxButton:wxButton(). @@ -117,12 +133,10 @@ setAffirmativeButton(#wx_ref{type=ThisT}=This,#wx_ref{type=ButtonT}=Button) -> ?CLASS(ButtonT,wxButton), wxe_util:queue_cmd(This,Button,?get_env(),?wxStdDialogButtonSizer_SetAffirmativeButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizersetcancelbutton">external documentation</a>. -doc """ Sets the cancel button for the sizer. -This allows you to use identifiers other than the standard identifiers outlined -above. +This allows you to use identifiers other than the standard identifiers outlined above. """. -spec setCancelButton(This, Button) -> 'ok' when This::wxStdDialogButtonSizer(), Button::wxButton:wxButton(). @@ -131,12 +145,10 @@ setCancelButton(#wx_ref{type=ThisT}=This,#wx_ref{type=ButtonT}=Button) -> ?CLASS(ButtonT,wxButton), wxe_util:queue_cmd(This,Button,?get_env(),?wxStdDialogButtonSizer_SetCancelButton). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstddialogbuttonsizer.html#wxstddialogbuttonsizersetnegativebutton">external documentation</a>. -doc """ Sets the negative button for the sizer. -This allows you to use identifiers other than the standard identifiers outlined -above. +This allows you to use identifiers other than the standard identifiers outlined above. """. -spec setNegativeButton(This, Button) -> 'ok' when This::wxStdDialogButtonSizer(), Button::wxButton:wxButton(). @@ -145,162 +157,111 @@ setNegativeButton(#wx_ref{type=ThisT}=This,#wx_ref{type=ButtonT}=Button) -> ?CLASS(ButtonT,wxButton), wxe_util:queue_cmd(This,Button,?get_env(),?wxStdDialogButtonSizer_SetNegativeButton). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxStdDialogButtonSizer()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStdDialogButtonSizer), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBoxSizer -%% @hidden -doc false. getOrientation(This) -> wxBoxSizer:getOrientation(This). %% From wxSizer -%% @hidden -doc false. showItems(This,Show) -> wxSizer:showItems(This,Show). -%% @hidden -doc false. show(This,Window, Options) -> wxSizer:show(This,Window, Options). -%% @hidden -doc false. show(This,Window) -> wxSizer:show(This,Window). -%% @hidden -doc false. setSizeHints(This,Window) -> wxSizer:setSizeHints(This,Window). -%% @hidden -doc false. setItemMinSize(This,Window,Width,Height) -> wxSizer:setItemMinSize(This,Window,Width,Height). -%% @hidden -doc false. setItemMinSize(This,Window,Size) -> wxSizer:setItemMinSize(This,Window,Size). -%% @hidden -doc false. setMinSize(This,Width,Height) -> wxSizer:setMinSize(This,Width,Height). -%% @hidden -doc false. setMinSize(This,Size) -> wxSizer:setMinSize(This,Size). -%% @hidden -doc false. setDimension(This,X,Y,Width,Height) -> wxSizer:setDimension(This,X,Y,Width,Height). -%% @hidden -doc false. setDimension(This,Pos,Size) -> wxSizer:setDimension(This,Pos,Size). -%% @hidden -doc false. replace(This,Oldwin,Newwin, Options) -> wxSizer:replace(This,Oldwin,Newwin, Options). -%% @hidden -doc false. replace(This,Oldwin,Newwin) -> wxSizer:replace(This,Oldwin,Newwin). -%% @hidden -doc false. remove(This,Index) -> wxSizer:remove(This,Index). -%% @hidden -doc false. prependStretchSpacer(This, Options) -> wxSizer:prependStretchSpacer(This, Options). -%% @hidden -doc false. prependStretchSpacer(This) -> wxSizer:prependStretchSpacer(This). -%% @hidden -doc false. prependSpacer(This,Size) -> wxSizer:prependSpacer(This,Size). -%% @hidden -doc false. prepend(This,Width,Height, Options) -> wxSizer:prepend(This,Width,Height, Options). -%% @hidden -doc false. prepend(This,Width,Height) -> wxSizer:prepend(This,Width,Height). -%% @hidden -doc false. prepend(This,Item) -> wxSizer:prepend(This,Item). -%% @hidden -doc false. layout(This) -> wxSizer:layout(This). -%% @hidden -doc false. recalcSizes(This) -> wxSizer:recalcSizes(This). -%% @hidden -doc false. isShown(This,Window) -> wxSizer:isShown(This,Window). -%% @hidden -doc false. insertStretchSpacer(This,Index, Options) -> wxSizer:insertStretchSpacer(This,Index, Options). -%% @hidden -doc false. insertStretchSpacer(This,Index) -> wxSizer:insertStretchSpacer(This,Index). -%% @hidden -doc false. insertSpacer(This,Index,Size) -> wxSizer:insertSpacer(This,Index,Size). -%% @hidden -doc false. insert(This,Index,Width,Height, Options) -> wxSizer:insert(This,Index,Width,Height, Options). -%% @hidden -doc false. insert(This,Index,Width,Height) -> wxSizer:insert(This,Index,Width,Height). -%% @hidden -doc false. insert(This,Index,Item) -> wxSizer:insert(This,Index,Item). -%% @hidden -doc false. hide(This,Window, Options) -> wxSizer:hide(This,Window, Options). -%% @hidden -doc false. hide(This,Window) -> wxSizer:hide(This,Window). -%% @hidden -doc false. getMinSize(This) -> wxSizer:getMinSize(This). -%% @hidden -doc false. getPosition(This) -> wxSizer:getPosition(This). -%% @hidden -doc false. getSize(This) -> wxSizer:getSize(This). -%% @hidden -doc false. getItem(This,Window, Options) -> wxSizer:getItem(This,Window, Options). -%% @hidden -doc false. getItem(This,Window) -> wxSizer:getItem(This,Window). -%% @hidden -doc false. getChildren(This) -> wxSizer:getChildren(This). -%% @hidden -doc false. fitInside(This,Window) -> wxSizer:fitInside(This,Window). -%% @hidden -doc false. setVirtualSizeHints(This,Window) -> wxSizer:setVirtualSizeHints(This,Window). -%% @hidden -doc false. fit(This,Window) -> wxSizer:fit(This,Window). -%% @hidden -doc false. detach(This,Window) -> wxSizer:detach(This,Window). -%% @hidden -doc false. clear(This, Options) -> wxSizer:clear(This, Options). -%% @hidden -doc false. clear(This) -> wxSizer:clear(This). -%% @hidden -doc false. calcMin(This) -> wxSizer:calcMin(This). -%% @hidden -doc false. addStretchSpacer(This, Options) -> wxSizer:addStretchSpacer(This, Options). -%% @hidden -doc false. addStretchSpacer(This) -> wxSizer:addStretchSpacer(This). -%% @hidden -doc false. addSpacer(This,Size) -> wxSizer:addSpacer(This,Size). -%% @hidden -doc false. add(This,Width,Height, Options) -> wxSizer:add(This,Width,Height, Options). -%% @hidden -doc false. add(This,Width,Height) -> wxSizer:add(This,Width,Height). -%% @hidden -doc false. add(This,Window) -> wxSizer:add(This,Window). diff --git a/lib/wx/src/gen/wxStyledTextCtrl.erl b/lib/wx/src/gen/wxStyledTextCtrl.erl index 6bb624c49f82..5307479e788c 100644 --- a/lib/wx/src/gen/wxStyledTextCtrl.erl +++ b/lib/wx/src/gen/wxStyledTextCtrl.erl @@ -20,39 +20,32 @@ -module(wxStyledTextCtrl). -moduledoc """ -Functions for wxStyledTextCtrl class - A wxWidgets implementation of the Scintilla source code editing component. -As well as features found in standard text editing components, Scintilla -includes features especially useful when editing and debugging source code. -These include support for syntax styling, error indicators, code completion and -call tips. +As well as features found in standard text editing components, Scintilla includes +features especially useful when editing and debugging source code. These include support +for syntax styling, error indicators, code completion and call tips. -The selection margin can contain markers like those used in debuggers to -indicate breakpoints and the current line. Styling choices are more open than -with many editors, allowing the use of proportional fonts, bold and italics, -multiple foreground and background colours and multiple fonts. +The selection margin can contain markers like those used in debuggers to indicate +breakpoints and the current line. Styling choices are more open than with many editors, +allowing the use of proportional fonts, bold and italics, multiple foreground and +background colours and multiple fonts. `m:wxStyledTextCtrl` is a 1 to 1 mapping of "raw" scintilla interface, whose -documentation can be found in the Scintilla website -([http://www.scintilla.org/](http://www.scintilla.org/)). +documentation can be found in the Scintilla website ([http://www.scintilla.org/](http://www.scintilla.org/)). -Please see `m:wxStyledTextEvent` for the documentation of all event types you -can use with `m:wxStyledTextCtrl`. +Please see `m:wxStyledTextEvent` for the documentation of all event types you can use +with `m:wxStyledTextCtrl`. -Index of the member groups +This class is derived, and can use functions, from: -Links for quick access to the various categories of `m:wxStyledTextCtrl` -functions: +* `m:wxControl` -See: `m:wxStyledTextEvent` +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxStyledTextCtrl](https://docs.wxwidgets.org/3.1/classwx_styled_text_ctrl.html) +wxWidgets docs: [wxStyledTextCtrl](https://docs.wxwidgets.org/3.2/classwx_styled_text_ctrl.html) """. -include("wxe.hrl"). -export([addText/2,addTextRaw/2,addTextRaw/3,allocate/2,appendText/2,appendTextRaw/2, @@ -201,21 +194,19 @@ wxWidgets docs: -type wxStyledTextCtrl() :: wx:wx_object(). -export_type([wxStyledTextCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwxstyledtextctrl">external documentation</a>. -doc "Default ctor.". -spec new() -> wxStyledTextCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxStyledTextCtrl_new_0), wxe_util:rec(?wxStyledTextCtrl_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxStyledTextCtrl() when Parent::wxWindow:wxWindow(). @@ -223,7 +214,6 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwxstyledtextctrl">external documentation</a>. -doc "Ctor.". -spec new(Parent, [Option]) -> wxStyledTextCtrl() when Parent::wxWindow:wxWindow(), @@ -243,7 +233,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxStyledTextCtrl_new_2), wxe_util:rec(?wxStyledTextCtrl_new_2). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxStyledTextCtrl(), Parent::wxWindow:wxWindow(). @@ -251,7 +241,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcreate">external documentation</a>. -doc """ Create the UI elements for a STC that was created with the default ctor. @@ -276,7 +265,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxStyledTextCtrl_Create), wxe_util:rec(?wxStyledTextCtrl_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrladdtext">external documentation</a>. -doc "Add text to the document at current position.". -spec addText(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -286,7 +274,6 @@ addText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_AddText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlinserttext">external documentation</a>. -doc "Insert string at a position.". -spec insertText(This, Pos, Text) -> 'ok' when This::wxStyledTextCtrl(), Pos::integer(), Text::unicode:chardata(). @@ -296,7 +283,6 @@ insertText(#wx_ref{type=ThisT}=This,Pos,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Pos,Text_UC,?get_env(),?wxStyledTextCtrl_InsertText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlclearall">external documentation</a>. -doc "Delete all text in the document.". -spec clearAll(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -304,7 +290,6 @@ clearAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ClearAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcleardocumentstyle">external documentation</a>. -doc "Set all style bytes to 0, remove all folding information.". -spec clearDocumentStyle(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -312,7 +297,6 @@ clearDocumentStyle(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ClearDocumentStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlength">external documentation</a>. -doc "Returns the number of bytes in the document.". -spec getLength(This) -> integer() when This::wxStyledTextCtrl(). @@ -321,7 +305,6 @@ getLength(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetLength), wxe_util:rec(?wxStyledTextCtrl_GetLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcharat">external documentation</a>. -doc "Returns the character byte at the position.". -spec getCharAt(This, Pos) -> integer() when This::wxStyledTextCtrl(), Pos::integer(). @@ -331,7 +314,6 @@ getCharAt(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_GetCharAt), wxe_util:rec(?wxStyledTextCtrl_GetCharAt). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcurrentpos">external documentation</a>. -doc "Returns the position of the caret.". -spec getCurrentPos(This) -> integer() when This::wxStyledTextCtrl(). @@ -340,7 +322,6 @@ getCurrentPos(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCurrentPos), wxe_util:rec(?wxStyledTextCtrl_GetCurrentPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetanchor">external documentation</a>. -doc "Returns the position of the opposite end of the selection to the caret.". -spec getAnchor(This) -> integer() when This::wxStyledTextCtrl(). @@ -349,7 +330,6 @@ getAnchor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetAnchor), wxe_util:rec(?wxStyledTextCtrl_GetAnchor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstyleat">external documentation</a>. -doc "Returns the style byte at the position.". -spec getStyleAt(This, Pos) -> integer() when This::wxStyledTextCtrl(), Pos::integer(). @@ -359,7 +339,6 @@ getStyleAt(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_GetStyleAt), wxe_util:rec(?wxStyledTextCtrl_GetStyleAt). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlredo">external documentation</a>. -doc "Redoes the next action on the undo history.". -spec redo(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -367,7 +346,6 @@ redo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Redo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetundocollection">external documentation</a>. -doc "Choose between collecting actions into the undo history and discarding them.". -spec setUndoCollection(This, CollectUndo) -> 'ok' when This::wxStyledTextCtrl(), CollectUndo::boolean(). @@ -376,7 +354,6 @@ setUndoCollection(#wx_ref{type=ThisT}=This,CollectUndo) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CollectUndo,?get_env(),?wxStyledTextCtrl_SetUndoCollection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlselectall">external documentation</a>. -doc "Select all the text in the document.". -spec selectAll(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -384,10 +361,9 @@ selectAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SelectAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetsavepoint">external documentation</a>. -doc """ -Remember the current position in the undo history as the position at which the -document was saved. +Remember the current position in the undo history as the position at which the document +was saved. """. -spec setSavePoint(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -395,7 +371,6 @@ setSavePoint(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SetSavePoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcanredo">external documentation</a>. -doc "Are there any redoable actions in the undo history?". -spec canRedo(This) -> boolean() when This::wxStyledTextCtrl(). @@ -404,7 +379,6 @@ canRedo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CanRedo), wxe_util:rec(?wxStyledTextCtrl_CanRedo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerlinefromhandle">external documentation</a>. -doc "Retrieve the line number at which a particular marker is located.". -spec markerLineFromHandle(This, MarkerHandle) -> integer() when This::wxStyledTextCtrl(), MarkerHandle::integer(). @@ -414,7 +388,6 @@ markerLineFromHandle(#wx_ref{type=ThisT}=This,MarkerHandle) wxe_util:queue_cmd(This,MarkerHandle,?get_env(),?wxStyledTextCtrl_MarkerLineFromHandle), wxe_util:rec(?wxStyledTextCtrl_MarkerLineFromHandle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerdeletehandle">external documentation</a>. -doc "Delete a marker.". -spec markerDeleteHandle(This, MarkerHandle) -> 'ok' when This::wxStyledTextCtrl(), MarkerHandle::integer(). @@ -423,7 +396,6 @@ markerDeleteHandle(#wx_ref{type=ThisT}=This,MarkerHandle) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,MarkerHandle,?get_env(),?wxStyledTextCtrl_MarkerDeleteHandle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetundocollection">external documentation</a>. -doc "Is undo history being collected?". -spec getUndoCollection(This) -> boolean() when This::wxStyledTextCtrl(). @@ -432,11 +404,7 @@ getUndoCollection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetUndoCollection), wxe_util:rec(?wxStyledTextCtrl_GetUndoCollection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetviewwhitespace">external documentation</a>. --doc """ -Are white space characters currently visible? Returns one of wxSTC*WS*\* -constants. -""". +-doc "Are white space characters currently visible? Returns one of wxSTC\_WS\_\* constants.". -spec getViewWhiteSpace(This) -> integer() when This::wxStyledTextCtrl(). getViewWhiteSpace(#wx_ref{type=ThisT}=This) -> @@ -444,12 +412,10 @@ getViewWhiteSpace(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetViewWhiteSpace), wxe_util:rec(?wxStyledTextCtrl_GetViewWhiteSpace). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetviewwhitespace">external documentation</a>. -doc """ -Make white space characters invisible, always visible or visible outside -indentation. +Make white space characters invisible, always visible or visible outside indentation. -The input should be one of the ?wxSTC*WS*\* constants. +The input should be one of the ?wxSTC\_WS\_\* constants. """. -spec setViewWhiteSpace(This, ViewWS) -> 'ok' when This::wxStyledTextCtrl(), ViewWS::integer(). @@ -458,7 +424,6 @@ setViewWhiteSpace(#wx_ref{type=ThisT}=This,ViewWS) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,ViewWS,?get_env(),?wxStyledTextCtrl_SetViewWhiteSpace). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpositionfrompoint">external documentation</a>. -doc "Find the position from a point within the window.". -spec positionFromPoint(This, Pt) -> integer() when This::wxStyledTextCtrl(), Pt::{X::integer(), Y::integer()}. @@ -468,10 +433,9 @@ positionFromPoint(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxStyledTextCtrl_PositionFromPoint), wxe_util:rec(?wxStyledTextCtrl_PositionFromPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpositionfrompointclose">external documentation</a>. -doc """ -Find the position from a point within the window but return -wxSTC_INVALID_POSITION if not close to text. +Find the position from a point within the window but return wxSTC\_INVALID\_POSITION if +not close to text. """. -spec positionFromPointClose(This, X, Y) -> integer() when This::wxStyledTextCtrl(), X::integer(), Y::integer(). @@ -481,7 +445,6 @@ positionFromPointClose(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxStyledTextCtrl_PositionFromPointClose), wxe_util:rec(?wxStyledTextCtrl_PositionFromPointClose). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgotoline">external documentation</a>. -doc "Set caret to start of a line and ensure it is visible.". -spec gotoLine(This, Line) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(). @@ -490,7 +453,6 @@ gotoLine(#wx_ref{type=ThisT}=This,Line) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GotoLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgotopos">external documentation</a>. -doc "Set caret to a position and ensure it is visible.". -spec gotoPos(This, Caret) -> 'ok' when This::wxStyledTextCtrl(), Caret::integer(). @@ -499,7 +461,6 @@ gotoPos(#wx_ref{type=ThisT}=This,Caret) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Caret,?get_env(),?wxStyledTextCtrl_GotoPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetanchor">external documentation</a>. -doc """ Set the selection anchor to a position. @@ -512,12 +473,10 @@ setAnchor(#wx_ref{type=ThisT}=This,Anchor) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Anchor,?get_env(),?wxStyledTextCtrl_SetAnchor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcurline">external documentation</a>. -doc """ Retrieve the text of the line containing the caret. -linePos can optionally be passed in to receive the index of the caret on the -line. +linePos can optionally be passed in to receive the index of the caret on the line. """. -spec getCurLine(This) -> Result when Result ::{Res ::unicode:charlist(), LinePos::integer()}, @@ -527,7 +486,6 @@ getCurLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCurLine), wxe_util:rec(?wxStyledTextCtrl_GetCurLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetendstyled">external documentation</a>. -doc "Retrieve the position of the last correctly styled character.". -spec getEndStyled(This) -> integer() when This::wxStyledTextCtrl(). @@ -536,7 +494,6 @@ getEndStyled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEndStyled), wxe_util:rec(?wxStyledTextCtrl_GetEndStyled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlconverteols">external documentation</a>. -doc "Convert all line endings in the document to one mode.". -spec convertEOLs(This, EolMode) -> 'ok' when This::wxStyledTextCtrl(), EolMode::integer(). @@ -545,10 +502,9 @@ convertEOLs(#wx_ref{type=ThisT}=This,EolMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,EolMode,?get_env(),?wxStyledTextCtrl_ConvertEOLs). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgeteolmode">external documentation</a>. -doc """ -Retrieve the current end of line mode - one of wxSTC_EOL_CRLF, wxSTC_EOL_CR, or -wxSTC_EOL_LF. +Retrieve the current end of line mode - one of wxSTC\_EOL\_CRLF, wxSTC\_EOL\_CR, or +wxSTC\_EOL\_LF. """. -spec getEOLMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -557,11 +513,10 @@ getEOLMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEOLMode), wxe_util:rec(?wxStyledTextCtrl_GetEOLMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlseteolmode">external documentation</a>. -doc """ Set the current end of line mode. -The input should be one of the ?wxSTC*EOL*\* constants. +The input should be one of the ?wxSTC\_EOL\_\* constants. """. -spec setEOLMode(This, EolMode) -> 'ok' when This::wxStyledTextCtrl(), EolMode::integer(). @@ -570,7 +525,6 @@ setEOLMode(#wx_ref{type=ThisT}=This,EolMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,EolMode,?get_env(),?wxStyledTextCtrl_SetEOLMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstartstyling">external documentation</a>. -doc "Set the current styling position to start.". -spec startStyling(This, Start) -> 'ok' when This::wxStyledTextCtrl(), Start::integer(). @@ -579,10 +533,9 @@ startStyling(#wx_ref{type=ThisT}=This,Start) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Start,?get_env(),?wxStyledTextCtrl_StartStyling). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetstyling">external documentation</a>. -doc """ -Change style from current styling position for length characters to a style and -move the current styling position to after this newly styled segment. +Change style from current styling position for length characters to a style and move the +current styling position to after this newly styled segment. """. -spec setStyling(This, Length, Style) -> 'ok' when This::wxStyledTextCtrl(), Length::integer(), Style::integer(). @@ -591,7 +544,6 @@ setStyling(#wx_ref{type=ThisT}=This,Length,Style) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Length,Style,?get_env(),?wxStyledTextCtrl_SetStyling). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetbuffereddraw">external documentation</a>. -doc "Is drawing done first into a buffer or direct to the screen?". -spec getBufferedDraw(This) -> boolean() when This::wxStyledTextCtrl(). @@ -600,10 +552,9 @@ getBufferedDraw(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetBufferedDraw), wxe_util:rec(?wxStyledTextCtrl_GetBufferedDraw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetbuffereddraw">external documentation</a>. -doc """ -If drawing is buffered then each line of text is drawn into a bitmap buffer -before drawing it to the screen to avoid flicker. +If drawing is buffered then each line of text is drawn into a bitmap buffer before +drawing it to the screen to avoid flicker. """. -spec setBufferedDraw(This, Buffered) -> 'ok' when This::wxStyledTextCtrl(), Buffered::boolean(). @@ -612,11 +563,7 @@ setBufferedDraw(#wx_ref{type=ThisT}=This,Buffered) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Buffered,?get_env(),?wxStyledTextCtrl_SetBufferedDraw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettabwidth">external documentation</a>. --doc """ -Change the visible size of a tab to be a multiple of the width of a space -character. -""". +-doc "Change the visible size of a tab to be a multiple of the width of a space character.". -spec setTabWidth(This, TabWidth) -> 'ok' when This::wxStyledTextCtrl(), TabWidth::integer(). setTabWidth(#wx_ref{type=ThisT}=This,TabWidth) @@ -624,7 +571,6 @@ setTabWidth(#wx_ref{type=ThisT}=This,TabWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,TabWidth,?get_env(),?wxStyledTextCtrl_SetTabWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettabwidth">external documentation</a>. -doc "Retrieve the visible size of a tab.". -spec getTabWidth(This) -> integer() when This::wxStyledTextCtrl(). @@ -633,7 +579,6 @@ getTabWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTabWidth), wxe_util:rec(?wxStyledTextCtrl_GetTabWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcodepage">external documentation</a>. -doc "Set the code page used to interpret the bytes of the document as characters.". -spec setCodePage(This, CodePage) -> 'ok' when This::wxStyledTextCtrl(), CodePage::integer(). @@ -642,7 +587,7 @@ setCodePage(#wx_ref{type=ThisT}=This,CodePage) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CodePage,?get_env(),?wxStyledTextCtrl_SetCodePage). -%% @equiv markerDefine(This,MarkerNumber,MarkerSymbol, []) +-doc(#{equiv => markerDefine(This,MarkerNumber,MarkerSymbol, [])}). -spec markerDefine(This, MarkerNumber, MarkerSymbol) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), MarkerSymbol::integer(). @@ -650,12 +595,11 @@ markerDefine(This,MarkerNumber,MarkerSymbol) when is_record(This, wx_ref),is_integer(MarkerNumber),is_integer(MarkerSymbol) -> markerDefine(This,MarkerNumber,MarkerSymbol, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerdefine">external documentation</a>. -doc """ Set the symbol used for a particular marker number, and optionally the fore and background colours. -The second argument should be one of the ?wxSTC*MARK*\* constants. +The second argument should be one of the ?wxSTC\_MARK\_\* constants. """. -spec markerDefine(This, MarkerNumber, MarkerSymbol, [Option]) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), MarkerSymbol::integer(), @@ -670,7 +614,6 @@ markerDefine(#wx_ref{type=ThisT}=This,MarkerNumber,MarkerSymbol, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,MarkerNumber,MarkerSymbol, Opts,?get_env(),?wxStyledTextCtrl_MarkerDefine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkersetforeground">external documentation</a>. -doc "Set the foreground colour used for a particular marker number.". -spec markerSetForeground(This, MarkerNumber, Fore) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), Fore::wx:wx_colour(). @@ -679,7 +622,6 @@ markerSetForeground(#wx_ref{type=ThisT}=This,MarkerNumber,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,MarkerNumber,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_MarkerSetForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkersetbackground">external documentation</a>. -doc "Set the background colour used for a particular marker number.". -spec markerSetBackground(This, MarkerNumber, Back) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), Back::wx:wx_colour(). @@ -688,11 +630,7 @@ markerSetBackground(#wx_ref{type=ThisT}=This,MarkerNumber,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,MarkerNumber,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_MarkerSetBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkeradd">external documentation</a>. --doc """ -Add a marker to a line, returning an ID which can be used to find or delete the -marker. -""". +-doc "Add a marker to a line, returning an ID which can be used to find or delete the marker.". -spec markerAdd(This, Line, MarkerNumber) -> integer() when This::wxStyledTextCtrl(), Line::integer(), MarkerNumber::integer(). markerAdd(#wx_ref{type=ThisT}=This,Line,MarkerNumber) @@ -701,7 +639,6 @@ markerAdd(#wx_ref{type=ThisT}=This,Line,MarkerNumber) wxe_util:queue_cmd(This,Line,MarkerNumber,?get_env(),?wxStyledTextCtrl_MarkerAdd), wxe_util:rec(?wxStyledTextCtrl_MarkerAdd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerdelete">external documentation</a>. -doc "Delete a marker from a line.". -spec markerDelete(This, Line, MarkerNumber) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), MarkerNumber::integer(). @@ -710,7 +647,6 @@ markerDelete(#wx_ref{type=ThisT}=This,Line,MarkerNumber) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,MarkerNumber,?get_env(),?wxStyledTextCtrl_MarkerDelete). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerdeleteall">external documentation</a>. -doc "Delete all markers with a particular number from all lines.". -spec markerDeleteAll(This, MarkerNumber) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(). @@ -719,7 +655,6 @@ markerDeleteAll(#wx_ref{type=ThisT}=This,MarkerNumber) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,MarkerNumber,?get_env(),?wxStyledTextCtrl_MarkerDeleteAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerget">external documentation</a>. -doc "Get a bit mask of all the markers set on a line.". -spec markerGet(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -729,7 +664,6 @@ markerGet(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_MarkerGet), wxe_util:rec(?wxStyledTextCtrl_MarkerGet). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkernext">external documentation</a>. -doc """ Find the next line at or after lineStart that includes a marker in mask. @@ -743,7 +677,6 @@ markerNext(#wx_ref{type=ThisT}=This,LineStart,MarkerMask) wxe_util:queue_cmd(This,LineStart,MarkerMask,?get_env(),?wxStyledTextCtrl_MarkerNext), wxe_util:rec(?wxStyledTextCtrl_MarkerNext). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerprevious">external documentation</a>. -doc "Find the previous line before lineStart that includes a marker in mask.". -spec markerPrevious(This, LineStart, MarkerMask) -> integer() when This::wxStyledTextCtrl(), LineStart::integer(), MarkerMask::integer(). @@ -753,7 +686,6 @@ markerPrevious(#wx_ref{type=ThisT}=This,LineStart,MarkerMask) wxe_util:queue_cmd(This,LineStart,MarkerMask,?get_env(),?wxStyledTextCtrl_MarkerPrevious), wxe_util:rec(?wxStyledTextCtrl_MarkerPrevious). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkerdefinebitmap">external documentation</a>. -doc "Define a marker with a `m:wxBitmap`.". -spec markerDefineBitmap(This, MarkerNumber, Bmp) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), Bmp::wxBitmap:wxBitmap(). @@ -763,7 +695,6 @@ markerDefineBitmap(#wx_ref{type=ThisT}=This,MarkerNumber,#wx_ref{type=BmpT}=Bmp) ?CLASS(BmpT,wxBitmap), wxe_util:queue_cmd(This,MarkerNumber,Bmp,?get_env(),?wxStyledTextCtrl_MarkerDefineBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkeraddset">external documentation</a>. -doc "Add a set of markers to a line.". -spec markerAddSet(This, Line, MarkerSet) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), MarkerSet::integer(). @@ -772,7 +703,6 @@ markerAddSet(#wx_ref{type=ThisT}=This,Line,MarkerSet) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,MarkerSet,?get_env(),?wxStyledTextCtrl_MarkerAddSet). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmarkersetalpha">external documentation</a>. -doc "Set the alpha used for a marker that is drawn in the text area, not the margin.". -spec markerSetAlpha(This, MarkerNumber, Alpha) -> 'ok' when This::wxStyledTextCtrl(), MarkerNumber::integer(), Alpha::integer(). @@ -781,11 +711,10 @@ markerSetAlpha(#wx_ref{type=ThisT}=This,MarkerNumber,Alpha) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,MarkerNumber,Alpha,?get_env(),?wxStyledTextCtrl_MarkerSetAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmargintype">external documentation</a>. -doc """ Set a margin to be either numeric or symbolic. -The second argument should be one of the ?wxSTC*MARGIN*\* constants. +The second argument should be one of the ?wxSTC\_MARGIN\_\* constants. """. -spec setMarginType(This, Margin, MarginType) -> 'ok' when This::wxStyledTextCtrl(), Margin::integer(), MarginType::integer(). @@ -794,11 +723,10 @@ setMarginType(#wx_ref{type=ThisT}=This,Margin,MarginType) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Margin,MarginType,?get_env(),?wxStyledTextCtrl_SetMarginType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmargintype">external documentation</a>. -doc """ Retrieve the type of a margin. -The return value will be one of the ?wxSTC*MARGIN*\* constants. +The return value will be one of the ?wxSTC\_MARGIN\_\* constants. """. -spec getMarginType(This, Margin) -> integer() when This::wxStyledTextCtrl(), Margin::integer(). @@ -808,7 +736,6 @@ getMarginType(#wx_ref{type=ThisT}=This,Margin) wxe_util:queue_cmd(This,Margin,?get_env(),?wxStyledTextCtrl_GetMarginType), wxe_util:rec(?wxStyledTextCtrl_GetMarginType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmarginwidth">external documentation</a>. -doc "Set the width of a margin to a width expressed in pixels.". -spec setMarginWidth(This, Margin, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), Margin::integer(), PixelWidth::integer(). @@ -817,7 +744,6 @@ setMarginWidth(#wx_ref{type=ThisT}=This,Margin,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Margin,PixelWidth,?get_env(),?wxStyledTextCtrl_SetMarginWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmarginwidth">external documentation</a>. -doc "Retrieve the width of a margin in pixels.". -spec getMarginWidth(This, Margin) -> integer() when This::wxStyledTextCtrl(), Margin::integer(). @@ -827,7 +753,6 @@ getMarginWidth(#wx_ref{type=ThisT}=This,Margin) wxe_util:queue_cmd(This,Margin,?get_env(),?wxStyledTextCtrl_GetMarginWidth), wxe_util:rec(?wxStyledTextCtrl_GetMarginWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmarginmask">external documentation</a>. -doc "Set a mask that determines which markers are displayed in a margin.". -spec setMarginMask(This, Margin, Mask) -> 'ok' when This::wxStyledTextCtrl(), Margin::integer(), Mask::integer(). @@ -836,7 +761,6 @@ setMarginMask(#wx_ref{type=ThisT}=This,Margin,Mask) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Margin,Mask,?get_env(),?wxStyledTextCtrl_SetMarginMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmarginmask">external documentation</a>. -doc "Retrieve the marker mask of a margin.". -spec getMarginMask(This, Margin) -> integer() when This::wxStyledTextCtrl(), Margin::integer(). @@ -846,7 +770,6 @@ getMarginMask(#wx_ref{type=ThisT}=This,Margin) wxe_util:queue_cmd(This,Margin,?get_env(),?wxStyledTextCtrl_GetMarginMask), wxe_util:rec(?wxStyledTextCtrl_GetMarginMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmarginsensitive">external documentation</a>. -doc "Make a margin sensitive or insensitive to mouse clicks.". -spec setMarginSensitive(This, Margin, Sensitive) -> 'ok' when This::wxStyledTextCtrl(), Margin::integer(), Sensitive::boolean(). @@ -855,7 +778,6 @@ setMarginSensitive(#wx_ref{type=ThisT}=This,Margin,Sensitive) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Margin,Sensitive,?get_env(),?wxStyledTextCtrl_SetMarginSensitive). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmarginsensitive">external documentation</a>. -doc "Retrieve the mouse click sensitivity of a margin.". -spec getMarginSensitive(This, Margin) -> boolean() when This::wxStyledTextCtrl(), Margin::integer(). @@ -865,7 +787,6 @@ getMarginSensitive(#wx_ref{type=ThisT}=This,Margin) wxe_util:queue_cmd(This,Margin,?get_env(),?wxStyledTextCtrl_GetMarginSensitive), wxe_util:rec(?wxStyledTextCtrl_GetMarginSensitive). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstyleclearall">external documentation</a>. -doc "Clear all the styles and make equivalent to the global default style.". -spec styleClearAll(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -873,7 +794,6 @@ styleClearAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StyleClearAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetforeground">external documentation</a>. -doc "Set the foreground colour of a style.". -spec styleSetForeground(This, Style, Fore) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Fore::wx:wx_colour(). @@ -882,7 +802,6 @@ styleSetForeground(#wx_ref{type=ThisT}=This,Style,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_StyleSetForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetbackground">external documentation</a>. -doc "Set the background colour of a style.". -spec styleSetBackground(This, Style, Back) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Back::wx:wx_colour(). @@ -891,7 +810,6 @@ styleSetBackground(#wx_ref{type=ThisT}=This,Style,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_StyleSetBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetbold">external documentation</a>. -doc "Set a style to be bold or not.". -spec styleSetBold(This, Style, Bold) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Bold::boolean(). @@ -900,7 +818,6 @@ styleSetBold(#wx_ref{type=ThisT}=This,Style,Bold) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Bold,?get_env(),?wxStyledTextCtrl_StyleSetBold). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetitalic">external documentation</a>. -doc "Set a style to be italic or not.". -spec styleSetItalic(This, Style, Italic) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Italic::boolean(). @@ -909,7 +826,6 @@ styleSetItalic(#wx_ref{type=ThisT}=This,Style,Italic) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Italic,?get_env(),?wxStyledTextCtrl_StyleSetItalic). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetsize">external documentation</a>. -doc "Set the size of characters of a style.". -spec styleSetSize(This, Style, SizePoints) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), SizePoints::integer(). @@ -918,7 +834,6 @@ styleSetSize(#wx_ref{type=ThisT}=This,Style,SizePoints) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,SizePoints,?get_env(),?wxStyledTextCtrl_StyleSetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetfacename">external documentation</a>. -doc "Set the font of a style.". -spec styleSetFaceName(This, Style, FontName) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), FontName::unicode:chardata(). @@ -928,7 +843,6 @@ styleSetFaceName(#wx_ref{type=ThisT}=This,Style,FontName) FontName_UC = unicode:characters_to_binary(FontName), wxe_util:queue_cmd(This,Style,FontName_UC,?get_env(),?wxStyledTextCtrl_StyleSetFaceName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstyleseteolfilled">external documentation</a>. -doc "Set a style to have its end of line filled or not.". -spec styleSetEOLFilled(This, Style, EolFilled) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), EolFilled::boolean(). @@ -937,7 +851,6 @@ styleSetEOLFilled(#wx_ref{type=ThisT}=This,Style,EolFilled) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,EolFilled,?get_env(),?wxStyledTextCtrl_StyleSetEOLFilled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstyleresetdefault">external documentation</a>. -doc "Reset the default style to its state at startup.". -spec styleResetDefault(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -945,7 +858,6 @@ styleResetDefault(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StyleResetDefault). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetunderline">external documentation</a>. -doc "Set a style to be underlined or not.". -spec styleSetUnderline(This, Style, Underline) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Underline::boolean(). @@ -954,11 +866,10 @@ styleSetUnderline(#wx_ref{type=ThisT}=This,Style,Underline) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Underline,?get_env(),?wxStyledTextCtrl_StyleSetUnderline). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetcase">external documentation</a>. -doc """ Set a style to be mixed case, or to force upper or lower case. -The second argument should be one of the ?wxSTC*CASE*\* constants. +The second argument should be one of the ?wxSTC\_CASE\_\* constants. """. -spec styleSetCase(This, Style, CaseVisible) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), CaseVisible::integer(). @@ -967,7 +878,6 @@ styleSetCase(#wx_ref{type=ThisT}=This,Style,CaseVisible) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,CaseVisible,?get_env(),?wxStyledTextCtrl_StyleSetCase). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesethotspot">external documentation</a>. -doc "Set a style to be a hotspot or not.". -spec styleSetHotSpot(This, Style, Hotspot) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Hotspot::boolean(). @@ -976,10 +886,9 @@ styleSetHotSpot(#wx_ref{type=ThisT}=This,Style,Hotspot) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Hotspot,?get_env(),?wxStyledTextCtrl_StyleSetHotSpot). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselforeground">external documentation</a>. -doc """ -Set the foreground colour of the main and additional selections and whether to -use this setting. +Set the foreground colour of the main and additional selections and whether to use this +setting. """. -spec setSelForeground(This, UseSetting, Fore) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Fore::wx:wx_colour(). @@ -988,10 +897,9 @@ setSelForeground(#wx_ref{type=ThisT}=This,UseSetting,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_SetSelForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselbackground">external documentation</a>. -doc """ -Set the background colour of the main and additional selections and whether to -use this setting. +Set the background colour of the main and additional selections and whether to use this +setting. """. -spec setSelBackground(This, UseSetting, Back) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Back::wx:wx_colour(). @@ -1000,7 +908,6 @@ setSelBackground(#wx_ref{type=ThisT}=This,UseSetting,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_SetSelBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselalpha">external documentation</a>. -doc "Get the alpha of the selection.". -spec getSelAlpha(This) -> integer() when This::wxStyledTextCtrl(). @@ -1009,7 +916,6 @@ getSelAlpha(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelAlpha), wxe_util:rec(?wxStyledTextCtrl_GetSelAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselalpha">external documentation</a>. -doc "Set the alpha of the selection.". -spec setSelAlpha(This, Alpha) -> 'ok' when This::wxStyledTextCtrl(), Alpha::integer(). @@ -1018,7 +924,6 @@ setSelAlpha(#wx_ref{type=ThisT}=This,Alpha) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Alpha,?get_env(),?wxStyledTextCtrl_SetSelAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretforeground">external documentation</a>. -doc "Set the foreground colour of the caret.". -spec setCaretForeground(This, Fore) -> 'ok' when This::wxStyledTextCtrl(), Fore::wx:wx_colour(). @@ -1027,13 +932,11 @@ setCaretForeground(#wx_ref{type=ThisT}=This,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_SetCaretForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcmdkeyassign">external documentation</a>. -doc """ When key+modifier combination keyDefinition is pressed perform sciCommand. -The second argument should be a bit list containing one or more of the -?wxSTC*KEYMOD*_ constants and the third argument should be one of the -?wxSTC*CMD*_ constants. +The second argument should be a bit list containing one or more of the ?wxSTC\_KEYMOD\_\* +constants and the third argument should be one of the ?wxSTC\_CMD\_\* constants. """. -spec cmdKeyAssign(This, Key, Modifiers, Cmd) -> 'ok' when This::wxStyledTextCtrl(), Key::integer(), Modifiers::integer(), Cmd::integer(). @@ -1042,12 +945,11 @@ cmdKeyAssign(#wx_ref{type=ThisT}=This,Key,Modifiers,Cmd) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Key,Modifiers,Cmd,?get_env(),?wxStyledTextCtrl_CmdKeyAssign). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcmdkeyclear">external documentation</a>. -doc """ When key+modifier combination keyDefinition is pressed do nothing. -The second argument should be a bit list containing one or more of the -?wxSTC*KEYMOD*\* constants. +The second argument should be a bit list containing one or more of the ?wxSTC\_KEYMOD\_\* +constants. """. -spec cmdKeyClear(This, Key, Modifiers) -> 'ok' when This::wxStyledTextCtrl(), Key::integer(), Modifiers::integer(). @@ -1056,7 +958,6 @@ cmdKeyClear(#wx_ref{type=ThisT}=This,Key,Modifiers) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Key,Modifiers,?get_env(),?wxStyledTextCtrl_CmdKeyClear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcmdkeyclearall">external documentation</a>. -doc "Drop all key mappings.". -spec cmdKeyClearAll(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -1064,7 +965,6 @@ cmdKeyClearAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CmdKeyClearAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetstylebytes">external documentation</a>. -doc "Set the styles for a segment of the document.". -spec setStyleBytes(This, Length) -> integer() when This::wxStyledTextCtrl(), Length::integer(). @@ -1074,7 +974,6 @@ setStyleBytes(#wx_ref{type=ThisT}=This,Length) wxe_util:queue_cmd(This,Length,?get_env(),?wxStyledTextCtrl_SetStyleBytes), wxe_util:rec(?wxStyledTextCtrl_SetStyleBytes). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetvisible">external documentation</a>. -doc "Set a style to be visible or not.". -spec styleSetVisible(This, Style, Visible) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Visible::boolean(). @@ -1083,7 +982,6 @@ styleSetVisible(#wx_ref{type=ThisT}=This,Style,Visible) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Visible,?get_env(),?wxStyledTextCtrl_StyleSetVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretperiod">external documentation</a>. -doc "Get the time in milliseconds that the caret is on and off.". -spec getCaretPeriod(This) -> integer() when This::wxStyledTextCtrl(). @@ -1092,7 +990,6 @@ getCaretPeriod(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretPeriod), wxe_util:rec(?wxStyledTextCtrl_GetCaretPeriod). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretperiod">external documentation</a>. -doc """ Get the time in milliseconds that the caret is on and off. @@ -1105,7 +1002,6 @@ setCaretPeriod(#wx_ref{type=ThisT}=This,PeriodMilliseconds) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PeriodMilliseconds,?get_env(),?wxStyledTextCtrl_SetCaretPeriod). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwordchars">external documentation</a>. -doc """ Set the set of characters making up words for when moving or selecting by word. @@ -1119,7 +1015,6 @@ setWordChars(#wx_ref{type=ThisT}=This,Characters) Characters_UC = unicode:characters_to_binary(Characters), wxe_util:queue_cmd(This,Characters_UC,?get_env(),?wxStyledTextCtrl_SetWordChars). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlbeginundoaction">external documentation</a>. -doc """ Start a sequence of actions that is undone and redone as a unit. @@ -1131,7 +1026,6 @@ beginUndoAction(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_BeginUndoAction). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlendundoaction">external documentation</a>. -doc "End a sequence of actions that is undone and redone as a unit.". -spec endUndoAction(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -1139,11 +1033,10 @@ endUndoAction(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_EndUndoAction). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlindicatorsetstyle">external documentation</a>. -doc """ Set an indicator to plain, squiggle or TT. -The second argument should be one of the ?wxSTC*INDIC*\* constants. +The second argument should be one of the ?wxSTC\_INDIC\_\* constants. """. -spec indicatorSetStyle(This, Indicator, IndicatorStyle) -> 'ok' when This::wxStyledTextCtrl(), Indicator::integer(), IndicatorStyle::integer(). @@ -1152,11 +1045,10 @@ indicatorSetStyle(#wx_ref{type=ThisT}=This,Indicator,IndicatorStyle) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Indicator,IndicatorStyle,?get_env(),?wxStyledTextCtrl_IndicatorSetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlindicatorgetstyle">external documentation</a>. -doc """ Retrieve the style of an indicator. -The return value will be one of the ?wxSTC*INDIC*\* constants. +The return value will be one of the ?wxSTC\_INDIC\_\* constants. """. -spec indicatorGetStyle(This, Indicator) -> integer() when This::wxStyledTextCtrl(), Indicator::integer(). @@ -1166,7 +1058,6 @@ indicatorGetStyle(#wx_ref{type=ThisT}=This,Indicator) wxe_util:queue_cmd(This,Indicator,?get_env(),?wxStyledTextCtrl_IndicatorGetStyle), wxe_util:rec(?wxStyledTextCtrl_IndicatorGetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlindicatorsetforeground">external documentation</a>. -doc "Set the foreground colour of an indicator.". -spec indicatorSetForeground(This, Indicator, Fore) -> 'ok' when This::wxStyledTextCtrl(), Indicator::integer(), Fore::wx:wx_colour(). @@ -1175,7 +1066,6 @@ indicatorSetForeground(#wx_ref{type=ThisT}=This,Indicator,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Indicator,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_IndicatorSetForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlindicatorgetforeground">external documentation</a>. -doc "Retrieve the foreground colour of an indicator.". -spec indicatorGetForeground(This, Indicator) -> wx:wx_colour4() when This::wxStyledTextCtrl(), Indicator::integer(). @@ -1185,7 +1075,6 @@ indicatorGetForeground(#wx_ref{type=ThisT}=This,Indicator) wxe_util:queue_cmd(This,Indicator,?get_env(),?wxStyledTextCtrl_IndicatorGetForeground), wxe_util:rec(?wxStyledTextCtrl_IndicatorGetForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwhitespaceforeground">external documentation</a>. -doc "Set the foreground colour of all whitespace and whether to use this setting.". -spec setWhitespaceForeground(This, UseSetting, Fore) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Fore::wx:wx_colour(). @@ -1194,7 +1083,6 @@ setWhitespaceForeground(#wx_ref{type=ThisT}=This,UseSetting,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_SetWhitespaceForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwhitespacebackground">external documentation</a>. -doc "Set the background colour of all whitespace and whether to use this setting.". -spec setWhitespaceBackground(This, UseSetting, Back) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Back::wx:wx_colour(). @@ -1203,7 +1091,6 @@ setWhitespaceBackground(#wx_ref{type=ThisT}=This,UseSetting,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_SetWhitespaceBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstylebits">external documentation</a>. -doc """ Retrieve number of bits in style bytes used to hold the lexical state. @@ -1216,7 +1103,6 @@ getStyleBits(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetStyleBits), wxe_util:rec(?wxStyledTextCtrl_GetStyleBits). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlinestate">external documentation</a>. -doc "Used to hold extra styling information for each line.". -spec setLineState(This, Line, State) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), State::integer(). @@ -1225,7 +1111,6 @@ setLineState(#wx_ref{type=ThisT}=This,Line,State) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,State,?get_env(),?wxStyledTextCtrl_SetLineState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlinestate">external documentation</a>. -doc "Retrieve the extra styling information for a line.". -spec getLineState(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -1235,7 +1120,6 @@ getLineState(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineState), wxe_util:rec(?wxStyledTextCtrl_GetLineState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmaxlinestate">external documentation</a>. -doc "Retrieve the last line number that has line state.". -spec getMaxLineState(This) -> integer() when This::wxStyledTextCtrl(). @@ -1244,7 +1128,6 @@ getMaxLineState(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetMaxLineState), wxe_util:rec(?wxStyledTextCtrl_GetMaxLineState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretlinevisible">external documentation</a>. -doc "Is the background of the line containing the caret in a different colour?". -spec getCaretLineVisible(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1253,7 +1136,6 @@ getCaretLineVisible(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretLineVisible), wxe_util:rec(?wxStyledTextCtrl_GetCaretLineVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretlinevisible">external documentation</a>. -doc "Display the background of the line containing the caret in a different colour.". -spec setCaretLineVisible(This, Show) -> 'ok' when This::wxStyledTextCtrl(), Show::boolean(). @@ -1262,7 +1144,6 @@ setCaretLineVisible(#wx_ref{type=ThisT}=This,Show) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Show,?get_env(),?wxStyledTextCtrl_SetCaretLineVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretlinebackground">external documentation</a>. -doc "Get the colour of the background of the line containing the caret.". -spec getCaretLineBackground(This) -> wx:wx_colour4() when This::wxStyledTextCtrl(). @@ -1271,7 +1152,6 @@ getCaretLineBackground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretLineBackground), wxe_util:rec(?wxStyledTextCtrl_GetCaretLineBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretlinebackground">external documentation</a>. -doc "Set the colour of the background of the line containing the caret.". -spec setCaretLineBackground(This, Back) -> 'ok' when This::wxStyledTextCtrl(), Back::wx:wx_colour(). @@ -1280,12 +1160,11 @@ setCaretLineBackground(#wx_ref{type=ThisT}=This,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_SetCaretLineBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompshow">external documentation</a>. -doc """ Display a auto-completion list. -The lengthEntered parameter indicates how many characters before the caret -should be used to provide context. +The lengthEntered parameter indicates how many characters before the caret should be used +to provide context. """. -spec autoCompShow(This, LengthEntered, ItemList) -> 'ok' when This::wxStyledTextCtrl(), LengthEntered::integer(), ItemList::unicode:chardata(). @@ -1295,7 +1174,6 @@ autoCompShow(#wx_ref{type=ThisT}=This,LengthEntered,ItemList) ItemList_UC = unicode:characters_to_binary(ItemList), wxe_util:queue_cmd(This,LengthEntered,ItemList_UC,?get_env(),?wxStyledTextCtrl_AutoCompShow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompcancel">external documentation</a>. -doc "Remove the auto-completion list from the screen.". -spec autoCompCancel(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -1303,7 +1181,6 @@ autoCompCancel(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompCancel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompactive">external documentation</a>. -doc "Is there an auto-completion list visible?". -spec autoCompActive(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1312,7 +1189,6 @@ autoCompActive(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompActive), wxe_util:rec(?wxStyledTextCtrl_AutoCompActive). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompposstart">external documentation</a>. -doc "Retrieve the position of the caret when the auto-completion list was displayed.". -spec autoCompPosStart(This) -> integer() when This::wxStyledTextCtrl(). @@ -1321,7 +1197,6 @@ autoCompPosStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompPosStart), wxe_util:rec(?wxStyledTextCtrl_AutoCompPosStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompcomplete">external documentation</a>. -doc "User has selected an item so remove the list and insert the selection.". -spec autoCompComplete(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -1329,7 +1204,6 @@ autoCompComplete(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompComplete). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompstops">external documentation</a>. -doc "Define a set of character that when typed cancel the auto-completion list.". -spec autoCompStops(This, CharacterSet) -> 'ok' when This::wxStyledTextCtrl(), CharacterSet::unicode:chardata(). @@ -1339,7 +1213,6 @@ autoCompStops(#wx_ref{type=ThisT}=This,CharacterSet) CharacterSet_UC = unicode:characters_to_binary(CharacterSet), wxe_util:queue_cmd(This,CharacterSet_UC,?get_env(),?wxStyledTextCtrl_AutoCompStops). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetseparator">external documentation</a>. -doc """ Change the separator character in the string setting up an auto-completion list. @@ -1352,7 +1225,6 @@ autoCompSetSeparator(#wx_ref{type=ThisT}=This,SeparatorCharacter) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,SeparatorCharacter,?get_env(),?wxStyledTextCtrl_AutoCompSetSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetseparator">external documentation</a>. -doc "Retrieve the auto-completion list separator character.". -spec autoCompGetSeparator(This) -> integer() when This::wxStyledTextCtrl(). @@ -1361,7 +1233,6 @@ autoCompGetSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetSeparator), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompselect">external documentation</a>. -doc "Select the item in the auto-completion list that starts with a string.". -spec autoCompSelect(This, Select) -> 'ok' when This::wxStyledTextCtrl(), Select::unicode:chardata(). @@ -1371,10 +1242,9 @@ autoCompSelect(#wx_ref{type=ThisT}=This,Select) Select_UC = unicode:characters_to_binary(Select), wxe_util:queue_cmd(This,Select_UC,?get_env(),?wxStyledTextCtrl_AutoCompSelect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetcancelatstart">external documentation</a>. -doc """ -Should the auto-completion list be cancelled if the user backspaces to a -position before where the box was created. +Should the auto-completion list be cancelled if the user backspaces to a position before +where the box was created. """. -spec autoCompSetCancelAtStart(This, Cancel) -> 'ok' when This::wxStyledTextCtrl(), Cancel::boolean(). @@ -1383,7 +1253,6 @@ autoCompSetCancelAtStart(#wx_ref{type=ThisT}=This,Cancel) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Cancel,?get_env(),?wxStyledTextCtrl_AutoCompSetCancelAtStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetcancelatstart">external documentation</a>. -doc "Retrieve whether auto-completion cancelled by backspacing before start.". -spec autoCompGetCancelAtStart(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1392,10 +1261,9 @@ autoCompGetCancelAtStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetCancelAtStart), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetCancelAtStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetfillups">external documentation</a>. -doc """ -Define a set of characters that when typed will cause the autocompletion to -choose the selected item. +Define a set of characters that when typed will cause the autocompletion to choose the +selected item. """. -spec autoCompSetFillUps(This, CharacterSet) -> 'ok' when This::wxStyledTextCtrl(), CharacterSet::unicode:chardata(). @@ -1405,7 +1273,6 @@ autoCompSetFillUps(#wx_ref{type=ThisT}=This,CharacterSet) CharacterSet_UC = unicode:characters_to_binary(CharacterSet), wxe_util:queue_cmd(This,CharacterSet_UC,?get_env(),?wxStyledTextCtrl_AutoCompSetFillUps). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetchoosesingle">external documentation</a>. -doc "Should a single item auto-completion list automatically choose the item.". -spec autoCompSetChooseSingle(This, ChooseSingle) -> 'ok' when This::wxStyledTextCtrl(), ChooseSingle::boolean(). @@ -1414,11 +1281,7 @@ autoCompSetChooseSingle(#wx_ref{type=ThisT}=This,ChooseSingle) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,ChooseSingle,?get_env(),?wxStyledTextCtrl_AutoCompSetChooseSingle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetchoosesingle">external documentation</a>. --doc """ -Retrieve whether a single item auto-completion list automatically choose the -item. -""". +-doc "Retrieve whether a single item auto-completion list automatically choose the item.". -spec autoCompGetChooseSingle(This) -> boolean() when This::wxStyledTextCtrl(). autoCompGetChooseSingle(#wx_ref{type=ThisT}=This) -> @@ -1426,7 +1289,6 @@ autoCompGetChooseSingle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetChooseSingle), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetChooseSingle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetignorecase">external documentation</a>. -doc "Set whether case is significant when performing auto-completion searches.". -spec autoCompSetIgnoreCase(This, IgnoreCase) -> 'ok' when This::wxStyledTextCtrl(), IgnoreCase::boolean(). @@ -1435,7 +1297,6 @@ autoCompSetIgnoreCase(#wx_ref{type=ThisT}=This,IgnoreCase) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,IgnoreCase,?get_env(),?wxStyledTextCtrl_AutoCompSetIgnoreCase). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetignorecase">external documentation</a>. -doc "Retrieve state of ignore case flag.". -spec autoCompGetIgnoreCase(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1444,7 +1305,6 @@ autoCompGetIgnoreCase(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetIgnoreCase), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetIgnoreCase). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrluserlistshow">external documentation</a>. -doc "Display a list of strings and send notification when user chooses one.". -spec userListShow(This, ListType, ItemList) -> 'ok' when This::wxStyledTextCtrl(), ListType::integer(), ItemList::unicode:chardata(). @@ -1454,7 +1314,6 @@ userListShow(#wx_ref{type=ThisT}=This,ListType,ItemList) ItemList_UC = unicode:characters_to_binary(ItemList), wxe_util:queue_cmd(This,ListType,ItemList_UC,?get_env(),?wxStyledTextCtrl_UserListShow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetautohide">external documentation</a>. -doc "Set whether or not autocompletion is hidden automatically when nothing matches.". -spec autoCompSetAutoHide(This, AutoHide) -> 'ok' when This::wxStyledTextCtrl(), AutoHide::boolean(). @@ -1463,11 +1322,7 @@ autoCompSetAutoHide(#wx_ref{type=ThisT}=This,AutoHide) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,AutoHide,?get_env(),?wxStyledTextCtrl_AutoCompSetAutoHide). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetautohide">external documentation</a>. --doc """ -Retrieve whether or not autocompletion is hidden automatically when nothing -matches. -""". +-doc "Retrieve whether or not autocompletion is hidden automatically when nothing matches.". -spec autoCompGetAutoHide(This) -> boolean() when This::wxStyledTextCtrl(). autoCompGetAutoHide(#wx_ref{type=ThisT}=This) -> @@ -1475,10 +1330,9 @@ autoCompGetAutoHide(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetAutoHide), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetAutoHide). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetdroprestofword">external documentation</a>. -doc """ -Set whether or not autocompletion deletes any word characters after the inserted -text upon completion. +Set whether or not autocompletion deletes any word characters after the inserted text +upon completion. """. -spec autoCompSetDropRestOfWord(This, DropRestOfWord) -> 'ok' when This::wxStyledTextCtrl(), DropRestOfWord::boolean(). @@ -1487,10 +1341,9 @@ autoCompSetDropRestOfWord(#wx_ref{type=ThisT}=This,DropRestOfWord) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,DropRestOfWord,?get_env(),?wxStyledTextCtrl_AutoCompSetDropRestOfWord). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetdroprestofword">external documentation</a>. -doc """ -Retrieve whether or not autocompletion deletes any word characters after the -inserted text upon completion. +Retrieve whether or not autocompletion deletes any word characters after the inserted +text upon completion. """. -spec autoCompGetDropRestOfWord(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1499,7 +1352,6 @@ autoCompGetDropRestOfWord(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetDropRestOfWord), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetDropRestOfWord). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlregisterimage">external documentation</a>. -doc "Register an image for use in autocompletion lists.". -spec registerImage(This, Type, Bmp) -> 'ok' when This::wxStyledTextCtrl(), Type::integer(), Bmp::wxBitmap:wxBitmap(). @@ -1509,7 +1361,6 @@ registerImage(#wx_ref{type=ThisT}=This,Type,#wx_ref{type=BmpT}=Bmp) ?CLASS(BmpT,wxBitmap), wxe_util:queue_cmd(This,Type,Bmp,?get_env(),?wxStyledTextCtrl_RegisterImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlclearregisteredimages">external documentation</a>. -doc "Clear all the registered images.". -spec clearRegisteredImages(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -1517,7 +1368,6 @@ clearRegisteredImages(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ClearRegisteredImages). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgettypeseparator">external documentation</a>. -doc "Retrieve the auto-completion list type-separator character.". -spec autoCompGetTypeSeparator(This) -> integer() when This::wxStyledTextCtrl(). @@ -1526,10 +1376,8 @@ autoCompGetTypeSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetTypeSeparator), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetTypeSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsettypeseparator">external documentation</a>. -doc """ -Change the type-separator character in the string setting up an auto-completion -list. +Change the type-separator character in the string setting up an auto-completion list. Default is '?' but can be changed if items contain '?'. """. @@ -1540,7 +1388,6 @@ autoCompSetTypeSeparator(#wx_ref{type=ThisT}=This,SeparatorCharacter) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,SeparatorCharacter,?get_env(),?wxStyledTextCtrl_AutoCompSetTypeSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetmaxwidth">external documentation</a>. -doc """ Set the maximum width, in characters, of auto-completion and user lists. @@ -1553,7 +1400,6 @@ autoCompSetMaxWidth(#wx_ref{type=ThisT}=This,CharacterCount) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CharacterCount,?get_env(),?wxStyledTextCtrl_AutoCompSetMaxWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetmaxwidth">external documentation</a>. -doc "Get the maximum width, in characters, of auto-completion and user lists.". -spec autoCompGetMaxWidth(This) -> integer() when This::wxStyledTextCtrl(). @@ -1562,7 +1408,6 @@ autoCompGetMaxWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetMaxWidth), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetMaxWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompsetmaxheight">external documentation</a>. -doc """ Set the maximum height, in rows, of auto-completion and user lists. @@ -1575,7 +1420,6 @@ autoCompSetMaxHeight(#wx_ref{type=ThisT}=This,RowCount) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,RowCount,?get_env(),?wxStyledTextCtrl_AutoCompSetMaxHeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetmaxheight">external documentation</a>. -doc "Set the maximum height, in rows, of auto-completion and user lists.". -spec autoCompGetMaxHeight(This) -> integer() when This::wxStyledTextCtrl(). @@ -1584,7 +1428,6 @@ autoCompGetMaxHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetMaxHeight), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetMaxHeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetindent">external documentation</a>. -doc "Set the number of spaces used for one level of indentation.". -spec setIndent(This, IndentSize) -> 'ok' when This::wxStyledTextCtrl(), IndentSize::integer(). @@ -1593,7 +1436,6 @@ setIndent(#wx_ref{type=ThisT}=This,IndentSize) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,IndentSize,?get_env(),?wxStyledTextCtrl_SetIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetindent">external documentation</a>. -doc "Retrieve indentation size.". -spec getIndent(This) -> integer() when This::wxStyledTextCtrl(). @@ -1602,10 +1444,9 @@ getIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetIndent), wxe_util:rec(?wxStyledTextCtrl_GetIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetusetabs">external documentation</a>. -doc """ -Indentation will only use space characters if useTabs is false, otherwise it -will use a combination of tabs and spaces. +Indentation will only use space characters if useTabs is false, otherwise it will use a +combination of tabs and spaces. """. -spec setUseTabs(This, UseTabs) -> 'ok' when This::wxStyledTextCtrl(), UseTabs::boolean(). @@ -1614,7 +1455,6 @@ setUseTabs(#wx_ref{type=ThisT}=This,UseTabs) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseTabs,?get_env(),?wxStyledTextCtrl_SetUseTabs). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetusetabs">external documentation</a>. -doc "Retrieve whether tabs will be used in indentation.". -spec getUseTabs(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1623,7 +1463,6 @@ getUseTabs(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetUseTabs), wxe_util:rec(?wxStyledTextCtrl_GetUseTabs). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlineindentation">external documentation</a>. -doc "Change the indentation of a line to a number of columns.". -spec setLineIndentation(This, Line, Indentation) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), Indentation::integer(). @@ -1632,7 +1471,6 @@ setLineIndentation(#wx_ref{type=ThisT}=This,Line,Indentation) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,Indentation,?get_env(),?wxStyledTextCtrl_SetLineIndentation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlineindentation">external documentation</a>. -doc "Retrieve the number of columns that a line is indented.". -spec getLineIndentation(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -1642,7 +1480,6 @@ getLineIndentation(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineIndentation), wxe_util:rec(?wxStyledTextCtrl_GetLineIndentation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlineindentposition">external documentation</a>. -doc "Retrieve the position before the first non indentation character on a line.". -spec getLineIndentPosition(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -1652,7 +1489,6 @@ getLineIndentPosition(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineIndentPosition), wxe_util:rec(?wxStyledTextCtrl_GetLineIndentPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcolumn">external documentation</a>. -doc "Retrieve the column number of a position, taking tab width into account.". -spec getColumn(This, Pos) -> integer() when This::wxStyledTextCtrl(), Pos::integer(). @@ -1662,7 +1498,6 @@ getColumn(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_GetColumn), wxe_util:rec(?wxStyledTextCtrl_GetColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetusehorizontalscrollbar">external documentation</a>. -doc "Show or hide the horizontal scroll bar.". -spec setUseHorizontalScrollBar(This, Visible) -> 'ok' when This::wxStyledTextCtrl(), Visible::boolean(). @@ -1671,7 +1506,6 @@ setUseHorizontalScrollBar(#wx_ref{type=ThisT}=This,Visible) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Visible,?get_env(),?wxStyledTextCtrl_SetUseHorizontalScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetusehorizontalscrollbar">external documentation</a>. -doc "Is the horizontal scroll bar visible?". -spec getUseHorizontalScrollBar(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1680,11 +1514,10 @@ getUseHorizontalScrollBar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetUseHorizontalScrollBar), wxe_util:rec(?wxStyledTextCtrl_GetUseHorizontalScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetindentationguides">external documentation</a>. -doc """ Show or hide indentation guides. -The input should be one of the ?wxSTC*IV*\* constants. +The input should be one of the ?wxSTC\_IV\_\* constants. """. -spec setIndentationGuides(This, IndentView) -> 'ok' when This::wxStyledTextCtrl(), IndentView::integer(). @@ -1693,11 +1526,10 @@ setIndentationGuides(#wx_ref{type=ThisT}=This,IndentView) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,IndentView,?get_env(),?wxStyledTextCtrl_SetIndentationGuides). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetindentationguides">external documentation</a>. -doc """ Are the indentation guides visible? -The return value will be one of the ?wxSTC*IV*\* constants. +The return value will be one of the ?wxSTC\_IV\_\* constants. """. -spec getIndentationGuides(This) -> integer() when This::wxStyledTextCtrl(). @@ -1706,7 +1538,6 @@ getIndentationGuides(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetIndentationGuides), wxe_util:rec(?wxStyledTextCtrl_GetIndentationGuides). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethighlightguide">external documentation</a>. -doc """ Set the highlighted indentation guide column. @@ -1719,7 +1550,6 @@ setHighlightGuide(#wx_ref{type=ThisT}=This,Column) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Column,?get_env(),?wxStyledTextCtrl_SetHighlightGuide). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgethighlightguide">external documentation</a>. -doc "Get the highlighted indentation guide column.". -spec getHighlightGuide(This) -> integer() when This::wxStyledTextCtrl(). @@ -1728,7 +1558,6 @@ getHighlightGuide(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetHighlightGuide), wxe_util:rec(?wxStyledTextCtrl_GetHighlightGuide). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlineendposition">external documentation</a>. -doc "Get the position after the last visible characters on a line.". -spec getLineEndPosition(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -1738,7 +1567,6 @@ getLineEndPosition(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineEndPosition), wxe_util:rec(?wxStyledTextCtrl_GetLineEndPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcodepage">external documentation</a>. -doc "Get the code page used to interpret the bytes of the document as characters.". -spec getCodePage(This) -> integer() when This::wxStyledTextCtrl(). @@ -1747,7 +1575,6 @@ getCodePage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCodePage), wxe_util:rec(?wxStyledTextCtrl_GetCodePage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretforeground">external documentation</a>. -doc "Get the foreground colour of the caret.". -spec getCaretForeground(This) -> wx:wx_colour4() when This::wxStyledTextCtrl(). @@ -1756,7 +1583,6 @@ getCaretForeground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretForeground), wxe_util:rec(?wxStyledTextCtrl_GetCaretForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetreadonly">external documentation</a>. -doc "In read-only mode?". -spec getReadOnly(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1765,7 +1591,6 @@ getReadOnly(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetReadOnly), wxe_util:rec(?wxStyledTextCtrl_GetReadOnly). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcurrentpos">external documentation</a>. -doc "Sets the position of the caret.". -spec setCurrentPos(This, Caret) -> 'ok' when This::wxStyledTextCtrl(), Caret::integer(). @@ -1774,7 +1599,6 @@ setCurrentPos(#wx_ref{type=ThisT}=This,Caret) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Caret,?get_env(),?wxStyledTextCtrl_SetCurrentPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselectionstart">external documentation</a>. -doc "Sets the position that starts the selection - this becomes the anchor.". -spec setSelectionStart(This, Anchor) -> 'ok' when This::wxStyledTextCtrl(), Anchor::integer(). @@ -1783,7 +1607,6 @@ setSelectionStart(#wx_ref{type=ThisT}=This,Anchor) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Anchor,?get_env(),?wxStyledTextCtrl_SetSelectionStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselectionstart">external documentation</a>. -doc "Returns the position at the start of the selection.". -spec getSelectionStart(This) -> integer() when This::wxStyledTextCtrl(). @@ -1792,7 +1615,6 @@ getSelectionStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelectionStart), wxe_util:rec(?wxStyledTextCtrl_GetSelectionStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselectionend">external documentation</a>. -doc "Sets the position that ends the selection - this becomes the caret.". -spec setSelectionEnd(This, Caret) -> 'ok' when This::wxStyledTextCtrl(), Caret::integer(). @@ -1801,7 +1623,6 @@ setSelectionEnd(#wx_ref{type=ThisT}=This,Caret) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Caret,?get_env(),?wxStyledTextCtrl_SetSelectionEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselectionend">external documentation</a>. -doc "Returns the position at the end of the selection.". -spec getSelectionEnd(This) -> integer() when This::wxStyledTextCtrl(). @@ -1810,7 +1631,6 @@ getSelectionEnd(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelectionEnd), wxe_util:rec(?wxStyledTextCtrl_GetSelectionEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetprintmagnification">external documentation</a>. -doc "Sets the print magnification added to the point size of each style for printing.". -spec setPrintMagnification(This, Magnification) -> 'ok' when This::wxStyledTextCtrl(), Magnification::integer(). @@ -1819,7 +1639,6 @@ setPrintMagnification(#wx_ref{type=ThisT}=This,Magnification) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Magnification,?get_env(),?wxStyledTextCtrl_SetPrintMagnification). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetprintmagnification">external documentation</a>. -doc "Returns the print magnification.". -spec getPrintMagnification(This) -> integer() when This::wxStyledTextCtrl(). @@ -1828,11 +1647,10 @@ getPrintMagnification(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetPrintMagnification), wxe_util:rec(?wxStyledTextCtrl_GetPrintMagnification). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetprintcolourmode">external documentation</a>. -doc """ Modify colours when printing for clearer printed text. -The input should be one of the ?wxSTC*PRINT*\* constants. +The input should be one of the ?wxSTC\_PRINT\_\* constants. """. -spec setPrintColourMode(This, Mode) -> 'ok' when This::wxStyledTextCtrl(), Mode::integer(). @@ -1841,11 +1659,10 @@ setPrintColourMode(#wx_ref{type=ThisT}=This,Mode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Mode,?get_env(),?wxStyledTextCtrl_SetPrintColourMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetprintcolourmode">external documentation</a>. -doc """ Returns the print colour mode. -The return value will be one of the ?wxSTC*PRINT*\* constants. +The return value will be one of the ?wxSTC\_PRINT\_\* constants. """. -spec getPrintColourMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -1854,7 +1671,7 @@ getPrintColourMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetPrintColourMode), wxe_util:rec(?wxStyledTextCtrl_GetPrintColourMode). -%% @equiv findText(This,MinPos,MaxPos,Text, []) +-doc(#{equiv => findText(This,MinPos,MaxPos,Text, [])}). -spec findText(This, MinPos, MaxPos, Text) -> integer() when This::wxStyledTextCtrl(), MinPos::integer(), MaxPos::integer(), Text::unicode:chardata(). @@ -1862,15 +1679,17 @@ findText(This,MinPos,MaxPos,Text) when is_record(This, wx_ref),is_integer(MinPos),is_integer(MaxPos),?is_chardata(Text) -> findText(This,MinPos,MaxPos,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlfindtext">external documentation</a>. -doc """ -`Find some text in the document. @param minPos The position (starting from zero) in the document at which to begin the search @param maxPos The last position (starting from zero) in the document to which the search will be restricted. @param text The text to search for. @param flags (Optional) The search flags. This should be a bit list containing one or more of the @link wxStyledTextCtrl::wxSTC_FIND_WHOLEWORD wxSTC_FIND_* @endlink constants.` +` Find some text in the document. @param minPos The position (starting from zero) in the +document at which to begin the search @param maxPos The last position (starting from zero) +in the document to which the search will be restricted. @param text The text to search +for. @param flags (Optional) The search flags. This should be a bit list containing one or +more of the @link wxStyledTextCtrl::wxSTC_FIND_WHOLEWORD wxSTC_FIND_* @endlink constants. ` -Return: The position (starting from zero) in the document at which the text was -found or wxSTC_INVALID_POSITION if the search fails. +Return: The position (starting from zero) in the document at which the text was found or +wxSTC_INVALID_POSITION if the search fails. -Remark: A backwards search can be performed by setting minPos to be greater than -maxPos. +Remark: A backwards search can be performed by setting minPos to be greater than maxPos. """. -spec findText(This, MinPos, MaxPos, Text, [Option]) -> integer() when This::wxStyledTextCtrl(), MinPos::integer(), MaxPos::integer(), Text::unicode:chardata(), @@ -1885,7 +1704,6 @@ findText(#wx_ref{type=ThisT}=This,MinPos,MaxPos,Text, Options) wxe_util:queue_cmd(This,MinPos,MaxPos,Text_UC, Opts,?get_env(),?wxStyledTextCtrl_FindText), wxe_util:rec(?wxStyledTextCtrl_FindText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlformatrange">external documentation</a>. -doc "On Windows, will draw the document into a display context such as a printer.". -spec formatRange(This, DoDraw, StartPos, EndPos, Draw, Target, RenderRect, PageRect) -> integer() when This::wxStyledTextCtrl(), DoDraw::boolean(), StartPos::integer(), EndPos::integer(), Draw::wxDC:wxDC(), Target::wxDC:wxDC(), RenderRect::{X::integer(), Y::integer(), W::integer(), H::integer()}, PageRect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -1897,7 +1715,6 @@ formatRange(#wx_ref{type=ThisT}=This,DoDraw,StartPos,EndPos,#wx_ref{type=DrawT}= wxe_util:queue_cmd(This,DoDraw,StartPos,EndPos,Draw,Target,RenderRect,PageRect,?get_env(),?wxStyledTextCtrl_FormatRange), wxe_util:rec(?wxStyledTextCtrl_FormatRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetfirstvisibleline">external documentation</a>. -doc "Retrieve the display line at the top of the display.". -spec getFirstVisibleLine(This) -> integer() when This::wxStyledTextCtrl(). @@ -1906,7 +1723,6 @@ getFirstVisibleLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetFirstVisibleLine), wxe_util:rec(?wxStyledTextCtrl_GetFirstVisibleLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetline">external documentation</a>. -doc "Retrieve the contents of a line.". -spec getLine(This, Line) -> unicode:charlist() when This::wxStyledTextCtrl(), Line::integer(). @@ -1916,7 +1732,6 @@ getLine(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLine), wxe_util:rec(?wxStyledTextCtrl_GetLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlinecount">external documentation</a>. -doc """ Returns the number of lines in the document. @@ -1929,7 +1744,6 @@ getLineCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetLineCount), wxe_util:rec(?wxStyledTextCtrl_GetLineCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmarginleft">external documentation</a>. -doc "Sets the size in pixels of the left margin.". -spec setMarginLeft(This, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), PixelWidth::integer(). @@ -1938,7 +1752,6 @@ setMarginLeft(#wx_ref{type=ThisT}=This,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PixelWidth,?get_env(),?wxStyledTextCtrl_SetMarginLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmarginleft">external documentation</a>. -doc "Returns the size in pixels of the left margin.". -spec getMarginLeft(This) -> integer() when This::wxStyledTextCtrl(). @@ -1947,7 +1760,6 @@ getMarginLeft(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetMarginLeft), wxe_util:rec(?wxStyledTextCtrl_GetMarginLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmarginright">external documentation</a>. -doc "Sets the size in pixels of the right margin.". -spec setMarginRight(This, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), PixelWidth::integer(). @@ -1956,7 +1768,6 @@ setMarginRight(#wx_ref{type=ThisT}=This,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PixelWidth,?get_env(),?wxStyledTextCtrl_SetMarginRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmarginright">external documentation</a>. -doc "Returns the size in pixels of the right margin.". -spec getMarginRight(This) -> integer() when This::wxStyledTextCtrl(). @@ -1965,7 +1776,6 @@ getMarginRight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetMarginRight), wxe_util:rec(?wxStyledTextCtrl_GetMarginRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmodify">external documentation</a>. -doc "Is the document different from when it was last saved?". -spec getModify(This) -> boolean() when This::wxStyledTextCtrl(). @@ -1974,10 +1784,9 @@ getModify(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetModify), wxe_util:rec(?wxStyledTextCtrl_GetModify). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselection">external documentation</a>. -doc """ -Selects the text starting at the first position up to (but not including) the -character at the last position. +Selects the text starting at the first position up to (but not including) the character +at the last position. If both parameters are equal to -1 all text in the control is selected. @@ -1992,7 +1801,6 @@ setSelection(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,From,To,?get_env(),?wxStyledTextCtrl_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselectedtext">external documentation</a>. -doc "Retrieve the selected text.". -spec getSelectedText(This) -> unicode:charlist() when This::wxStyledTextCtrl(). @@ -2001,7 +1809,6 @@ getSelectedText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelectedText), wxe_util:rec(?wxStyledTextCtrl_GetSelectedText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettextrange">external documentation</a>. -doc "Retrieve a range of text.". -spec getTextRange(This, StartPos, EndPos) -> unicode:charlist() when This::wxStyledTextCtrl(), StartPos::integer(), EndPos::integer(). @@ -2011,7 +1818,6 @@ getTextRange(#wx_ref{type=ThisT}=This,StartPos,EndPos) wxe_util:queue_cmd(This,StartPos,EndPos,?get_env(),?wxStyledTextCtrl_GetTextRange), wxe_util:rec(?wxStyledTextCtrl_GetTextRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhideselection">external documentation</a>. -doc "Draw the selection in normal style or with selection highlighted.". -spec hideSelection(This, Hide) -> 'ok' when This::wxStyledTextCtrl(), Hide::boolean(). @@ -2020,7 +1826,6 @@ hideSelection(#wx_ref{type=ThisT}=This,Hide) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Hide,?get_env(),?wxStyledTextCtrl_HideSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinefromposition">external documentation</a>. -doc "Retrieve the line containing a position.". -spec lineFromPosition(This, Pos) -> integer() when This::wxStyledTextCtrl(), Pos::integer(). @@ -2030,7 +1835,6 @@ lineFromPosition(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_LineFromPosition), wxe_util:rec(?wxStyledTextCtrl_LineFromPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpositionfromline">external documentation</a>. -doc "Retrieve the position at the start of a line.". -spec positionFromLine(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -2040,7 +1844,6 @@ positionFromLine(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_PositionFromLine), wxe_util:rec(?wxStyledTextCtrl_PositionFromLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinescroll">external documentation</a>. -doc "Scroll horizontally and vertically.". -spec lineScroll(This, Columns, Lines) -> 'ok' when This::wxStyledTextCtrl(), Columns::integer(), Lines::integer(). @@ -2049,7 +1852,6 @@ lineScroll(#wx_ref{type=ThisT}=This,Columns,Lines) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Columns,Lines,?get_env(),?wxStyledTextCtrl_LineScroll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlensurecaretvisible">external documentation</a>. -doc "Ensure the caret is visible.". -spec ensureCaretVisible(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2057,7 +1859,6 @@ ensureCaretVisible(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_EnsureCaretVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlreplaceselection">external documentation</a>. -doc "Replace the selected text with the argument text.". -spec replaceSelection(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -2067,7 +1868,6 @@ replaceSelection(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_ReplaceSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetreadonly">external documentation</a>. -doc "Set to read only or read write.". -spec setReadOnly(This, ReadOnly) -> 'ok' when This::wxStyledTextCtrl(), ReadOnly::boolean(). @@ -2076,7 +1876,6 @@ setReadOnly(#wx_ref{type=ThisT}=This,ReadOnly) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,ReadOnly,?get_env(),?wxStyledTextCtrl_SetReadOnly). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcanpaste">external documentation</a>. -doc "Will a paste succeed?". -spec canPaste(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2085,7 +1884,6 @@ canPaste(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CanPaste), wxe_util:rec(?wxStyledTextCtrl_CanPaste). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcanundo">external documentation</a>. -doc "Are there any undoable actions in the undo history?". -spec canUndo(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2094,7 +1892,6 @@ canUndo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CanUndo), wxe_util:rec(?wxStyledTextCtrl_CanUndo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlemptyundobuffer">external documentation</a>. -doc "Delete the undo history.". -spec emptyUndoBuffer(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2102,7 +1899,6 @@ emptyUndoBuffer(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_EmptyUndoBuffer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlundo">external documentation</a>. -doc "Undo one action in the undo history.". -spec undo(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2110,7 +1906,6 @@ undo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Undo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcut">external documentation</a>. -doc "Cut the selection to the clipboard.". -spec cut(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2118,7 +1913,6 @@ cut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Cut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcopy">external documentation</a>. -doc "Copy the selection to the clipboard.". -spec copy(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2126,7 +1920,6 @@ copy(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Copy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpaste">external documentation</a>. -doc "Paste the contents of the clipboard into the document replacing the selection.". -spec paste(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2134,7 +1927,6 @@ paste(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Paste). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlclear">external documentation</a>. -doc "Clear the selection.". -spec clear(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2142,7 +1934,6 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Clear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettext">external documentation</a>. -doc "Replace the contents of the document with the argument text.". -spec setText(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -2152,7 +1943,6 @@ setText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_SetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettext">external documentation</a>. -doc "Retrieve all the text in the document.". -spec getText(This) -> unicode:charlist() when This::wxStyledTextCtrl(). @@ -2161,7 +1951,6 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetText), wxe_util:rec(?wxStyledTextCtrl_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettextlength">external documentation</a>. -doc "Retrieve the number of characters in the document.". -spec getTextLength(This) -> integer() when This::wxStyledTextCtrl(). @@ -2170,7 +1959,6 @@ getTextLength(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTextLength), wxe_util:rec(?wxStyledTextCtrl_GetTextLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetovertype">external documentation</a>. -doc "Returns true if overtype mode is active otherwise false is returned.". -spec getOvertype(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2179,7 +1967,6 @@ getOvertype(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetOvertype), wxe_util:rec(?wxStyledTextCtrl_GetOvertype). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretwidth">external documentation</a>. -doc "Set the width of the insert mode caret.". -spec setCaretWidth(This, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), PixelWidth::integer(). @@ -2188,7 +1975,6 @@ setCaretWidth(#wx_ref{type=ThisT}=This,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PixelWidth,?get_env(),?wxStyledTextCtrl_SetCaretWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretwidth">external documentation</a>. -doc "Returns the width of the insert mode caret.". -spec getCaretWidth(This) -> integer() when This::wxStyledTextCtrl(). @@ -2197,10 +1983,9 @@ getCaretWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretWidth), wxe_util:rec(?wxStyledTextCtrl_GetCaretWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettargetstart">external documentation</a>. -doc """ -Sets the position that starts the target which is used for updating the document -without affecting the scroll position. +Sets the position that starts the target which is used for updating the document without +affecting the scroll position. """. -spec setTargetStart(This, Start) -> 'ok' when This::wxStyledTextCtrl(), Start::integer(). @@ -2209,7 +1994,6 @@ setTargetStart(#wx_ref{type=ThisT}=This,Start) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Start,?get_env(),?wxStyledTextCtrl_SetTargetStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettargetstart">external documentation</a>. -doc "Get the position that starts the target.". -spec getTargetStart(This) -> integer() when This::wxStyledTextCtrl(). @@ -2218,10 +2002,9 @@ getTargetStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTargetStart), wxe_util:rec(?wxStyledTextCtrl_GetTargetStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettargetend">external documentation</a>. -doc """ -Sets the position that ends the target which is used for updating the document -without affecting the scroll position. +Sets the position that ends the target which is used for updating the document without +affecting the scroll position. """. -spec setTargetEnd(This, End) -> 'ok' when This::wxStyledTextCtrl(), End::integer(). @@ -2230,7 +2013,6 @@ setTargetEnd(#wx_ref{type=ThisT}=This,End) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,End,?get_env(),?wxStyledTextCtrl_SetTargetEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettargetend">external documentation</a>. -doc "Get the position that ends the target.". -spec getTargetEnd(This) -> integer() when This::wxStyledTextCtrl(). @@ -2239,12 +2021,10 @@ getTargetEnd(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTargetEnd), wxe_util:rec(?wxStyledTextCtrl_GetTargetEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlreplacetarget">external documentation</a>. -doc """ Replace the target text with the argument text. -Text is counted so it can contain NULs. Returns the length of the replacement -text. +Text is counted so it can contain NULs. Returns the length of the replacement text. """. -spec replaceTarget(This, Text) -> integer() when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -2255,12 +2035,11 @@ replaceTarget(#wx_ref{type=ThisT}=This,Text) wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_ReplaceTarget), wxe_util:rec(?wxStyledTextCtrl_ReplaceTarget). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsearchintarget">external documentation</a>. -doc """ Search for a counted string in the target and set the target to the found range. -Text is counted so it can contain NULs. Returns length of range or -1 for -failure in which case target is not moved. +Text is counted so it can contain NULs. Returns length of range or -1 for failure in +which case target is not moved. """. -spec searchInTarget(This, Text) -> integer() when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -2271,12 +2050,10 @@ searchInTarget(#wx_ref{type=ThisT}=This,Text) wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_SearchInTarget), wxe_util:rec(?wxStyledTextCtrl_SearchInTarget). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetsearchflags">external documentation</a>. -doc """ Set the search flags used by SearchInTarget. -The input should be a bit list containing one or more of the ?wxSTC*FIND*\* -constants. +The input should be a bit list containing one or more of the ?wxSTC\_FIND\_\* constants. """. -spec setSearchFlags(This, SearchFlags) -> 'ok' when This::wxStyledTextCtrl(), SearchFlags::integer(). @@ -2285,11 +2062,10 @@ setSearchFlags(#wx_ref{type=ThisT}=This,SearchFlags) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,SearchFlags,?get_env(),?wxStyledTextCtrl_SetSearchFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetsearchflags">external documentation</a>. -doc """ Get the search flags used by SearchInTarget. -The return value will be a bit list containing one or more of the ?wxSTC*FIND*\* +The return value will be a bit list containing one or more of the ?wxSTC\_FIND\_\* constants. """. -spec getSearchFlags(This) -> integer() when @@ -2299,7 +2075,6 @@ getSearchFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSearchFlags), wxe_util:rec(?wxStyledTextCtrl_GetSearchFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipshow">external documentation</a>. -doc "Show a call tip containing a definition near position pos.". -spec callTipShow(This, Pos, Definition) -> 'ok' when This::wxStyledTextCtrl(), Pos::integer(), Definition::unicode:chardata(). @@ -2309,7 +2084,6 @@ callTipShow(#wx_ref{type=ThisT}=This,Pos,Definition) Definition_UC = unicode:characters_to_binary(Definition), wxe_util:queue_cmd(This,Pos,Definition_UC,?get_env(),?wxStyledTextCtrl_CallTipShow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipcancel">external documentation</a>. -doc "Remove the call tip from the screen.". -spec callTipCancel(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2317,7 +2091,6 @@ callTipCancel(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CallTipCancel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipactive">external documentation</a>. -doc "Is there an active call tip?". -spec callTipActive(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2326,7 +2099,6 @@ callTipActive(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CallTipActive), wxe_util:rec(?wxStyledTextCtrl_CallTipActive). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipposatstart">external documentation</a>. -doc """ Retrieve the position where the caret was before displaying the call tip. @@ -2339,7 +2111,6 @@ callTipPosAtStart(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CallTipPosAtStart), wxe_util:rec(?wxStyledTextCtrl_CallTipPosAtStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipsethighlight">external documentation</a>. -doc "Highlight a segment of the definition.". -spec callTipSetHighlight(This, HighlightStart, HighlightEnd) -> 'ok' when This::wxStyledTextCtrl(), HighlightStart::integer(), HighlightEnd::integer(). @@ -2348,7 +2119,6 @@ callTipSetHighlight(#wx_ref{type=ThisT}=This,HighlightStart,HighlightEnd) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,HighlightStart,HighlightEnd,?get_env(),?wxStyledTextCtrl_CallTipSetHighlight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipsetbackground">external documentation</a>. -doc "Set the background colour for the call tip.". -spec callTipSetBackground(This, Back) -> 'ok' when This::wxStyledTextCtrl(), Back::wx:wx_colour(). @@ -2357,7 +2127,6 @@ callTipSetBackground(#wx_ref{type=ThisT}=This,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_CallTipSetBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipsetforeground">external documentation</a>. -doc "Set the foreground colour for the call tip.". -spec callTipSetForeground(This, Fore) -> 'ok' when This::wxStyledTextCtrl(), Fore::wx:wx_colour(). @@ -2366,7 +2135,6 @@ callTipSetForeground(#wx_ref{type=ThisT}=This,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_CallTipSetForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipsetforegroundhighlight">external documentation</a>. -doc "Set the foreground colour for the highlighted part of the call tip.". -spec callTipSetForegroundHighlight(This, Fore) -> 'ok' when This::wxStyledTextCtrl(), Fore::wx:wx_colour(). @@ -2375,8 +2143,7 @@ callTipSetForegroundHighlight(#wx_ref{type=ThisT}=This,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_CallTipSetForegroundHighlight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcalltipusestyle">external documentation</a>. --doc "Enable use of wxSTC_STYLE_CALLTIP and set call tip tab size in pixels.". +-doc "Enable use of wxSTC\_STYLE\_CALLTIP and set call tip tab size in pixels.". -spec callTipUseStyle(This, TabSize) -> 'ok' when This::wxStyledTextCtrl(), TabSize::integer(). callTipUseStyle(#wx_ref{type=ThisT}=This,TabSize) @@ -2384,7 +2151,6 @@ callTipUseStyle(#wx_ref{type=ThisT}=This,TabSize) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,TabSize,?get_env(),?wxStyledTextCtrl_CallTipUseStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvisiblefromdocline">external documentation</a>. -doc "Find the display line of a document line taking hidden lines into account.". -spec visibleFromDocLine(This, DocLine) -> integer() when This::wxStyledTextCtrl(), DocLine::integer(). @@ -2394,7 +2160,6 @@ visibleFromDocLine(#wx_ref{type=ThisT}=This,DocLine) wxe_util:queue_cmd(This,DocLine,?get_env(),?wxStyledTextCtrl_VisibleFromDocLine), wxe_util:rec(?wxStyledTextCtrl_VisibleFromDocLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldoclinefromvisible">external documentation</a>. -doc "Find the document line of a display line taking hidden lines into account.". -spec docLineFromVisible(This, DisplayLine) -> integer() when This::wxStyledTextCtrl(), DisplayLine::integer(). @@ -2404,7 +2169,6 @@ docLineFromVisible(#wx_ref{type=ThisT}=This,DisplayLine) wxe_util:queue_cmd(This,DisplayLine,?get_env(),?wxStyledTextCtrl_DocLineFromVisible), wxe_util:rec(?wxStyledTextCtrl_DocLineFromVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwrapcount">external documentation</a>. -doc "The number of display lines needed to wrap a document line.". -spec wrapCount(This, DocLine) -> integer() when This::wxStyledTextCtrl(), DocLine::integer(). @@ -2414,12 +2178,11 @@ wrapCount(#wx_ref{type=ThisT}=This,DocLine) wxe_util:queue_cmd(This,DocLine,?get_env(),?wxStyledTextCtrl_WrapCount), wxe_util:rec(?wxStyledTextCtrl_WrapCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetfoldlevel">external documentation</a>. -doc """ Set the fold level of a line. -This encodes an integer level along with flags indicating whether the line is a -header and whether it is effectively white space. +This encodes an integer level along with flags indicating whether the line is a header +and whether it is effectively white space. """. -spec setFoldLevel(This, Line, Level) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), Level::integer(). @@ -2428,7 +2191,6 @@ setFoldLevel(#wx_ref{type=ThisT}=This,Line,Level) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,Level,?get_env(),?wxStyledTextCtrl_SetFoldLevel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetfoldlevel">external documentation</a>. -doc "Retrieve the fold level of a line.". -spec getFoldLevel(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -2438,7 +2200,6 @@ getFoldLevel(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetFoldLevel), wxe_util:rec(?wxStyledTextCtrl_GetFoldLevel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlastchild">external documentation</a>. -doc "Find the last child line of a header line.". -spec getLastChild(This, Line, Level) -> integer() when This::wxStyledTextCtrl(), Line::integer(), Level::integer(). @@ -2448,7 +2209,6 @@ getLastChild(#wx_ref{type=ThisT}=This,Line,Level) wxe_util:queue_cmd(This,Line,Level,?get_env(),?wxStyledTextCtrl_GetLastChild), wxe_util:rec(?wxStyledTextCtrl_GetLastChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetfoldparent">external documentation</a>. -doc "Find the parent line of a child line.". -spec getFoldParent(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -2458,7 +2218,6 @@ getFoldParent(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetFoldParent), wxe_util:rec(?wxStyledTextCtrl_GetFoldParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlshowlines">external documentation</a>. -doc "Make a range of lines visible.". -spec showLines(This, LineStart, LineEnd) -> 'ok' when This::wxStyledTextCtrl(), LineStart::integer(), LineEnd::integer(). @@ -2467,7 +2226,6 @@ showLines(#wx_ref{type=ThisT}=This,LineStart,LineEnd) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,LineStart,LineEnd,?get_env(),?wxStyledTextCtrl_ShowLines). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhidelines">external documentation</a>. -doc "Make a range of lines invisible.". -spec hideLines(This, LineStart, LineEnd) -> 'ok' when This::wxStyledTextCtrl(), LineStart::integer(), LineEnd::integer(). @@ -2476,7 +2234,6 @@ hideLines(#wx_ref{type=ThisT}=This,LineStart,LineEnd) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,LineStart,LineEnd,?get_env(),?wxStyledTextCtrl_HideLines). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlinevisible">external documentation</a>. -doc "Is a line visible?". -spec getLineVisible(This, Line) -> boolean() when This::wxStyledTextCtrl(), Line::integer(). @@ -2486,7 +2243,6 @@ getLineVisible(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineVisible), wxe_util:rec(?wxStyledTextCtrl_GetLineVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetfoldexpanded">external documentation</a>. -doc "Show the children of a header line.". -spec setFoldExpanded(This, Line, Expanded) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(), Expanded::boolean(). @@ -2495,7 +2251,6 @@ setFoldExpanded(#wx_ref{type=ThisT}=This,Line,Expanded) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,Expanded,?get_env(),?wxStyledTextCtrl_SetFoldExpanded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetfoldexpanded">external documentation</a>. -doc "Is a header line expanded?". -spec getFoldExpanded(This, Line) -> boolean() when This::wxStyledTextCtrl(), Line::integer(). @@ -2505,7 +2260,6 @@ getFoldExpanded(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetFoldExpanded), wxe_util:rec(?wxStyledTextCtrl_GetFoldExpanded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltogglefold">external documentation</a>. -doc "Switch a header line between expanded and contracted.". -spec toggleFold(This, Line) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(). @@ -2514,7 +2268,6 @@ toggleFold(#wx_ref{type=ThisT}=This,Line) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_ToggleFold). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlensurevisible">external documentation</a>. -doc "Ensure a particular line is visible by expanding any header line hiding it.". -spec ensureVisible(This, Line) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(). @@ -2523,12 +2276,11 @@ ensureVisible(#wx_ref{type=ThisT}=This,Line) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_EnsureVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetfoldflags">external documentation</a>. -doc """ Set some style options for folding. The second argument should be a bit list containing one or more of the -?wxSTC*FOLDFLAG*\* constants. +?wxSTC\_FOLDFLAG\_\* constants. """. -spec setFoldFlags(This, Flags) -> 'ok' when This::wxStyledTextCtrl(), Flags::integer(). @@ -2537,7 +2289,6 @@ setFoldFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Flags,?get_env(),?wxStyledTextCtrl_SetFoldFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlensurevisibleenforcepolicy">external documentation</a>. -doc """ Ensure a particular line is visible by expanding any header line hiding it. @@ -2550,7 +2301,6 @@ ensureVisibleEnforcePolicy(#wx_ref{type=ThisT}=This,Line) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_EnsureVisibleEnforcePolicy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettabindents">external documentation</a>. -doc "Sets whether a tab pressed when caret is within indentation indents.". -spec setTabIndents(This, TabIndents) -> 'ok' when This::wxStyledTextCtrl(), TabIndents::boolean(). @@ -2559,7 +2309,6 @@ setTabIndents(#wx_ref{type=ThisT}=This,TabIndents) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,TabIndents,?get_env(),?wxStyledTextCtrl_SetTabIndents). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettabindents">external documentation</a>. -doc "Does a tab pressed when caret is within indentation indent?". -spec getTabIndents(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2568,7 +2317,6 @@ getTabIndents(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTabIndents), wxe_util:rec(?wxStyledTextCtrl_GetTabIndents). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetbackspaceunindents">external documentation</a>. -doc "Sets whether a backspace pressed when caret is within indentation unindents.". -spec setBackSpaceUnIndents(This, BsUnIndents) -> 'ok' when This::wxStyledTextCtrl(), BsUnIndents::boolean(). @@ -2577,7 +2325,6 @@ setBackSpaceUnIndents(#wx_ref{type=ThisT}=This,BsUnIndents) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,BsUnIndents,?get_env(),?wxStyledTextCtrl_SetBackSpaceUnIndents). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetbackspaceunindents">external documentation</a>. -doc "Does a backspace pressed when caret is within indentation unindent?". -spec getBackSpaceUnIndents(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2586,7 +2333,6 @@ getBackSpaceUnIndents(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetBackSpaceUnIndents), wxe_util:rec(?wxStyledTextCtrl_GetBackSpaceUnIndents). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmousedwelltime">external documentation</a>. -doc """ Sets the time the mouse must sit still to generate a mouse dwell event. @@ -2599,7 +2345,6 @@ setMouseDwellTime(#wx_ref{type=ThisT}=This,PeriodMilliseconds) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PeriodMilliseconds,?get_env(),?wxStyledTextCtrl_SetMouseDwellTime). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmousedwelltime">external documentation</a>. -doc """ Retrieve the time the mouse must sit still to generate a mouse dwell event. @@ -2612,7 +2357,6 @@ getMouseDwellTime(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetMouseDwellTime), wxe_util:rec(?wxStyledTextCtrl_GetMouseDwellTime). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordstartposition">external documentation</a>. -doc "Get position of start of word.". -spec wordStartPosition(This, Pos, OnlyWordCharacters) -> integer() when This::wxStyledTextCtrl(), Pos::integer(), OnlyWordCharacters::boolean(). @@ -2622,7 +2366,6 @@ wordStartPosition(#wx_ref{type=ThisT}=This,Pos,OnlyWordCharacters) wxe_util:queue_cmd(This,Pos,OnlyWordCharacters,?get_env(),?wxStyledTextCtrl_WordStartPosition), wxe_util:rec(?wxStyledTextCtrl_WordStartPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordendposition">external documentation</a>. -doc "Get position of end of word.". -spec wordEndPosition(This, Pos, OnlyWordCharacters) -> integer() when This::wxStyledTextCtrl(), Pos::integer(), OnlyWordCharacters::boolean(). @@ -2632,11 +2375,10 @@ wordEndPosition(#wx_ref{type=ThisT}=This,Pos,OnlyWordCharacters) wxe_util:queue_cmd(This,Pos,OnlyWordCharacters,?get_env(),?wxStyledTextCtrl_WordEndPosition), wxe_util:rec(?wxStyledTextCtrl_WordEndPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwrapmode">external documentation</a>. -doc """ Sets whether text is word wrapped. -The input should be one of the ?wxSTC*WRAP*\* constants. +The input should be one of the ?wxSTC\_WRAP\_\* constants. """. -spec setWrapMode(This, WrapMode) -> 'ok' when This::wxStyledTextCtrl(), WrapMode::integer(). @@ -2645,11 +2387,10 @@ setWrapMode(#wx_ref{type=ThisT}=This,WrapMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,WrapMode,?get_env(),?wxStyledTextCtrl_SetWrapMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetwrapmode">external documentation</a>. -doc """ Retrieve whether text is word wrapped. -The return value will be one of the ?wxSTC*WRAP*\* constants. +The return value will be one of the ?wxSTC\_WRAP\_\* constants. """. -spec getWrapMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -2658,12 +2399,11 @@ getWrapMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetWrapMode), wxe_util:rec(?wxStyledTextCtrl_GetWrapMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwrapvisualflags">external documentation</a>. -doc """ Set the display mode of visual flags for wrapped lines. -The input should be a bit list containing one or more of the -?wxSTC*WRAPVISUALFLAG*\* constants. +The input should be a bit list containing one or more of the ?wxSTC\_WRAPVISUALFLAG\_\* +constants. """. -spec setWrapVisualFlags(This, WrapVisualFlags) -> 'ok' when This::wxStyledTextCtrl(), WrapVisualFlags::integer(). @@ -2672,12 +2412,11 @@ setWrapVisualFlags(#wx_ref{type=ThisT}=This,WrapVisualFlags) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,WrapVisualFlags,?get_env(),?wxStyledTextCtrl_SetWrapVisualFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetwrapvisualflags">external documentation</a>. -doc """ Retrieve the display mode of visual flags for wrapped lines. The return value will be a bit list containing one or more of the -?wxSTC*WRAPVISUALFLAG*\* constants. +?wxSTC\_WRAPVISUALFLAG\_\* constants. """. -spec getWrapVisualFlags(This) -> integer() when This::wxStyledTextCtrl(). @@ -2686,12 +2425,11 @@ getWrapVisualFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetWrapVisualFlags), wxe_util:rec(?wxStyledTextCtrl_GetWrapVisualFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwrapvisualflagslocation">external documentation</a>. -doc """ Set the location of visual flags for wrapped lines. The input should be a bit list containing one or more of the -?wxSTC*WRAPVISUALFLAGLOC*\* constants. +?wxSTC\_WRAPVISUALFLAGLOC\_\* constants. """. -spec setWrapVisualFlagsLocation(This, WrapVisualFlagsLocation) -> 'ok' when This::wxStyledTextCtrl(), WrapVisualFlagsLocation::integer(). @@ -2700,12 +2438,11 @@ setWrapVisualFlagsLocation(#wx_ref{type=ThisT}=This,WrapVisualFlagsLocation) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,WrapVisualFlagsLocation,?get_env(),?wxStyledTextCtrl_SetWrapVisualFlagsLocation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetwrapvisualflagslocation">external documentation</a>. -doc """ Retrieve the location of visual flags for wrapped lines. The return value will be a bit list containing one or more of the -?wxSTC*WRAPVISUALFLAGLOC*\* constants. +?wxSTC\_WRAPVISUALFLAGLOC\_\* constants. """. -spec getWrapVisualFlagsLocation(This) -> integer() when This::wxStyledTextCtrl(). @@ -2714,7 +2451,6 @@ getWrapVisualFlagsLocation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetWrapVisualFlagsLocation), wxe_util:rec(?wxStyledTextCtrl_GetWrapVisualFlagsLocation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwrapstartindent">external documentation</a>. -doc "Set the start indent for wrapped lines.". -spec setWrapStartIndent(This, Indent) -> 'ok' when This::wxStyledTextCtrl(), Indent::integer(). @@ -2723,7 +2459,6 @@ setWrapStartIndent(#wx_ref{type=ThisT}=This,Indent) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Indent,?get_env(),?wxStyledTextCtrl_SetWrapStartIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetwrapstartindent">external documentation</a>. -doc "Retrieve the start indent for wrapped lines.". -spec getWrapStartIndent(This) -> integer() when This::wxStyledTextCtrl(). @@ -2732,11 +2467,10 @@ getWrapStartIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetWrapStartIndent), wxe_util:rec(?wxStyledTextCtrl_GetWrapStartIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlayoutcache">external documentation</a>. -doc """ Sets the degree of caching of layout information. -The input should be one of the ?wxSTC*CACHE*\* constants. +The input should be one of the ?wxSTC\_CACHE\_\* constants. """. -spec setLayoutCache(This, CacheMode) -> 'ok' when This::wxStyledTextCtrl(), CacheMode::integer(). @@ -2745,11 +2479,10 @@ setLayoutCache(#wx_ref{type=ThisT}=This,CacheMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CacheMode,?get_env(),?wxStyledTextCtrl_SetLayoutCache). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlayoutcache">external documentation</a>. -doc """ Retrieve the degree of caching of layout information. -The return value will be one of the ?wxSTC*CACHE*\* constants. +The return value will be one of the ?wxSTC\_CACHE\_\* constants. """. -spec getLayoutCache(This) -> integer() when This::wxStyledTextCtrl(). @@ -2758,7 +2491,6 @@ getLayoutCache(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetLayoutCache), wxe_util:rec(?wxStyledTextCtrl_GetLayoutCache). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetscrollwidth">external documentation</a>. -doc "Sets the document width assumed for scrolling.". -spec setScrollWidth(This, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), PixelWidth::integer(). @@ -2767,7 +2499,6 @@ setScrollWidth(#wx_ref{type=ThisT}=This,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PixelWidth,?get_env(),?wxStyledTextCtrl_SetScrollWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetscrollwidth">external documentation</a>. -doc "Retrieve the document width assumed for scrolling.". -spec getScrollWidth(This) -> integer() when This::wxStyledTextCtrl(). @@ -2776,7 +2507,6 @@ getScrollWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetScrollWidth), wxe_util:rec(?wxStyledTextCtrl_GetScrollWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltextwidth">external documentation</a>. -doc """ Measure the pixel width of some text in a particular style. @@ -2791,11 +2521,7 @@ textWidth(#wx_ref{type=ThisT}=This,Style,Text) wxe_util:queue_cmd(This,Style,Text_UC,?get_env(),?wxStyledTextCtrl_TextWidth), wxe_util:rec(?wxStyledTextCtrl_TextWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetendatlastline">external documentation</a>. --doc """ -Retrieve whether the maximum scroll position has the last line at the bottom of -the view. -""". +-doc "Retrieve whether the maximum scroll position has the last line at the bottom of the view.". -spec getEndAtLastLine(This) -> boolean() when This::wxStyledTextCtrl(). getEndAtLastLine(#wx_ref{type=ThisT}=This) -> @@ -2803,7 +2529,6 @@ getEndAtLastLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEndAtLastLine), wxe_util:rec(?wxStyledTextCtrl_GetEndAtLastLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltextheight">external documentation</a>. -doc "Retrieve the height of a particular line of text in pixels.". -spec textHeight(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -2813,7 +2538,6 @@ textHeight(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_TextHeight), wxe_util:rec(?wxStyledTextCtrl_TextHeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetuseverticalscrollbar">external documentation</a>. -doc "Show or hide the vertical scroll bar.". -spec setUseVerticalScrollBar(This, Visible) -> 'ok' when This::wxStyledTextCtrl(), Visible::boolean(). @@ -2822,7 +2546,6 @@ setUseVerticalScrollBar(#wx_ref{type=ThisT}=This,Visible) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Visible,?get_env(),?wxStyledTextCtrl_SetUseVerticalScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetuseverticalscrollbar">external documentation</a>. -doc "Is the vertical scroll bar visible?". -spec getUseVerticalScrollBar(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2831,7 +2554,6 @@ getUseVerticalScrollBar(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetUseVerticalScrollBar), wxe_util:rec(?wxStyledTextCtrl_GetUseVerticalScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlappendtext">external documentation</a>. -doc "Append a string to the end of the document without changing the selection.". -spec appendText(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::unicode:chardata(). @@ -2841,7 +2563,6 @@ appendText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxStyledTextCtrl_AppendText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettwophasedraw">external documentation</a>. -doc "Is drawing done in two phases with backgrounds drawn before foregrounds?". -spec getTwoPhaseDraw(This) -> boolean() when This::wxStyledTextCtrl(). @@ -2850,10 +2571,9 @@ getTwoPhaseDraw(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTwoPhaseDraw), wxe_util:rec(?wxStyledTextCtrl_GetTwoPhaseDraw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettwophasedraw">external documentation</a>. -doc """ -In twoPhaseDraw mode, drawing is performed in two phases, first the background -and then the foreground. +In twoPhaseDraw mode, drawing is performed in two phases, first the background and then +the foreground. This avoids chopping off characters that overlap the next run. """. @@ -2864,18 +2584,13 @@ setTwoPhaseDraw(#wx_ref{type=ThisT}=This,TwoPhase) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,TwoPhase,?get_env(),?wxStyledTextCtrl_SetTwoPhaseDraw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltargetfromselection">external documentation</a>. --doc """ -Make the target range start and end be the same as the selection range start and -end. -""". +-doc "Make the target range start and end be the same as the selection range start and end.". -spec targetFromSelection(This) -> 'ok' when This::wxStyledTextCtrl(). targetFromSelection(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_TargetFromSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinesjoin">external documentation</a>. -doc "Join the lines in the target.". -spec linesJoin(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2883,10 +2598,9 @@ linesJoin(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LinesJoin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinessplit">external documentation</a>. -doc """ -Split the lines in the target into lines that are less wide than pixelWidth -where possible. +Split the lines in the target into lines that are less wide than pixelWidth where +possible. """. -spec linesSplit(This, PixelWidth) -> 'ok' when This::wxStyledTextCtrl(), PixelWidth::integer(). @@ -2895,7 +2609,6 @@ linesSplit(#wx_ref{type=ThisT}=This,PixelWidth) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PixelWidth,?get_env(),?wxStyledTextCtrl_LinesSplit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetfoldmargincolour">external documentation</a>. -doc "Set one of the colours used as a chequerboard pattern in the fold margin.". -spec setFoldMarginColour(This, UseSetting, Back) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Back::wx:wx_colour(). @@ -2904,7 +2617,6 @@ setFoldMarginColour(#wx_ref{type=ThisT}=This,UseSetting,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_SetFoldMarginColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetfoldmarginhicolour">external documentation</a>. -doc "Set the other colour used as a chequerboard pattern in the fold margin.". -spec setFoldMarginHiColour(This, UseSetting, Fore) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Fore::wx:wx_colour(). @@ -2913,7 +2625,6 @@ setFoldMarginHiColour(#wx_ref{type=ThisT}=This,UseSetting,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_SetFoldMarginHiColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinedown">external documentation</a>. -doc "Move caret down one line.". -spec lineDown(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2921,7 +2632,6 @@ lineDown(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinedownextend">external documentation</a>. -doc "Move caret down one line extending selection to new caret position.". -spec lineDownExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2929,7 +2639,6 @@ lineDownExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineDownExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineup">external documentation</a>. -doc "Move caret up one line.". -spec lineUp(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2937,7 +2646,6 @@ lineUp(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineupextend">external documentation</a>. -doc "Move caret up one line extending selection to new caret position.". -spec lineUpExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2945,7 +2653,6 @@ lineUpExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineUpExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharleft">external documentation</a>. -doc "Move caret left one character.". -spec charLeft(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2953,7 +2660,6 @@ charLeft(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharleftextend">external documentation</a>. -doc "Move caret left one character extending selection to new caret position.". -spec charLeftExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2961,7 +2667,6 @@ charLeftExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharLeftExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharright">external documentation</a>. -doc "Move caret right one character.". -spec charRight(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2969,7 +2674,6 @@ charRight(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharrightextend">external documentation</a>. -doc "Move caret right one character extending selection to new caret position.". -spec charRightExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2977,7 +2681,6 @@ charRightExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharRightExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordleft">external documentation</a>. -doc "Move caret left one word.". -spec wordLeft(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2985,7 +2688,6 @@ wordLeft(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordleftextend">external documentation</a>. -doc "Move caret left one word extending selection to new caret position.". -spec wordLeftExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -2993,7 +2695,6 @@ wordLeftExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordLeftExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordright">external documentation</a>. -doc "Move caret right one word.". -spec wordRight(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3001,7 +2702,6 @@ wordRight(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordrightextend">external documentation</a>. -doc "Move caret right one word extending selection to new caret position.". -spec wordRightExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3009,7 +2709,6 @@ wordRightExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordRightExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhome">external documentation</a>. -doc "Move caret to first position on line.". -spec home(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3017,7 +2716,6 @@ home(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Home). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhomeextend">external documentation</a>. -doc "Move caret to first position on line extending selection to new caret position.". -spec homeExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3025,7 +2723,6 @@ homeExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_HomeExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineend">external documentation</a>. -doc "Move caret to last position on line.". -spec lineEnd(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3033,7 +2730,6 @@ lineEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineendextend">external documentation</a>. -doc "Move caret to last position on line extending selection to new caret position.". -spec lineEndExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3041,7 +2737,6 @@ lineEndExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldocumentstart">external documentation</a>. -doc "Move caret to first position in document.". -spec documentStart(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3049,18 +2744,13 @@ documentStart(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DocumentStart). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldocumentstartextend">external documentation</a>. --doc """ -Move caret to first position in document extending selection to new caret -position. -""". +-doc "Move caret to first position in document extending selection to new caret position.". -spec documentStartExtend(This) -> 'ok' when This::wxStyledTextCtrl(). documentStartExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DocumentStartExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldocumentend">external documentation</a>. -doc "Move caret to last position in document.". -spec documentEnd(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3068,18 +2758,13 @@ documentEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DocumentEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldocumentendextend">external documentation</a>. --doc """ -Move caret to last position in document extending selection to new caret -position. -""". +-doc "Move caret to last position in document extending selection to new caret position.". -spec documentEndExtend(This) -> 'ok' when This::wxStyledTextCtrl(). documentEndExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DocumentEndExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpageup">external documentation</a>. -doc "Move caret one page up.". -spec pageUp(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3087,7 +2772,6 @@ pageUp(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpageupextend">external documentation</a>. -doc "Move caret one page up extending selection to new caret position.". -spec pageUpExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3095,7 +2779,6 @@ pageUpExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageUpExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpagedown">external documentation</a>. -doc "Move caret one page down.". -spec pageDown(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3103,7 +2786,6 @@ pageDown(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpagedownextend">external documentation</a>. -doc "Move caret one page down extending selection to new caret position.". -spec pageDownExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3111,7 +2793,6 @@ pageDownExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageDownExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrledittoggleovertype">external documentation</a>. -doc "Switch from insert to overtype mode or the reverse.". -spec editToggleOvertype(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3119,7 +2800,6 @@ editToggleOvertype(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_EditToggleOvertype). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcancel">external documentation</a>. -doc "Cancel any modes such as call tip or auto-completion list display.". -spec cancel(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3127,7 +2807,6 @@ cancel(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Cancel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldeleteback">external documentation</a>. -doc "Delete the selection or if no selection, the character before the caret.". -spec deleteBack(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3135,10 +2814,8 @@ deleteBack(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DeleteBack). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltab">external documentation</a>. -doc """ -If selection is empty or all on one line replace the selection with a tab -character. +If selection is empty or all on one line replace the selection with a tab character. If more than one line selected, indent the lines. """. @@ -3148,7 +2825,6 @@ tab(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_Tab). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlbacktab">external documentation</a>. -doc "Dedent the selected lines.". -spec backTab(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3156,7 +2832,6 @@ backTab(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_BackTab). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlnewline">external documentation</a>. -doc "Insert a new line, may use a CRLF, CR or LF depending on EOL mode.". -spec newLine(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3164,7 +2839,6 @@ newLine(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_NewLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlformfeed">external documentation</a>. -doc "Insert a Form Feed character.". -spec formFeed(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3172,7 +2846,6 @@ formFeed(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_FormFeed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvchome">external documentation</a>. -doc """ Move caret to before first visible character on line. @@ -3184,7 +2857,6 @@ vCHome(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_VCHome). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvchomeextend">external documentation</a>. -doc "Like VCHome but extending selection to new caret position.". -spec vCHomeExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3192,7 +2864,6 @@ vCHomeExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_VCHomeExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlzoomin">external documentation</a>. -doc "Magnify the displayed text by increasing the sizes by 1 point.". -spec zoomIn(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3200,7 +2871,6 @@ zoomIn(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ZoomIn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlzoomout">external documentation</a>. -doc "Make the displayed text smaller by decreasing the sizes by 1 point.". -spec zoomOut(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3208,7 +2878,6 @@ zoomOut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ZoomOut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldelwordleft">external documentation</a>. -doc "Delete the word to the left of the caret.". -spec delWordLeft(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3216,7 +2885,6 @@ delWordLeft(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DelWordLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldelwordright">external documentation</a>. -doc "Delete the word to the right of the caret.". -spec delWordRight(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3224,7 +2892,6 @@ delWordRight(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DelWordRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinecut">external documentation</a>. -doc "Cut the line containing the caret.". -spec lineCut(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3232,7 +2899,6 @@ lineCut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineCut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinedelete">external documentation</a>. -doc "Delete the line containing the caret.". -spec lineDelete(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3240,7 +2906,6 @@ lineDelete(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineDelete). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinetranspose">external documentation</a>. -doc "Switch the current line with the previous.". -spec lineTranspose(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3248,7 +2913,6 @@ lineTranspose(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineTranspose). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineduplicate">external documentation</a>. -doc "Duplicate the current line.". -spec lineDuplicate(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3256,7 +2920,6 @@ lineDuplicate(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineDuplicate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllowercase">external documentation</a>. -doc "Transform the selection to lower case.". -spec lowerCase(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3264,7 +2927,6 @@ lowerCase(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LowerCase). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrluppercase">external documentation</a>. -doc "Transform the selection to upper case.". -spec upperCase(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3272,7 +2934,6 @@ upperCase(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_UpperCase). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinescrolldown">external documentation</a>. -doc "Scroll the document down, keeping the caret visible.". -spec lineScrollDown(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3280,7 +2941,6 @@ lineScrollDown(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineScrollDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinescrollup">external documentation</a>. -doc "Scroll the document up, keeping the caret visible.". -spec lineScrollUp(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3288,7 +2948,6 @@ lineScrollUp(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineScrollUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldeletebacknotline">external documentation</a>. -doc """ Delete the selection or if no selection, the character before the caret. @@ -3300,7 +2959,6 @@ deleteBackNotLine(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DeleteBackNotLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhomedisplay">external documentation</a>. -doc "Move caret to first position on display line.". -spec homeDisplay(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3308,18 +2966,13 @@ homeDisplay(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_HomeDisplay). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhomedisplayextend">external documentation</a>. --doc """ -Move caret to first position on display line extending selection to new caret -position. -""". +-doc "Move caret to first position on display line extending selection to new caret position.". -spec homeDisplayExtend(This) -> 'ok' when This::wxStyledTextCtrl(). homeDisplayExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_HomeDisplayExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineenddisplay">external documentation</a>. -doc "Move caret to last position on display line.". -spec lineEndDisplay(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3327,21 +2980,16 @@ lineEndDisplay(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndDisplay). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineenddisplayextend">external documentation</a>. --doc """ -Move caret to last position on display line extending selection to new caret -position. -""". +-doc "Move caret to last position on display line extending selection to new caret position.". -spec lineEndDisplayExtend(This) -> 'ok' when This::wxStyledTextCtrl(). lineEndDisplayExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndDisplayExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhomewrapextend">external documentation</a>. -doc """ -Like HomeExtend but when word-wrap is enabled extends first to start of display -line HomeDisplayExtend, then to start of document line HomeExtend. +Like HomeExtend but when word-wrap is enabled extends first to start of display line +HomeDisplayExtend, then to start of document line HomeExtend. """. -spec homeWrapExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3349,7 +2997,6 @@ homeWrapExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_HomeWrapExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineendwrap">external documentation</a>. -doc """ Like LineEnd but when word-wrap is enabled goes first to end of display line LineEndDisplay, then to start of document line LineEnd. @@ -3360,10 +3007,9 @@ lineEndWrap(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndWrap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineendwrapextend">external documentation</a>. -doc """ -Like LineEndExtend but when word-wrap is enabled extends first to end of display -line LineEndDisplayExtend, then to start of document line LineEndExtend. +Like LineEndExtend but when word-wrap is enabled extends first to end of display line +LineEndDisplayExtend, then to start of document line LineEndExtend. """. -spec lineEndWrapExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3371,7 +3017,6 @@ lineEndWrapExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndWrapExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvchomewrap">external documentation</a>. -doc """ Like VCHome but when word-wrap is enabled goes first to start of display line VCHomeDisplay, then behaves like VCHome. @@ -3382,10 +3027,9 @@ vCHomeWrap(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_VCHomeWrap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvchomewrapextend">external documentation</a>. -doc """ -Like VCHomeExtend but when word-wrap is enabled extends first to start of -display line VCHomeDisplayExtend, then behaves like VCHomeExtend. +Like VCHomeExtend but when word-wrap is enabled extends first to start of display line +VCHomeDisplayExtend, then behaves like VCHomeExtend. """. -spec vCHomeWrapExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3393,7 +3037,6 @@ vCHomeWrapExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_VCHomeWrapExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinecopy">external documentation</a>. -doc "Copy the line containing the caret.". -spec lineCopy(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3401,7 +3044,6 @@ lineCopy(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineCopy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlmovecaretinsideview">external documentation</a>. -doc "Move the caret inside current view if it's not there already.". -spec moveCaretInsideView(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3409,7 +3051,6 @@ moveCaretInsideView(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_MoveCaretInsideView). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinelength">external documentation</a>. -doc "How many characters are on a line, including end of line characters?". -spec lineLength(This, Line) -> integer() when This::wxStyledTextCtrl(), Line::integer(). @@ -3419,7 +3060,6 @@ lineLength(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_LineLength), wxe_util:rec(?wxStyledTextCtrl_LineLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlbracehighlight">external documentation</a>. -doc "Highlight the characters at two positions.". -spec braceHighlight(This, PosA, PosB) -> 'ok' when This::wxStyledTextCtrl(), PosA::integer(), PosB::integer(). @@ -3428,7 +3068,6 @@ braceHighlight(#wx_ref{type=ThisT}=This,PosA,PosB) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PosA,PosB,?get_env(),?wxStyledTextCtrl_BraceHighlight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlbracebadlight">external documentation</a>. -doc "Highlight the character at a position indicating there is no matching brace.". -spec braceBadLight(This, Pos) -> 'ok' when This::wxStyledTextCtrl(), Pos::integer(). @@ -3437,8 +3076,7 @@ braceBadLight(#wx_ref{type=ThisT}=This,Pos) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_BraceBadLight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlbracematch">external documentation</a>. --doc "Find the position of a matching brace or wxSTC_INVALID_POSITION if no match.". +-doc "Find the position of a matching brace or wxSTC\_INVALID\_POSITION if no match.". -spec braceMatch(This, Pos) -> integer() when This::wxStyledTextCtrl(), Pos::integer(). braceMatch(#wx_ref{type=ThisT}=This,Pos) @@ -3447,7 +3085,6 @@ braceMatch(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_BraceMatch), wxe_util:rec(?wxStyledTextCtrl_BraceMatch). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetvieweol">external documentation</a>. -doc "Are the end of line characters visible?". -spec getViewEOL(This) -> boolean() when This::wxStyledTextCtrl(). @@ -3456,7 +3093,6 @@ getViewEOL(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetViewEOL), wxe_util:rec(?wxStyledTextCtrl_GetViewEOL). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetvieweol">external documentation</a>. -doc "Make the end of line characters visible or invisible.". -spec setViewEOL(This, Visible) -> 'ok' when This::wxStyledTextCtrl(), Visible::boolean(). @@ -3465,15 +3101,13 @@ setViewEOL(#wx_ref{type=ThisT}=This,Visible) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Visible,?get_env(),?wxStyledTextCtrl_SetViewEOL). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmodeventmask">external documentation</a>. -doc """ Set which document modification events are sent to the container. -The input should be a bit list containing one or more of the ?wxSTC*MOD*_ -constants, the ?wxSTC*PERFORMED*_ constants, wxSTC_STARTACTION, -wxSTC_MULTILINEUNDOREDO, wxSTC_MULTISTEPUNDOREDO, and wxSTC_LASTSTEPINUNDOREDO. -The input can also be wxSTC_MODEVENTMASKALL to indicate that all changes should -generate events. +The input should be a bit list containing one or more of the ?wxSTC\_MOD\_\* constants, +the ?wxSTC\_PERFORMED\_\* constants, wxSTC_STARTACTION, wxSTC_MULTILINEUNDOREDO, +wxSTC_MULTISTEPUNDOREDO, and wxSTC_LASTSTEPINUNDOREDO. The input can also be +wxSTC_MODEVENTMASKALL to indicate that all changes should generate events. """. -spec setModEventMask(This, EventMask) -> 'ok' when This::wxStyledTextCtrl(), EventMask::integer(). @@ -3482,7 +3116,6 @@ setModEventMask(#wx_ref{type=ThisT}=This,EventMask) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,EventMask,?get_env(),?wxStyledTextCtrl_SetModEventMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetedgecolumn">external documentation</a>. -doc "Retrieve the column number which text should be kept within.". -spec getEdgeColumn(This) -> integer() when This::wxStyledTextCtrl(). @@ -3491,7 +3124,6 @@ getEdgeColumn(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEdgeColumn), wxe_util:rec(?wxStyledTextCtrl_GetEdgeColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetedgecolumn">external documentation</a>. -doc """ Set the column number of the edge. @@ -3504,13 +3136,12 @@ setEdgeColumn(#wx_ref{type=ThisT}=This,Column) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Column,?get_env(),?wxStyledTextCtrl_SetEdgeColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetedgemode">external documentation</a>. -doc """ -The edge may be displayed by a line (wxSTC_EDGE_LINE/wxSTC_EDGE_MULTILINE) or by -highlighting text that goes beyond it (wxSTC_EDGE_BACKGROUND) or not displayed -at all (wxSTC_EDGE_NONE). +The edge may be displayed by a line (wxSTC\_EDGE\_LINE/wxSTC\_EDGE\_MULTILINE) or by +highlighting text that goes beyond it (wxSTC\_EDGE\_BACKGROUND) or not displayed at all +(wxSTC\_EDGE\_NONE). -The input should be one of the ?wxSTC*EDGE*\* constants. +The input should be one of the ?wxSTC\_EDGE\_\* constants. """. -spec setEdgeMode(This, EdgeMode) -> 'ok' when This::wxStyledTextCtrl(), EdgeMode::integer(). @@ -3519,11 +3150,10 @@ setEdgeMode(#wx_ref{type=ThisT}=This,EdgeMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,EdgeMode,?get_env(),?wxStyledTextCtrl_SetEdgeMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetedgemode">external documentation</a>. -doc """ Retrieve the edge highlight mode. -The return value will be one of the ?wxSTC*EDGE*\* constants. +The return value will be one of the ?wxSTC\_EDGE\_\* constants. """. -spec getEdgeMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -3532,7 +3162,6 @@ getEdgeMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEdgeMode), wxe_util:rec(?wxStyledTextCtrl_GetEdgeMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetedgecolour">external documentation</a>. -doc "Retrieve the colour used in edge indication.". -spec getEdgeColour(This) -> wx:wx_colour4() when This::wxStyledTextCtrl(). @@ -3541,7 +3170,6 @@ getEdgeColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetEdgeColour), wxe_util:rec(?wxStyledTextCtrl_GetEdgeColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetedgecolour">external documentation</a>. -doc "Change the colour used in edge indication.". -spec setEdgeColour(This, EdgeColour) -> 'ok' when This::wxStyledTextCtrl(), EdgeColour::wx:wx_colour(). @@ -3550,7 +3178,6 @@ setEdgeColour(#wx_ref{type=ThisT}=This,EdgeColour) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,wxe_util:color(EdgeColour),?get_env(),?wxStyledTextCtrl_SetEdgeColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsearchanchor">external documentation</a>. -doc "Sets the current caret position to be the search anchor.". -spec searchAnchor(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3558,7 +3185,6 @@ searchAnchor(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SearchAnchor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsearchnext">external documentation</a>. -doc """ Find some text starting at the search anchor. @@ -3573,7 +3199,6 @@ searchNext(#wx_ref{type=ThisT}=This,SearchFlags,Text) wxe_util:queue_cmd(This,SearchFlags,Text_UC,?get_env(),?wxStyledTextCtrl_SearchNext), wxe_util:rec(?wxStyledTextCtrl_SearchNext). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsearchprev">external documentation</a>. -doc """ Find some text starting at the search anchor and moving backwards. @@ -3588,7 +3213,6 @@ searchPrev(#wx_ref{type=ThisT}=This,SearchFlags,Text) wxe_util:queue_cmd(This,SearchFlags,Text_UC,?get_env(),?wxStyledTextCtrl_SearchPrev), wxe_util:rec(?wxStyledTextCtrl_SearchPrev). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinesonscreen">external documentation</a>. -doc "Retrieves the number of lines completely visible.". -spec linesOnScreen(This) -> integer() when This::wxStyledTextCtrl(). @@ -3597,16 +3221,15 @@ linesOnScreen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LinesOnScreen), wxe_util:rec(?wxStyledTextCtrl_LinesOnScreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlusepopup">external documentation</a>. -doc """ -Set whether a pop up menu is displayed automatically when the user presses the -wrong mouse button on certain areas. +Set whether a pop up menu is displayed automatically when the user presses the wrong +mouse button on certain areas. -The input should be one of the ?wxSTC*POPUP*\* constants. +The input should be one of the ?wxSTC\_POPUP\_\* constants. -Remark: When `m:wxContextMenuEvent` is used to create a custom popup menu, this -function should be called with wxSTC_POPUP_NEVER. Otherwise the default menu -will be shown instead of the custom one. +Remark: When `m:wxContextMenuEvent` is used to create a custom popup menu, this function +should be called with wxSTC_POPUP_NEVER. Otherwise the default menu will be shown instead +of the custom one. """. -spec usePopUp(This, PopUpMode) -> 'ok' when This::wxStyledTextCtrl(), PopUpMode::integer(). @@ -3615,11 +3238,7 @@ usePopUp(#wx_ref{type=ThisT}=This,PopUpMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,PopUpMode,?get_env(),?wxStyledTextCtrl_UsePopUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlselectionisrectangle">external documentation</a>. --doc """ -Is the selection rectangular? The alternative is the more common stream -selection. -""". +-doc "Is the selection rectangular? The alternative is the more common stream selection.". -spec selectionIsRectangle(This) -> boolean() when This::wxStyledTextCtrl(). selectionIsRectangle(#wx_ref{type=ThisT}=This) -> @@ -3627,12 +3246,11 @@ selectionIsRectangle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SelectionIsRectangle), wxe_util:rec(?wxStyledTextCtrl_SelectionIsRectangle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetzoom">external documentation</a>. -doc """ Set the zoom level. -This number of points is added to the size of all fonts. It may be positive to -magnify or negative to reduce. +This number of points is added to the size of all fonts. It may be positive to magnify or +negative to reduce. """. -spec setZoom(This, ZoomInPoints) -> 'ok' when This::wxStyledTextCtrl(), ZoomInPoints::integer(). @@ -3641,7 +3259,6 @@ setZoom(#wx_ref{type=ThisT}=This,ZoomInPoints) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,ZoomInPoints,?get_env(),?wxStyledTextCtrl_SetZoom). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetzoom">external documentation</a>. -doc "Retrieve the zoom level.". -spec getZoom(This) -> integer() when This::wxStyledTextCtrl(). @@ -3650,14 +3267,13 @@ getZoom(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetZoom), wxe_util:rec(?wxStyledTextCtrl_GetZoom). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmodeventmask">external documentation</a>. -doc """ Get which document modification events are sent to the container. -The return value will wxSTC*MODEVENTMASKALL if all changes generate events. -Otherwise it will be a bit list containing one or more of the ?wxSTC_MOD*_ -constants, the ?wxSTC*PERFORMED*_ constants, wxSTC_STARTACTION, -wxSTC_MULTILINEUNDOREDO, wxSTC_MULTISTEPUNDOREDO, and wxSTC_LASTSTEPINUNDOREDO. +The return value will wxSTC_MODEVENTMASKALL if all changes generate events. Otherwise it +will be a bit list containing one or more of the ?wxSTC\_MOD\_\* constants, the +?wxSTC\_PERFORMED\_\* constants, wxSTC_STARTACTION, wxSTC_MULTILINEUNDOREDO, +wxSTC_MULTISTEPUNDOREDO, and wxSTC_LASTSTEPINUNDOREDO. """. -spec getModEventMask(This) -> integer() when This::wxStyledTextCtrl(). @@ -3666,7 +3282,6 @@ getModEventMask(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetModEventMask), wxe_util:rec(?wxStyledTextCtrl_GetModEventMask). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetstcfocus">external documentation</a>. -doc "Change internal focus flag.". -spec setSTCFocus(This, Focus) -> 'ok' when This::wxStyledTextCtrl(), Focus::boolean(). @@ -3675,7 +3290,6 @@ setSTCFocus(#wx_ref{type=ThisT}=This,Focus) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Focus,?get_env(),?wxStyledTextCtrl_SetSTCFocus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstcfocus">external documentation</a>. -doc "Get internal focus flag.". -spec getSTCFocus(This) -> boolean() when This::wxStyledTextCtrl(). @@ -3684,11 +3298,10 @@ getSTCFocus(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSTCFocus), wxe_util:rec(?wxStyledTextCtrl_GetSTCFocus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetstatus">external documentation</a>. -doc """ Change error status - 0 = OK. -The input should be one of the ?wxSTC*STATUS*\* constants. +The input should be one of the ?wxSTC\_STATUS\_\* constants. """. -spec setStatus(This, Status) -> 'ok' when This::wxStyledTextCtrl(), Status::integer(). @@ -3697,11 +3310,10 @@ setStatus(#wx_ref{type=ThisT}=This,Status) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Status,?get_env(),?wxStyledTextCtrl_SetStatus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstatus">external documentation</a>. -doc """ Get error status. -The return value will be one of the ?wxSTC*STATUS*\* constants. +The return value will be one of the ?wxSTC\_STATUS\_\* constants. """. -spec getStatus(This) -> integer() when This::wxStyledTextCtrl(). @@ -3710,7 +3322,6 @@ getStatus(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetStatus), wxe_util:rec(?wxStyledTextCtrl_GetStatus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmousedowncaptures">external documentation</a>. -doc "Set whether the mouse is captured when its button is pressed.". -spec setMouseDownCaptures(This, Captures) -> 'ok' when This::wxStyledTextCtrl(), Captures::boolean(). @@ -3719,7 +3330,6 @@ setMouseDownCaptures(#wx_ref{type=ThisT}=This,Captures) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Captures,?get_env(),?wxStyledTextCtrl_SetMouseDownCaptures). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetmousedowncaptures">external documentation</a>. -doc "Get whether mouse gets captured.". -spec getMouseDownCaptures(This) -> boolean() when This::wxStyledTextCtrl(). @@ -3728,10 +3338,7 @@ getMouseDownCaptures(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetMouseDownCaptures), wxe_util:rec(?wxStyledTextCtrl_GetMouseDownCaptures). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetstccursor">external documentation</a>. --doc """ -Sets the cursor to one of the wxSTC_CURSOR\* values. -""". +-doc "Sets the cursor to one of the wxSTC\_CURSOR\* values.". -spec setSTCCursor(This, CursorType) -> 'ok' when This::wxStyledTextCtrl(), CursorType::integer(). setSTCCursor(#wx_ref{type=ThisT}=This,CursorType) @@ -3739,11 +3346,10 @@ setSTCCursor(#wx_ref{type=ThisT}=This,CursorType) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CursorType,?get_env(),?wxStyledTextCtrl_SetSTCCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstccursor">external documentation</a>. -doc """ Get cursor type. -The return value will be one of the ?wxSTC_CURSOR\* constants. +The return value will be one of the ?wxSTC\_CURSOR\* constants. """. -spec getSTCCursor(This) -> integer() when This::wxStyledTextCtrl(). @@ -3752,10 +3358,9 @@ getSTCCursor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSTCCursor), wxe_util:rec(?wxStyledTextCtrl_GetSTCCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcontrolcharsymbol">external documentation</a>. -doc """ -Change the way control characters are displayed: If symbol is < 32, keep the -drawn way, else, use the given character. +Change the way control characters are displayed: If symbol is *< 32, keep the drawn way, +else, use the given character. """. -spec setControlCharSymbol(This, Symbol) -> 'ok' when This::wxStyledTextCtrl(), Symbol::integer(). @@ -3764,7 +3369,6 @@ setControlCharSymbol(#wx_ref{type=ThisT}=This,Symbol) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Symbol,?get_env(),?wxStyledTextCtrl_SetControlCharSymbol). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcontrolcharsymbol">external documentation</a>. -doc "Get the way control characters are displayed.". -spec getControlCharSymbol(This) -> integer() when This::wxStyledTextCtrl(). @@ -3773,7 +3377,6 @@ getControlCharSymbol(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetControlCharSymbol), wxe_util:rec(?wxStyledTextCtrl_GetControlCharSymbol). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordpartleft">external documentation</a>. -doc "Move to the previous change in capitalisation.". -spec wordPartLeft(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3781,18 +3384,13 @@ wordPartLeft(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordPartLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordpartleftextend">external documentation</a>. --doc """ -Move to the previous change in capitalisation extending selection to new caret -position. -""". +-doc "Move to the previous change in capitalisation extending selection to new caret position.". -spec wordPartLeftExtend(This) -> 'ok' when This::wxStyledTextCtrl(). wordPartLeftExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordPartLeftExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordpartright">external documentation</a>. -doc "Move to the change next in capitalisation.". -spec wordPartRight(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3800,24 +3398,19 @@ wordPartRight(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordPartRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordpartrightextend">external documentation</a>. --doc """ -Move to the next change in capitalisation extending selection to new caret -position. -""". +-doc "Move to the next change in capitalisation extending selection to new caret position.". -spec wordPartRightExtend(This) -> 'ok' when This::wxStyledTextCtrl(). wordPartRightExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordPartRightExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetvisiblepolicy">external documentation</a>. -doc """ -Set the way the display area is determined when a particular line is to be moved -to by Find, FindNext, GotoLine, etc. +Set the way the display area is determined when a particular line is to be moved to by +Find, FindNext, GotoLine, etc. -The first argument should be a bit list containing one or more of the -?wxSTC*VISIBLE*\* constants. +The first argument should be a bit list containing one or more of the ?wxSTC\_VISIBLE\_\* +constants. """. -spec setVisiblePolicy(This, VisiblePolicy, VisibleSlop) -> 'ok' when This::wxStyledTextCtrl(), VisiblePolicy::integer(), VisibleSlop::integer(). @@ -3826,7 +3419,6 @@ setVisiblePolicy(#wx_ref{type=ThisT}=This,VisiblePolicy,VisibleSlop) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,VisiblePolicy,VisibleSlop,?get_env(),?wxStyledTextCtrl_SetVisiblePolicy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldellineleft">external documentation</a>. -doc "Delete back from the current position to the start of the line.". -spec delLineLeft(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3834,7 +3426,6 @@ delLineLeft(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DelLineLeft). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldellineright">external documentation</a>. -doc "Delete forwards from the current position to the end of the line.". -spec delLineRight(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3842,7 +3433,6 @@ delLineRight(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_DelLineRight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetxoffset">external documentation</a>. -doc "Get the xOffset (ie, horizontal scroll position).". -spec getXOffset(This) -> integer() when This::wxStyledTextCtrl(). @@ -3851,7 +3441,6 @@ getXOffset(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetXOffset), wxe_util:rec(?wxStyledTextCtrl_GetXOffset). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlchoosecaretx">external documentation</a>. -doc "Set the last x chosen value to be the caret x position.". -spec chooseCaretX(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3859,14 +3448,13 @@ chooseCaretX(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ChooseCaretX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetxcaretpolicy">external documentation</a>. -doc """ Set the way the caret is kept visible when going sideways. The exclusion zone is given in pixels. -The first argument should be a bit list containing one or more of the -?wxSTC*CARET*\* constants. +The first argument should be a bit list containing one or more of the ?wxSTC\_CARET\_\* +constants. """. -spec setXCaretPolicy(This, CaretPolicy, CaretSlop) -> 'ok' when This::wxStyledTextCtrl(), CaretPolicy::integer(), CaretSlop::integer(). @@ -3875,14 +3463,13 @@ setXCaretPolicy(#wx_ref{type=ThisT}=This,CaretPolicy,CaretSlop) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CaretPolicy,CaretSlop,?get_env(),?wxStyledTextCtrl_SetXCaretPolicy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetycaretpolicy">external documentation</a>. -doc """ Set the way the line the caret is on is kept visible. The exclusion zone is given in lines. -The first argument should be a bit list containing one or more of the -?wxSTC*CARET*\* constants. +The first argument should be a bit list containing one or more of the ?wxSTC\_CARET\_\* +constants. """. -spec setYCaretPolicy(This, CaretPolicy, CaretSlop) -> 'ok' when This::wxStyledTextCtrl(), CaretPolicy::integer(), CaretSlop::integer(). @@ -3891,11 +3478,10 @@ setYCaretPolicy(#wx_ref{type=ThisT}=This,CaretPolicy,CaretSlop) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,CaretPolicy,CaretSlop,?get_env(),?wxStyledTextCtrl_SetYCaretPolicy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetprintwrapmode">external documentation</a>. -doc """ Is printing line wrapped? -The return value will be one of the ?wxSTC*WRAP*\* constants. +The return value will be one of the ?wxSTC\_WRAP\_\* constants. """. -spec getPrintWrapMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -3904,7 +3490,6 @@ getPrintWrapMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetPrintWrapMode), wxe_util:rec(?wxStyledTextCtrl_GetPrintWrapMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethotspotactiveforeground">external documentation</a>. -doc "Set a fore colour for active hotspots.". -spec setHotspotActiveForeground(This, UseSetting, Fore) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Fore::wx:wx_colour(). @@ -3913,7 +3498,6 @@ setHotspotActiveForeground(#wx_ref{type=ThisT}=This,UseSetting,Fore) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Fore),?get_env(),?wxStyledTextCtrl_SetHotspotActiveForeground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethotspotactivebackground">external documentation</a>. -doc "Set a back colour for active hotspots.". -spec setHotspotActiveBackground(This, UseSetting, Back) -> 'ok' when This::wxStyledTextCtrl(), UseSetting::boolean(), Back::wx:wx_colour(). @@ -3922,7 +3506,6 @@ setHotspotActiveBackground(#wx_ref{type=ThisT}=This,UseSetting,Back) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseSetting,wxe_util:color(Back),?get_env(),?wxStyledTextCtrl_SetHotspotActiveBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethotspotactiveunderline">external documentation</a>. -doc "Enable / Disable underlining active hotspots.". -spec setHotspotActiveUnderline(This, Underline) -> 'ok' when This::wxStyledTextCtrl(), Underline::boolean(). @@ -3931,7 +3514,6 @@ setHotspotActiveUnderline(#wx_ref{type=ThisT}=This,Underline) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Underline,?get_env(),?wxStyledTextCtrl_SetHotspotActiveUnderline). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethotspotsingleline">external documentation</a>. -doc "Limit hotspots to single line so hotspots on two lines don't merge.". -spec setHotspotSingleLine(This, SingleLine) -> 'ok' when This::wxStyledTextCtrl(), SingleLine::boolean(). @@ -3940,7 +3522,6 @@ setHotspotSingleLine(#wx_ref{type=ThisT}=This,SingleLine) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,SingleLine,?get_env(),?wxStyledTextCtrl_SetHotspotSingleLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlparadownextend">external documentation</a>. -doc "Extend selection down one paragraph (delimited by empty lines).". -spec paraDownExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3948,7 +3529,6 @@ paraDownExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ParaDownExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlparaup">external documentation</a>. -doc "Move caret up one paragraph (delimited by empty lines).". -spec paraUp(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3956,7 +3536,6 @@ paraUp(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ParaUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlparaupextend">external documentation</a>. -doc "Extend selection up one paragraph (delimited by empty lines).". -spec paraUpExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -3964,10 +3543,9 @@ paraUpExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ParaUpExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpositionbefore">external documentation</a>. -doc """ -Given a valid document position, return the previous position taking code page -into account. +Given a valid document position, return the previous position taking code page into +account. Returns 0 if passed 0. """. @@ -3979,10 +3557,8 @@ positionBefore(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_PositionBefore), wxe_util:rec(?wxStyledTextCtrl_PositionBefore). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpositionafter">external documentation</a>. -doc """ -Given a valid document position, return the next position taking code page into -account. +Given a valid document position, return the next position taking code page into account. Maximum value returned is the last position in the document. """. @@ -3994,7 +3570,6 @@ positionAfter(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_PositionAfter), wxe_util:rec(?wxStyledTextCtrl_PositionAfter). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcopyrange">external documentation</a>. -doc """ Copy a range of text to the clipboard. @@ -4007,7 +3582,6 @@ copyRange(#wx_ref{type=ThisT}=This,Start,End) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Start,End,?get_env(),?wxStyledTextCtrl_CopyRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcopytext">external documentation</a>. -doc "Copy argument text to the clipboard.". -spec copyText(This, Length, Text) -> 'ok' when This::wxStyledTextCtrl(), Length::integer(), Text::unicode:chardata(). @@ -4017,10 +3591,9 @@ copyText(#wx_ref{type=ThisT}=This,Length,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Length,Text_UC,?get_env(),?wxStyledTextCtrl_CopyText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetselectionmode">external documentation</a>. -doc """ -Set the selection mode to stream (wxSTC_SEL_STREAM) or rectangular -(wxSTC_SEL_RECTANGLE/wxSTC_SEL_THIN) or by lines (wxSTC_SEL_LINES). +Set the selection mode to stream (wxSTC\_SEL\_STREAM) or rectangular +(wxSTC\_SEL\_RECTANGLE/wxSTC\_SEL\_THIN) or by lines (wxSTC\_SEL\_LINES). """. -spec setSelectionMode(This, SelectionMode) -> 'ok' when This::wxStyledTextCtrl(), SelectionMode::integer(). @@ -4029,11 +3602,10 @@ setSelectionMode(#wx_ref{type=ThisT}=This,SelectionMode) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,SelectionMode,?get_env(),?wxStyledTextCtrl_SetSelectionMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselectionmode">external documentation</a>. -doc """ Get the mode of the current selection. -The return value will be one of the ?wxSTC*SEL*\* constants. +The return value will be one of the ?wxSTC\_SEL\_\* constants. """. -spec getSelectionMode(This) -> integer() when This::wxStyledTextCtrl(). @@ -4042,7 +3614,6 @@ getSelectionMode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelectionMode), wxe_util:rec(?wxStyledTextCtrl_GetSelectionMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllinedownrectextend">external documentation</a>. -doc "Move caret down one line, extending rectangular selection to new caret position.". -spec lineDownRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4050,7 +3621,6 @@ lineDownRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineDownRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineuprectextend">external documentation</a>. -doc "Move caret up one line, extending rectangular selection to new caret position.". -spec lineUpRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4058,32 +3628,23 @@ lineUpRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineUpRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharleftrectextend">external documentation</a>. --doc """ -Move caret left one character, extending rectangular selection to new caret -position. -""". +-doc "Move caret left one character, extending rectangular selection to new caret position.". -spec charLeftRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). charLeftRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharLeftRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcharrightrectextend">external documentation</a>. --doc """ -Move caret right one character, extending rectangular selection to new caret -position. -""". +-doc "Move caret right one character, extending rectangular selection to new caret position.". -spec charRightRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). charRightRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_CharRightRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlhomerectextend">external documentation</a>. -doc """ -Move caret to first position on line, extending rectangular selection to new -caret position. +Move caret to first position on line, extending rectangular selection to new caret +position. """. -spec homeRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4091,12 +3652,11 @@ homeRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_HomeRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlvchomerectextend">external documentation</a>. -doc """ Move caret to before first visible character on line. -If already there move to first character on line. In either case, extend -rectangular selection to new caret position. +If already there move to first character on line. In either case, extend rectangular +selection to new caret position. """. -spec vCHomeRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4104,10 +3664,9 @@ vCHomeRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_VCHomeRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrllineendrectextend">external documentation</a>. -doc """ -Move caret to last position on line, extending rectangular selection to new -caret position. +Move caret to last position on line, extending rectangular selection to new caret +position. """. -spec lineEndRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4115,7 +3674,6 @@ lineEndRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_LineEndRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpageuprectextend">external documentation</a>. -doc "Move caret one page up, extending rectangular selection to new caret position.". -spec pageUpRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4123,7 +3681,6 @@ pageUpRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageUpRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpagedownrectextend">external documentation</a>. -doc "Move caret one page down, extending rectangular selection to new caret position.". -spec pageDownRectExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4131,7 +3688,6 @@ pageDownRectExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_PageDownRectExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstutteredpageup">external documentation</a>. -doc "Move caret to top of page, or one page up if already at top of page.". -spec stutteredPageUp(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4139,10 +3695,9 @@ stutteredPageUp(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StutteredPageUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstutteredpageupextend">external documentation</a>. -doc """ -Move caret to top of page, or one page up if already at top of page, extending -selection to new caret position. +Move caret to top of page, or one page up if already at top of page, extending selection +to new caret position. """. -spec stutteredPageUpExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4150,7 +3705,6 @@ stutteredPageUpExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StutteredPageUpExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstutteredpagedown">external documentation</a>. -doc "Move caret to bottom of page, or one page down if already at bottom of page.". -spec stutteredPageDown(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4158,10 +3712,9 @@ stutteredPageDown(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StutteredPageDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstutteredpagedownextend">external documentation</a>. -doc """ -Move caret to bottom of page, or one page down if already at bottom of page, -extending selection to new caret position. +Move caret to bottom of page, or one page down if already at bottom of page, extending +selection to new caret position. """. -spec stutteredPageDownExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4169,7 +3722,6 @@ stutteredPageDownExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StutteredPageDownExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordleftend">external documentation</a>. -doc "Move caret left one word, position cursor at end of word.". -spec wordLeftEnd(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4177,10 +3729,9 @@ wordLeftEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordLeftEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordleftendextend">external documentation</a>. -doc """ -Move caret left one word, position cursor at end of word, extending selection to -new caret position. +Move caret left one word, position cursor at end of word, extending selection to new +caret position. """. -spec wordLeftEndExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4188,7 +3739,6 @@ wordLeftEndExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordLeftEndExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordrightend">external documentation</a>. -doc "Move caret right one word, position cursor at end of word.". -spec wordRightEnd(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4196,10 +3746,9 @@ wordRightEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordRightEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlwordrightendextend">external documentation</a>. -doc """ -Move caret right one word, position cursor at end of word, extending selection -to new caret position. +Move caret right one word, position cursor at end of word, extending selection to new +caret position. """. -spec wordRightEndExtend(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4207,10 +3756,8 @@ wordRightEndExtend(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_WordRightEndExtend). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetwhitespacechars">external documentation</a>. -doc """ -Set the set of characters making up whitespace for when moving or selecting by -word. +Set the set of characters making up whitespace for when moving or selecting by word. Should be called after SetWordChars. """. @@ -4222,7 +3769,6 @@ setWhitespaceChars(#wx_ref{type=ThisT}=This,Characters) Characters_UC = unicode:characters_to_binary(Characters), wxe_util:queue_cmd(This,Characters_UC,?get_env(),?wxStyledTextCtrl_SetWhitespaceChars). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcharsdefault">external documentation</a>. -doc "Reset the set of characters for whitespace and word characters to the defaults.". -spec setCharsDefault(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4230,7 +3776,6 @@ setCharsDefault(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SetCharsDefault). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlautocompgetcurrent">external documentation</a>. -doc "Get currently selected item position in the auto-completion list.". -spec autoCompGetCurrent(This) -> integer() when This::wxStyledTextCtrl(). @@ -4239,7 +3784,6 @@ autoCompGetCurrent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_AutoCompGetCurrent), wxe_util:rec(?wxStyledTextCtrl_AutoCompGetCurrent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlallocate">external documentation</a>. -doc "Enlarge the document to a particular size of text bytes.". -spec allocate(This, Bytes) -> 'ok' when This::wxStyledTextCtrl(), Bytes::integer(). @@ -4248,7 +3792,6 @@ allocate(#wx_ref{type=ThisT}=This,Bytes) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Bytes,?get_env(),?wxStyledTextCtrl_Allocate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlfindcolumn">external documentation</a>. -doc """ Find the position of a column on a line taking into account tabs and multi-byte characters. @@ -4263,12 +3806,10 @@ findColumn(#wx_ref{type=ThisT}=This,Line,Column) wxe_util:queue_cmd(This,Line,Column,?get_env(),?wxStyledTextCtrl_FindColumn), wxe_util:rec(?wxStyledTextCtrl_FindColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretsticky">external documentation</a>. -doc """ -Can the caret preferred x position only be changed by explicit movement -commands? +Can the caret preferred x position only be changed by explicit movement commands? -The return value will be one of the ?wxSTC*CARETSTICKY*\* constants. +The return value will be one of the ?wxSTC\_CARETSTICKY\_\* constants. """. -spec getCaretSticky(This) -> integer() when This::wxStyledTextCtrl(). @@ -4277,11 +3818,10 @@ getCaretSticky(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretSticky), wxe_util:rec(?wxStyledTextCtrl_GetCaretSticky). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretsticky">external documentation</a>. -doc """ Stop the caret preferred x position changing when the user types. -The input should be one of the ?wxSTC*CARETSTICKY*\* constants. +The input should be one of the ?wxSTC\_CARETSTICKY\_\* constants. """. -spec setCaretSticky(This, UseCaretStickyBehaviour) -> 'ok' when This::wxStyledTextCtrl(), UseCaretStickyBehaviour::integer(). @@ -4290,7 +3830,6 @@ setCaretSticky(#wx_ref{type=ThisT}=This,UseCaretStickyBehaviour) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,UseCaretStickyBehaviour,?get_env(),?wxStyledTextCtrl_SetCaretSticky). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrltogglecaretsticky">external documentation</a>. -doc "Switch between sticky and non-sticky: meant to be bound to a key.". -spec toggleCaretSticky(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4298,7 +3837,6 @@ toggleCaretSticky(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_ToggleCaretSticky). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetpasteconvertendings">external documentation</a>. -doc "Enable/Disable convert-on-paste for line endings.". -spec setPasteConvertEndings(This, Convert) -> 'ok' when This::wxStyledTextCtrl(), Convert::boolean(). @@ -4307,7 +3845,6 @@ setPasteConvertEndings(#wx_ref{type=ThisT}=This,Convert) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Convert,?get_env(),?wxStyledTextCtrl_SetPasteConvertEndings). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetpasteconvertendings">external documentation</a>. -doc "Get convert-on-paste setting.". -spec getPasteConvertEndings(This) -> boolean() when This::wxStyledTextCtrl(). @@ -4316,7 +3853,6 @@ getPasteConvertEndings(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetPasteConvertEndings), wxe_util:rec(?wxStyledTextCtrl_GetPasteConvertEndings). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlselectionduplicate">external documentation</a>. -doc """ Duplicate the selection. @@ -4328,7 +3864,6 @@ selectionDuplicate(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_SelectionDuplicate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetcaretlinebackalpha">external documentation</a>. -doc "Set background alpha of the caret line.". -spec setCaretLineBackAlpha(This, Alpha) -> 'ok' when This::wxStyledTextCtrl(), Alpha::integer(). @@ -4337,7 +3872,6 @@ setCaretLineBackAlpha(#wx_ref{type=ThisT}=This,Alpha) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Alpha,?get_env(),?wxStyledTextCtrl_SetCaretLineBackAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcaretlinebackalpha">external documentation</a>. -doc "Get the background alpha of the caret line.". -spec getCaretLineBackAlpha(This) -> integer() when This::wxStyledTextCtrl(). @@ -4346,7 +3880,6 @@ getCaretLineBackAlpha(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCaretLineBackAlpha), wxe_util:rec(?wxStyledTextCtrl_GetCaretLineBackAlpha). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstartrecord">external documentation</a>. -doc "Start notifying the container of all key presses and commands.". -spec startRecord(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4354,7 +3887,6 @@ startRecord(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StartRecord). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstoprecord">external documentation</a>. -doc "Stop notifying the container of all key presses and commands.". -spec stopRecord(This) -> 'ok' when This::wxStyledTextCtrl(). @@ -4362,11 +3894,10 @@ stopRecord(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_StopRecord). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlexer">external documentation</a>. -doc """ Set the lexing language of the document. -The input should be one of the ?wxSTC*LEX*\* constants. +The input should be one of the ?wxSTC\_LEX\_\* constants. """. -spec setLexer(This, Lexer) -> 'ok' when This::wxStyledTextCtrl(), Lexer::integer(). @@ -4375,11 +3906,10 @@ setLexer(#wx_ref{type=ThisT}=This,Lexer) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Lexer,?get_env(),?wxStyledTextCtrl_SetLexer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlexer">external documentation</a>. -doc """ Retrieve the lexing language of the document. -The return value will be one of the ?wxSTC*LEX*\* constants. +The return value will be one of the ?wxSTC\_LEX\_\* constants. """. -spec getLexer(This) -> integer() when This::wxStyledTextCtrl(). @@ -4388,7 +3918,6 @@ getLexer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetLexer), wxe_util:rec(?wxStyledTextCtrl_GetLexer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcolourise">external documentation</a>. -doc "Colourise a segment of the document using the current lexing language.". -spec colourise(This, Start, End) -> 'ok' when This::wxStyledTextCtrl(), Start::integer(), End::integer(). @@ -4397,7 +3926,6 @@ colourise(#wx_ref{type=ThisT}=This,Start,End) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Start,End,?get_env(),?wxStyledTextCtrl_Colourise). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetproperty">external documentation</a>. -doc "Set up a value that may be used by a lexer for some optional feature.". -spec setProperty(This, Key, Value) -> 'ok' when This::wxStyledTextCtrl(), Key::unicode:chardata(), Value::unicode:chardata(). @@ -4408,7 +3936,6 @@ setProperty(#wx_ref{type=ThisT}=This,Key,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Key_UC,Value_UC,?get_env(),?wxStyledTextCtrl_SetProperty). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetkeywords">external documentation</a>. -doc "Set up the key words used by the lexer.". -spec setKeyWords(This, KeyWordSet, KeyWords) -> 'ok' when This::wxStyledTextCtrl(), KeyWordSet::integer(), KeyWords::unicode:chardata(). @@ -4418,7 +3945,6 @@ setKeyWords(#wx_ref{type=ThisT}=This,KeyWordSet,KeyWords) KeyWords_UC = unicode:characters_to_binary(KeyWords), wxe_util:queue_cmd(This,KeyWordSet,KeyWords_UC,?get_env(),?wxStyledTextCtrl_SetKeyWords). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlexerlanguage">external documentation</a>. -doc "Set the lexing language of the document based on string name.". -spec setLexerLanguage(This, Language) -> 'ok' when This::wxStyledTextCtrl(), Language::unicode:chardata(). @@ -4428,7 +3954,6 @@ setLexerLanguage(#wx_ref{type=ThisT}=This,Language) Language_UC = unicode:characters_to_binary(Language), wxe_util:queue_cmd(This,Language_UC,?get_env(),?wxStyledTextCtrl_SetLexerLanguage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetproperty">external documentation</a>. -doc """ Retrieve a "property" value previously set with SetProperty. """. @@ -4441,7 +3966,6 @@ getProperty(#wx_ref{type=ThisT}=This,Key) wxe_util:queue_cmd(This,Key_UC,?get_env(),?wxStyledTextCtrl_GetProperty), wxe_util:rec(?wxStyledTextCtrl_GetProperty). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetstylebitsneeded">external documentation</a>. -doc """ Retrieve the number of bits the current lexer needs for styling. @@ -4454,7 +3978,6 @@ getStyleBitsNeeded(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetStyleBitsNeeded), wxe_util:rec(?wxStyledTextCtrl_GetStyleBitsNeeded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcurrentline">external documentation</a>. -doc "Returns the line number of the line with the caret.". -spec getCurrentLine(This) -> integer() when This::wxStyledTextCtrl(). @@ -4463,15 +3986,14 @@ getCurrentLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCurrentLine), wxe_util:rec(?wxStyledTextCtrl_GetCurrentLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetspec">external documentation</a>. -doc """ -Extract style settings from a spec-string which is composed of one or more of -the following comma separated elements: +Extract style settings from a spec-string which is composed of one or more of the +following comma separated elements: -bold turns on bold italic turns on italics fore:\[name or #RRGGBB] sets the -foreground colour back:\[name or #RRGGBB] sets the background colour -face:\[facename] sets the font face name to use size:\[num] sets the font size -in points eol turns on eol filling underline turns on underlining +bold turns on bold italic turns on italics fore:[name or #RRGGBB] sets the foreground +colour back:[name or #RRGGBB] sets the background colour face:[facename] sets the font +face name to use size:[num] sets the font size in points eol turns on eol filling +underline turns on underlining """. -spec styleSetSpec(This, StyleNum, Spec) -> 'ok' when This::wxStyledTextCtrl(), StyleNum::integer(), Spec::unicode:chardata(). @@ -4481,7 +4003,6 @@ styleSetSpec(#wx_ref{type=ThisT}=This,StyleNum,Spec) Spec_UC = unicode:characters_to_binary(Spec), wxe_util:queue_cmd(This,StyleNum,Spec_UC,?get_env(),?wxStyledTextCtrl_StyleSetSpec). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetfont">external documentation</a>. -doc """ Set style size, face, bold, italic, and underline attributes from a `m:wxFont`'s attributes. @@ -4494,7 +4015,7 @@ styleSetFont(#wx_ref{type=ThisT}=This,StyleNum,#wx_ref{type=FontT}=Font) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,StyleNum,Font,?get_env(),?wxStyledTextCtrl_StyleSetFont). -%% @equiv styleSetFontAttr(This,StyleNum,Size,FaceName,Bold,Italic,Underline, []) +-doc(#{equiv => styleSetFontAttr(This,StyleNum,Size,FaceName,Bold,Italic,Underline, [])}). -spec styleSetFontAttr(This, StyleNum, Size, FaceName, Bold, Italic, Underline) -> 'ok' when This::wxStyledTextCtrl(), StyleNum::integer(), Size::integer(), FaceName::unicode:chardata(), Bold::boolean(), Italic::boolean(), Underline::boolean(). @@ -4502,9 +4023,8 @@ styleSetFontAttr(This,StyleNum,Size,FaceName,Bold,Italic,Underline) when is_record(This, wx_ref),is_integer(StyleNum),is_integer(Size),?is_chardata(FaceName),is_boolean(Bold),is_boolean(Italic),is_boolean(Underline) -> styleSetFontAttr(This,StyleNum,Size,FaceName,Bold,Italic,Underline, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetfontattr">external documentation</a>. -%%<br /> Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc "Set all font style attributes at once.". +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec styleSetFontAttr(This, StyleNum, Size, FaceName, Bold, Italic, Underline, [Option]) -> 'ok' when This::wxStyledTextCtrl(), StyleNum::integer(), Size::integer(), FaceName::unicode:chardata(), Bold::boolean(), Italic::boolean(), Underline::boolean(), Option :: {'encoding', wx:wx_enum()}. @@ -4517,7 +4037,6 @@ styleSetFontAttr(#wx_ref{type=ThisT}=This,StyleNum,Size,FaceName,Bold,Italic,Und Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,StyleNum,Size,FaceName_UC,Bold,Italic,Underline, Opts,?get_env(),?wxStyledTextCtrl_StyleSetFontAttr). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetcharacterset">external documentation</a>. -doc """ Set the character set of the font in a style. @@ -4530,9 +4049,8 @@ styleSetCharacterSet(#wx_ref{type=ThisT}=This,Style,CharacterSet) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,CharacterSet,?get_env(),?wxStyledTextCtrl_StyleSetCharacterSet). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlstylesetfontencoding">external documentation</a>. -%%<br /> Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc "Set the font encoding to be used by a style.". +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec styleSetFontEncoding(This, Style, Encoding) -> 'ok' when This::wxStyledTextCtrl(), Style::integer(), Encoding::wx:wx_enum(). styleSetFontEncoding(#wx_ref{type=ThisT}=This,Style,Encoding) @@ -4540,10 +4058,7 @@ styleSetFontEncoding(#wx_ref{type=ThisT}=This,Style,Encoding) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Style,Encoding,?get_env(),?wxStyledTextCtrl_StyleSetFontEncoding). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlcmdkeyexecute">external documentation</a>. --doc """ -Perform one of the operations defined by the wxSTC*CMD*\* constants. -""". +-doc "Perform one of the operations defined by the wxSTC\_CMD\_\* constants.". -spec cmdKeyExecute(This, Cmd) -> 'ok' when This::wxStyledTextCtrl(), Cmd::integer(). cmdKeyExecute(#wx_ref{type=ThisT}=This,Cmd) @@ -4551,7 +4066,6 @@ cmdKeyExecute(#wx_ref{type=ThisT}=This,Cmd) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Cmd,?get_env(),?wxStyledTextCtrl_CmdKeyExecute). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetmargins">external documentation</a>. -doc "Set the left and right margin in the edit area, measured in pixels.". -spec setMargins(This, Left, Right) -> 'ok' when This::wxStyledTextCtrl(), Left::integer(), Right::integer(). @@ -4560,15 +4074,13 @@ setMargins(#wx_ref{type=ThisT}=This,Left,Right) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Left,Right,?get_env(),?wxStyledTextCtrl_SetMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselection">external documentation</a>. -doc """ Gets the current selection span. -If the returned values are equal, there was no selection. Please note that the -indices returned may be used with the other `m:wxTextCtrl` methods but don't -necessarily represent the correct indices into the string returned by -`wxComboBox:getValue/1` for multiline controls under Windows (at least,) you -should use `wxTextCtrl:getStringSelection/1` to get the selected text. +If the returned values are equal, there was no selection. Please note that the indices +returned may be used with the other `m:wxTextCtrl` methods but don't necessarily represent +the correct indices into the string returned by `wxComboBox:getValue/1` for multiline controls under Windows (at +least,) you should use `wxTextCtrl:getStringSelection/1` to get the selected text. """. -spec getSelection(This) -> {From::integer(), To::integer()} when This::wxStyledTextCtrl(). @@ -4577,7 +4089,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelection), wxe_util:rec(?wxStyledTextCtrl_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlpointfromposition">external documentation</a>. -doc "Retrieve the point in the window where a position is displayed.". -spec pointFromPosition(This, Pos) -> {X::integer(), Y::integer()} when This::wxStyledTextCtrl(), Pos::integer(). @@ -4587,7 +4098,6 @@ pointFromPosition(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxStyledTextCtrl_PointFromPosition), wxe_util:rec(?wxStyledTextCtrl_PointFromPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlscrolltoline">external documentation</a>. -doc "Scroll enough to make the given line visible.". -spec scrollToLine(This, Line) -> 'ok' when This::wxStyledTextCtrl(), Line::integer(). @@ -4596,7 +4106,6 @@ scrollToLine(#wx_ref{type=ThisT}=This,Line) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_ScrollToLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlscrolltocolumn">external documentation</a>. -doc "Scroll enough to make the given column visible.". -spec scrollToColumn(This, Column) -> 'ok' when This::wxStyledTextCtrl(), Column::integer(). @@ -4605,7 +4114,6 @@ scrollToColumn(#wx_ref{type=ThisT}=This,Column) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Column,?get_env(),?wxStyledTextCtrl_ScrollToColumn). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetvscrollbar">external documentation</a>. -doc "Set the vertical scrollbar to use instead of the one that's built-in.". -spec setVScrollBar(This, Bar) -> 'ok' when This::wxStyledTextCtrl(), Bar::wxScrollBar:wxScrollBar(). @@ -4614,7 +4122,6 @@ setVScrollBar(#wx_ref{type=ThisT}=This,#wx_ref{type=BarT}=Bar) -> ?CLASS(BarT,wxScrollBar), wxe_util:queue_cmd(This,Bar,?get_env(),?wxStyledTextCtrl_SetVScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsethscrollbar">external documentation</a>. -doc "Set the horizontal scrollbar to use instead of the one that's built-in.". -spec setHScrollBar(This, Bar) -> 'ok' when This::wxStyledTextCtrl(), Bar::wxScrollBar:wxScrollBar(). @@ -4623,8 +4130,7 @@ setHScrollBar(#wx_ref{type=ThisT}=This,#wx_ref{type=BarT}=Bar) -> ?CLASS(BarT,wxScrollBar), wxe_util:queue_cmd(This,Bar,?get_env(),?wxStyledTextCtrl_SetHScrollBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlastkeydownprocessed">external documentation</a>. --doc "Can be used to prevent the EVT_CHAR handler from adding the char.". +-doc "Can be used to prevent the EVT\_CHAR handler from adding the char.". -spec getLastKeydownProcessed(This) -> boolean() when This::wxStyledTextCtrl(). getLastKeydownProcessed(#wx_ref{type=ThisT}=This) -> @@ -4632,7 +4138,6 @@ getLastKeydownProcessed(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetLastKeydownProcessed), wxe_util:rec(?wxStyledTextCtrl_GetLastKeydownProcessed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsetlastkeydownprocessed">external documentation</a>. -doc "Returns the line number of the line with the caret.". -spec setLastKeydownProcessed(This, Val) -> 'ok' when This::wxStyledTextCtrl(), Val::boolean(). @@ -4641,7 +4146,6 @@ setLastKeydownProcessed(#wx_ref{type=ThisT}=This,Val) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Val,?get_env(),?wxStyledTextCtrl_SetLastKeydownProcessed). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsavefile">external documentation</a>. -doc "Write the contents of the editor to filename.". -spec saveFile(This, Filename) -> boolean() when This::wxStyledTextCtrl(), Filename::unicode:chardata(). @@ -4652,7 +4156,6 @@ saveFile(#wx_ref{type=ThisT}=This,Filename) wxe_util:queue_cmd(This,Filename_UC,?get_env(),?wxStyledTextCtrl_SaveFile), wxe_util:rec(?wxStyledTextCtrl_SaveFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlloadfile">external documentation</a>. -doc "Load the contents of filename into the editor.". -spec loadFile(This, Filename) -> boolean() when This::wxStyledTextCtrl(), Filename::unicode:chardata(). @@ -4663,10 +4166,9 @@ loadFile(#wx_ref{type=ThisT}=This,Filename) wxe_util:queue_cmd(This,Filename_UC,?get_env(),?wxStyledTextCtrl_LoadFile), wxe_util:rec(?wxStyledTextCtrl_LoadFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldodragover">external documentation</a>. -%%<br /> DefaultRes = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel -%%<br /> Res = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel -doc "Allow for simulating a DnD DragOver.". +%% DefaultRes = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel +%% Res = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel -spec doDragOver(This, X, Y, DefaultRes) -> wx:wx_enum() when This::wxStyledTextCtrl(), X::integer(), Y::integer(), DefaultRes::wx:wx_enum(). doDragOver(#wx_ref{type=ThisT}=This,X,Y,DefaultRes) @@ -4675,7 +4177,6 @@ doDragOver(#wx_ref{type=ThisT}=This,X,Y,DefaultRes) wxe_util:queue_cmd(This,X,Y,DefaultRes,?get_env(),?wxStyledTextCtrl_DoDragOver), wxe_util:rec(?wxStyledTextCtrl_DoDragOver). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrldodroptext">external documentation</a>. -doc "Allow for simulating a DnD DropText.". -spec doDropText(This, X, Y, Data) -> boolean() when This::wxStyledTextCtrl(), X::integer(), Y::integer(), Data::unicode:chardata(). @@ -4686,7 +4187,6 @@ doDropText(#wx_ref{type=ThisT}=This,X,Y,Data) wxe_util:queue_cmd(This,X,Y,Data_UC,?get_env(),?wxStyledTextCtrl_DoDropText), wxe_util:rec(?wxStyledTextCtrl_DoDropText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetuseantialiasing">external documentation</a>. -doc "Returns the current UseAntiAliasing setting.". -spec getUseAntiAliasing(This) -> boolean() when This::wxStyledTextCtrl(). @@ -4695,7 +4195,7 @@ getUseAntiAliasing(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetUseAntiAliasing), wxe_util:rec(?wxStyledTextCtrl_GetUseAntiAliasing). -%% @equiv addTextRaw(This,Text, []) +-doc(#{equiv => addTextRaw(This,Text, [])}). -spec addTextRaw(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::binary(). @@ -4703,7 +4203,6 @@ addTextRaw(This,Text) when is_record(This, wx_ref),is_binary(Text) -> addTextRaw(This,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrladdtextraw">external documentation</a>. -doc "Add text to the document at current position.". -spec addTextRaw(This, Text, [Option]) -> 'ok' when This::wxStyledTextCtrl(), Text::binary(), @@ -4716,7 +4215,6 @@ addTextRaw(#wx_ref{type=ThisT}=This,Text, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Text, Opts,?get_env(),?wxStyledTextCtrl_AddTextRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlinserttextraw">external documentation</a>. -doc "Insert string at a position.". -spec insertTextRaw(This, Pos, Text) -> 'ok' when This::wxStyledTextCtrl(), Pos::integer(), Text::binary(). @@ -4725,7 +4223,6 @@ insertTextRaw(#wx_ref{type=ThisT}=This,Pos,Text) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Pos,Text,?get_env(),?wxStyledTextCtrl_InsertTextRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetcurlineraw">external documentation</a>. -doc """ Retrieve the text of the line containing the caret. @@ -4739,7 +4236,6 @@ getCurLineRaw(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetCurLineRaw), wxe_util:rec(?wxStyledTextCtrl_GetCurLineRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetlineraw">external documentation</a>. -doc "Retrieve the contents of a line.". -spec getLineRaw(This, Line) -> binary() when This::wxStyledTextCtrl(), Line::integer(). @@ -4749,7 +4245,6 @@ getLineRaw(#wx_ref{type=ThisT}=This,Line) wxe_util:queue_cmd(This,Line,?get_env(),?wxStyledTextCtrl_GetLineRaw), wxe_util:rec(?wxStyledTextCtrl_GetLineRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgetselectedtextraw">external documentation</a>. -doc "Retrieve the selected text.". -spec getSelectedTextRaw(This) -> binary() when This::wxStyledTextCtrl(). @@ -4758,7 +4253,6 @@ getSelectedTextRaw(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetSelectedTextRaw), wxe_util:rec(?wxStyledTextCtrl_GetSelectedTextRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettextrangeraw">external documentation</a>. -doc "Retrieve a range of text.". -spec getTextRangeRaw(This, StartPos, EndPos) -> binary() when This::wxStyledTextCtrl(), StartPos::integer(), EndPos::integer(). @@ -4768,7 +4262,6 @@ getTextRangeRaw(#wx_ref{type=ThisT}=This,StartPos,EndPos) wxe_util:queue_cmd(This,StartPos,EndPos,?get_env(),?wxStyledTextCtrl_GetTextRangeRaw), wxe_util:rec(?wxStyledTextCtrl_GetTextRangeRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlsettextraw">external documentation</a>. -doc "Replace the contents of the document with the argument text.". -spec setTextRaw(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::binary(). @@ -4777,7 +4270,6 @@ setTextRaw(#wx_ref{type=ThisT}=This,Text) ?CLASS(ThisT,wxStyledTextCtrl), wxe_util:queue_cmd(This,Text,?get_env(),?wxStyledTextCtrl_SetTextRaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlgettextraw">external documentation</a>. -doc "Retrieve all the text in the document.". -spec getTextRaw(This) -> binary() when This::wxStyledTextCtrl(). @@ -4786,7 +4278,7 @@ getTextRaw(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextCtrl_GetTextRaw), wxe_util:rec(?wxStyledTextCtrl_GetTextRaw). -%% @equiv appendTextRaw(This,Text, []) +-doc(#{equiv => appendTextRaw(This,Text, [])}). -spec appendTextRaw(This, Text) -> 'ok' when This::wxStyledTextCtrl(), Text::binary(). @@ -4794,7 +4286,6 @@ appendTextRaw(This,Text) when is_record(This, wx_ref),is_binary(Text) -> appendTextRaw(This,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextctrl.html#wxstyledtextctrlappendtextraw">external documentation</a>. -doc "Append a string to the end of the document without changing the selection.". -spec appendTextRaw(This, Text, [Option]) -> 'ok' when This::wxStyledTextCtrl(), Text::binary(), @@ -4807,550 +4298,370 @@ appendTextRaw(#wx_ref{type=ThisT}=This,Text, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Text, Opts,?get_env(),?wxStyledTextCtrl_AppendTextRaw). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxStyledTextCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxStyledTextCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxStyledTextEvent.erl b/lib/wx/src/gen/wxStyledTextEvent.erl index cc9073554ba1..ec2e7c3fcd74 100644 --- a/lib/wx/src/gen/wxStyledTextEvent.erl +++ b/lib/wx/src/gen/wxStyledTextEvent.erl @@ -20,21 +20,19 @@ -module(wxStyledTextEvent). -moduledoc """ -Functions for wxStyledTextEvent class - The type of events sent from `m:wxStyledTextCtrl`. -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` -wxWidgets docs: -[wxStyledTextEvent](https://docs.wxwidgets.org/3.1/classwx_styled_text_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxStyledTextEvent](https://docs.wxwidgets.org/3.2/classwx_styled_text_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxStyledTextEventType`](`t:wxStyledTextEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxStyledTextEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getAlt/1,getControl/1,getDragAllowMove/1,getDragResult/1,getDragText/1, @@ -53,17 +51,51 @@ this type. -include("wx.hrl"). -type wxStyledTextEventType() :: 'stc_autocomp_cancelled' | 'stc_autocomp_char_deleted' | 'stc_autocomp_selection' | 'stc_calltip_click' | 'stc_change' | 'stc_charadded' | 'stc_do_drop' | 'stc_doubleclick' | 'stc_drag_over' | 'stc_dwellend' | 'stc_dwellstart' | 'stc_hotspot_click' | 'stc_hotspot_dclick' | 'stc_hotspot_release_click' | 'stc_indicator_click' | 'stc_indicator_release' | 'stc_macrorecord' | 'stc_marginclick' | 'stc_modified' | 'stc_needshown' | 'stc_painted' | 'stc_romodifyattempt' | 'stc_savepointleft' | 'stc_savepointreached' | 'stc_start_drag' | 'stc_styleneeded' | 'stc_updateui' | 'stc_userlistselection' | 'stc_zoom'. -export_type([wxStyledTextEvent/0, wxStyledText/0, wxStyledTextEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetposition">external documentation</a>. -doc """ Returns the zero-based text position associated this event. This method is valid for the following event types: + +* `wxEVT_STC_STYLENEEDED` + +* `wxEVT_STC_DOUBLECLICK` + +* `wxEVT_STC_MODIFIED` + +* `wxEVT_STC_MARGINCLICK` + +* `wxEVT_STC_NEEDSHOWN` + +* `wxEVT_STC_USERLISTSELECTION` + +* `wxEVT_STC_DWELLSTART` + +* `wxEVT_STC_DWELLEND` + +* `wxEVT_STC_HOTSPOT_CLICK` + +* `wxEVT_STC_HOTSPOT_DCLICK` + +* `wxEVT_STC_HOTSPOT_RELEASE_CLICK` + +* `wxEVT_STC_INDICATOR_CLICK` + +* `wxEVT_STC_INDICATOR_RELEASE` + +* `wxEVT_STC_CALLTIP_CLICK` + +* `wxEVT_STC_AUTOCOMP_SELECTION` + +* `wxEVT_STC_AUTOCOMP_SELECTION_CHANGE` + +* `wxEVT_STC_AUTOCOMP_COMPLETED` + +* `wxEVT_STC_MARGIN_RIGHT_CLICK` """. -spec getPosition(This) -> integer() when This::wxStyledTextEvent(). @@ -72,11 +104,18 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetPosition), wxe_util:rec(?wxStyledTextEvent_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetkey">external documentation</a>. -doc """ Returns the key code of the key that generated this event. This method is valid for the following event types: + +* `wxEVT_STC_CHARADDED` + +* `wxEVT_STC_USERLISTSELECTION` + +* `wxEVT_STC_AUTOCOMP_SELECTION` + +* `wxEVT_STC_AUTOCOMP_COMPLETED` """. -spec getKey(This) -> integer() when This::wxStyledTextEvent(). @@ -85,17 +124,41 @@ getKey(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetKey), wxe_util:rec(?wxStyledTextEvent_GetKey). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetmodifiers">external documentation</a>. -doc """ Returns the modifiers of the key press or mouse click for this event. -The returned value is a bit list that may contain one or more of the following -values: +The returned value is a bit list that may contain one or more of the following values: + +* ?wxSTC\_KEYMOD\_SHIFT -In addition, the value can be checked for equality with ?wxSTC_KEYMOD_NORM to -test if no modifiers are present. +* ?wxSTC\_KEYMOD\_CTRL + +* ?wxSTC\_KEYMOD\_ALT + +* ?wxSTC\_KEYMOD\_SUPER + +* ?wxSTC\_KEYMOD\_META + +In addition, the value can be checked for equality with ?wxSTC\_KEYMOD\_NORM to test if +no modifiers are present. This method is valid for the following event types: + +* `wxEVT_STC_DOUBLECLICK` + +* `wxEVT_STC_MARGINCLICK` + +* `wxEVT_STC_HOTSPOT_CLICK` + +* `wxEVT_STC_HOTSPOT_DCLICK` + +* `wxEVT_STC_HOTSPOT_RELEASE_CLICK` + +* `wxEVT_STC_INDICATOR_CLICK` + +* `wxEVT_STC_INDICATOR_RELEASE` + +* `wxEVT_STC_MARGIN_RIGHT_CLICK` """. -spec getModifiers(This) -> integer() when This::wxStyledTextEvent(). @@ -104,12 +167,55 @@ getModifiers(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetModifiers), wxe_util:rec(?wxStyledTextEvent_GetModifiers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetmodificationtype">external documentation</a>. -doc """ Returns the modification type for this event. -The modification type is a bit list that describes the change that generated -this event. It may contain one or more of the following values: +The modification type is a bit list that describes the change that generated this event. +It may contain one or more of the following values: + +* ?wxSTC\_MOD\_INSERTTEXT + +* ?wxSTC\_MOD\_DELETETEXT + +* ?wxSTC\_MOD\_CHANGESTYLE + +* ?wxSTC\_MOD\_CHANGEFOLD + +* ?wxSTC\_PERFORMED\_USER + +* ?wxSTC\_PERFORMED\_UNDO + +* ?wxSTC\_PERFORMED\_REDO + +* ?wxSTC\_MULTISTEPUNDOREDO + +* ?wxSTC\_LASTSTEPINUNDOREDO + +* ?wxSTC\_MOD\_CHANGEMARKER + +* ?wxSTC\_MOD\_BEFOREINSERT + +* ?wxSTC\_MOD\_BEFOREDELETE + +* ?wxSTC\_MULTILINEUNDOREDO + +* ?wxSTC\_STARTACTION + +* ?wxSTC\_MOD\_CHANGEINDICATOR + +* ?wxSTC\_MOD\_CHANGELINESTATE + +* ?wxSTC\_MOD\_CHANGEMARGIN + +* ?wxSTC\_MOD\_CHANGEANNOTATION + +* ?wxSTC\_MOD\_CONTAINER + +* ?wxSTC\_MOD\_LEXERSTATE + +* ?wxSTC\_MOD\_INSERTCHECK + +* ?wxSTC\_MOD\_CHANGETABSTOPS This method is valid for `wxEVT_STC_MODIFIED` events. """. @@ -120,8 +226,11 @@ getModificationType(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetModificationType), wxe_util:rec(?wxStyledTextEvent_GetModificationType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgettext">external documentation</a>. --doc "Deprecated: Use `wxCommandEvent:getString/1` instead.". +-doc """ +Deprecated: + +Use `wxCommandEvent:getString/1` instead. +""". -spec getText(This) -> unicode:charlist() when This::wxStyledTextEvent(). getText(#wx_ref{type=ThisT}=This) -> @@ -129,7 +238,6 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetText), wxe_util:rec(?wxStyledTextEvent_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetlength">external documentation</a>. -doc """ Returns the length (number of characters) of this event. @@ -142,12 +250,11 @@ getLength(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetLength), wxe_util:rec(?wxStyledTextEvent_GetLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetlinesadded">external documentation</a>. -doc """ Returns the number of lines added or deleted with this event. -This method is valid for `wxEVT_STC_MODIFIED` events when the result of -`getModificationType/1` includes ?wxSTC_MOD_INSERTTEXT or ?wxSTC_MOD_DELETETEXT. +This method is valid for `wxEVT_STC_MODIFIED` events when the result of `getModificationType/1` includes +?wxSTC\_MOD\_INSERTTEXT or ?wxSTC\_MOD\_DELETETEXT. """. -spec getLinesAdded(This) -> integer() when This::wxStyledTextEvent(). @@ -156,12 +263,10 @@ getLinesAdded(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetLinesAdded), wxe_util:rec(?wxStyledTextEvent_GetLinesAdded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetline">external documentation</a>. -doc """ Returns zero-based line number for this event. -This method is valid for `wxEVT_STC_DOUBLECLICK` and `wxEVT_STC_MODIFIED` -events. +This method is valid for `wxEVT_STC_DOUBLECLICK` and `wxEVT_STC_MODIFIED` events. """. -spec getLine(This) -> integer() when This::wxStyledTextEvent(). @@ -170,12 +275,11 @@ getLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetLine), wxe_util:rec(?wxStyledTextEvent_GetLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetfoldlevelnow">external documentation</a>. -doc """ Returns the current fold level for the line. -This method is valid for `wxEVT_STC_MODIFIED` events when the result of -`getModificationType/1` includes ?wxSTC_MOD_CHANGEFOLD. +This method is valid for `wxEVT_STC_MODIFIED` events when the result of `getModificationType/1` includes +?wxSTC\_MOD\_CHANGEFOLD. """. -spec getFoldLevelNow(This) -> integer() when This::wxStyledTextEvent(). @@ -184,12 +288,11 @@ getFoldLevelNow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetFoldLevelNow), wxe_util:rec(?wxStyledTextEvent_GetFoldLevelNow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetfoldlevelprev">external documentation</a>. -doc """ Returns previous fold level for the line. -This method is valid for `wxEVT_STC_MODIFIED` events when the result of -`getModificationType/1` includes ?wxSTC_MOD_CHANGEFOLD. +This method is valid for `wxEVT_STC_MODIFIED` events when the result of `getModificationType/1` includes +?wxSTC\_MOD\_CHANGEFOLD. """. -spec getFoldLevelPrev(This) -> integer() when This::wxStyledTextEvent(). @@ -198,12 +301,11 @@ getFoldLevelPrev(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetFoldLevelPrev), wxe_util:rec(?wxStyledTextEvent_GetFoldLevelPrev). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetmargin">external documentation</a>. -doc """ Returns the zero-based index of the margin that generated this event. -This method is valid for `wxEVT_STC_MARGINCLICK` and -`wxEVT_STC_MARGIN_RIGHT_CLICK` events. +This method is valid for `wxEVT_STC_MARGINCLICK` and `wxEVT_STC_MARGIN_RIGHT_CLICK` +events. """. -spec getMargin(This) -> integer() when This::wxStyledTextEvent(). @@ -212,14 +314,12 @@ getMargin(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetMargin), wxe_util:rec(?wxStyledTextEvent_GetMargin). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetmessage">external documentation</a>. -doc """ Returns a message number while a macro is being recorded. -Many of the `m:wxStyledTextCtrl` methods such as `wxStyledTextCtrl:insertText/3` -and `wxStyledTextCtrl:paste/1` have an event number associated with them. This -method returns that number while a macro is being recorded so that the macro can -be played back later. +Many of the `m:wxStyledTextCtrl` methods such as `wxStyledTextCtrl:insertText/3` and `wxStyledTextCtrl:paste/1` have an event number associated +with them. This method returns that number while a macro is being recorded so that the +macro can be played back later. This method is valid for `wxEVT_STC_MACRORECORD` events. """. @@ -230,7 +330,6 @@ getMessage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetMessage), wxe_util:rec(?wxStyledTextEvent_GetMessage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetwparam">external documentation</a>. -doc """ Returns value of the WParam field for this event. @@ -243,7 +342,6 @@ getWParam(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetWParam), wxe_util:rec(?wxStyledTextEvent_GetWParam). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetlparam">external documentation</a>. -doc """ Returns the value of the LParam field for this event. @@ -256,16 +354,14 @@ getLParam(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetLParam), wxe_util:rec(?wxStyledTextEvent_GetLParam). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetlisttype">external documentation</a>. -doc """ Returns the list type for this event. -The list type is an integer passed to a list when it is created with the -`wxStyledTextCtrl:userListShow/3` method and can be used to distinguish lists if -more than one is used. +The list type is an integer passed to a list when it is created with the `wxStyledTextCtrl:userListShow/3` method and can +be used to distinguish lists if more than one is used. -This method is valid for `wxEVT_STC_AUTOCOMP_SELECTION_CHANGE` and -`wxEVT_STC_USERLISTSELECTION` events. +This method is valid for `wxEVT_STC_AUTOCOMP_SELECTION_CHANGE` and `wxEVT_STC_USERLISTSELECTION` +events. """. -spec getListType(This) -> integer() when This::wxStyledTextEvent(). @@ -274,11 +370,20 @@ getListType(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetListType), wxe_util:rec(?wxStyledTextEvent_GetListType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetx">external documentation</a>. -doc """ Returns the X coordinate of the mouse for this event. This method is valid for the following event types: + +* `wxEVT_STC_DWELLSTART` + +* `wxEVT_STC_DWELLEND` + +* `wxEVT_STC_START_DRAG` + +* `wxEVT_STC_DRAG_OVER` + +* `wxEVT_STC_DO_DROP` """. -spec getX(This) -> integer() when This::wxStyledTextEvent(). @@ -287,11 +392,20 @@ getX(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetX), wxe_util:rec(?wxStyledTextEvent_GetX). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgety">external documentation</a>. -doc """ Returns the Y coordinate of the mouse for this event. This method is valid for the following event types: + +* `wxEVT_STC_DWELLSTART` + +* `wxEVT_STC_DWELLEND` + +* `wxEVT_STC_START_DRAG` + +* `wxEVT_STC_DRAG_OVER` + +* `wxEVT_STC_DO_DROP` """. -spec getY(This) -> integer() when This::wxStyledTextEvent(). @@ -300,8 +414,11 @@ getY(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetY), wxe_util:rec(?wxStyledTextEvent_GetY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetdragtext">external documentation</a>. --doc "Deprecated: Use `wxCommandEvent:getString/1` instead.". +-doc """ +Deprecated: + +Use `wxCommandEvent:getString/1` instead. +""". -spec getDragText(This) -> unicode:charlist() when This::wxStyledTextEvent(). getDragText(#wx_ref{type=ThisT}=This) -> @@ -309,7 +426,7 @@ getDragText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetDragText), wxe_util:rec(?wxStyledTextEvent_GetDragText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetdragallowmove">external documentation</a>. +-doc "". -spec getDragAllowMove(This) -> boolean() when This::wxStyledTextEvent(). getDragAllowMove(#wx_ref{type=ThisT}=This) -> @@ -317,13 +434,12 @@ getDragAllowMove(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetDragAllowMove), wxe_util:rec(?wxStyledTextEvent_GetDragAllowMove). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetdragresult">external documentation</a>. -%%<br /> Res = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel -doc """ Returns drag result for this event. This method is valid for `wxEVT_STC_DRAG_OVER` and `wxEVT_STC_DO_DROP` events. """. +%% Res = ?wxDragError | ?wxDragNone | ?wxDragCopy | ?wxDragMove | ?wxDragLink | ?wxDragCancel -spec getDragResult(This) -> wx:wx_enum() when This::wxStyledTextEvent(). getDragResult(#wx_ref{type=ThisT}=This) -> @@ -331,11 +447,26 @@ getDragResult(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetDragResult), wxe_util:rec(?wxStyledTextEvent_GetDragResult). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetshift">external documentation</a>. -doc """ Returns true if the Shift key is pressed. This method is valid for the following event types: + +* `wxEVT_STC_DOUBLECLICK` + +* `wxEVT_STC_MARGINCLICK` + +* `wxEVT_STC_HOTSPOT_CLICK` + +* `wxEVT_STC_HOTSPOT_DCLICK` + +* `wxEVT_STC_HOTSPOT_RELEASE_CLICK` + +* `wxEVT_STC_INDICATOR_CLICK` + +* `wxEVT_STC_INDICATOR_RELEASE` + +* `wxEVT_STC_MARGIN_RIGHT_CLICK` """. -spec getShift(This) -> boolean() when This::wxStyledTextEvent(). @@ -344,11 +475,26 @@ getShift(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetShift), wxe_util:rec(?wxStyledTextEvent_GetShift). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetcontrol">external documentation</a>. -doc """ Returns true if the Control key is pressed. This method is valid for the following event types: + +* `wxEVT_STC_DOUBLECLICK` + +* `wxEVT_STC_MARGINCLICK` + +* `wxEVT_STC_HOTSPOT_CLICK` + +* `wxEVT_STC_HOTSPOT_DCLICK` + +* `wxEVT_STC_HOTSPOT_RELEASE_CLICK` + +* `wxEVT_STC_INDICATOR_CLICK` + +* `wxEVT_STC_INDICATOR_RELEASE` + +* `wxEVT_STC_MARGIN_RIGHT_CLICK` """. -spec getControl(This) -> boolean() when This::wxStyledTextEvent(). @@ -357,11 +503,26 @@ getControl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxStyledTextEvent_GetControl), wxe_util:rec(?wxStyledTextEvent_GetControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxstyledtextevent.html#wxstyledtexteventgetalt">external documentation</a>. -doc """ Returns true if the Alt key is pressed. This method is valid for the following event types: + +* `wxEVT_STC_DOUBLECLICK` + +* `wxEVT_STC_MARGINCLICK` + +* `wxEVT_STC_HOTSPOT_CLICK` + +* `wxEVT_STC_HOTSPOT_DCLICK` + +* `wxEVT_STC_HOTSPOT_RELEASE_CLICK` + +* `wxEVT_STC_INDICATOR_CLICK` + +* `wxEVT_STC_INDICATOR_RELEASE` + +* `wxEVT_STC_MARGIN_RIGHT_CLICK` """. -spec getAlt(This) -> boolean() when This::wxStyledTextEvent(). @@ -371,58 +532,40 @@ getAlt(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxStyledTextEvent_GetAlt). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSysColourChangedEvent.erl b/lib/wx/src/gen/wxSysColourChangedEvent.erl index e19c26ad114c..c687d2d3ff78 100644 --- a/lib/wx/src/gen/wxSysColourChangedEvent.erl +++ b/lib/wx/src/gen/wxSysColourChangedEvent.erl @@ -20,30 +20,27 @@ -module(wxSysColourChangedEvent). -moduledoc """ -Functions for wxSysColourChangedEvent class +This class is used for system colour change events, which are generated when the user +changes the colour settings using the control panel. -This class is used for system colour change events, which are generated when the -user changes the colour settings using the control panel. This is only -appropriate under Windows. +This is only appropriate under Windows. -Remark: The default event handler for this event propagates the event to child -windows, since Windows only sends the events to top-level windows. If -intercepting this event for a top-level window, remember to call the base class -handler, or to pass the event on to the window's children explicitly. +Remark: The default event handler for this event propagates the event to child windows, +since Windows only sends the events to top-level windows. If intercepting this event for a +top-level window, remember to call the base class handler, or to pass the event on to the +window's children explicitly. -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxSysColourChangedEvent](https://docs.wxwidgets.org/3.1/classwx_sys_colour_changed_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxSysColourChangedEvent](https://docs.wxwidgets.org/3.2/classwx_sys_colour_changed_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxSysColourChangedEventType`](`t:wxSysColourChangedEventType/0`) to subscribe -to events of this type. +Use `wxEvtHandler:connect/3` with `wxSysColourChangedEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -56,36 +53,26 @@ to events of this type. -include("wx.hrl"). -type wxSysColourChangedEventType() :: 'sys_colour_changed'. -export_type([wxSysColourChangedEvent/0, wxSysColourChanged/0, wxSysColourChangedEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxSystemOptions.erl b/lib/wx/src/gen/wxSystemOptions.erl index 0013c92a66bd..9d587a71ef79 100644 --- a/lib/wx/src/gen/wxSystemOptions.erl +++ b/lib/wx/src/gen/wxSystemOptions.erl @@ -20,44 +20,110 @@ -module(wxSystemOptions). -moduledoc """ -Functions for wxSystemOptions class - -`m:wxSystemOptions` stores option/value pairs that wxWidgets itself or -applications can use to alter behaviour at run-time. It can be used to optimize -behaviour that doesn't deserve a distinct API, but is still important to be able -to configure. - -System options can be set by the program itself using `setOption/2` method and -they also can be set from the program environment by defining an environment -variable `wx_option` to set the given option for all wxWidgets applications or -`wx_appname_option` to set it just for the application with the given name (as -returned by `wxApp::GetAppName()` (not implemented in wx)). Notice that any -characters not allowed in the environment variables names, such as periods and -dashes, should be replaced with underscores. E.g. to define a system option +`m:wxSystemOptions` stores option/value pairs that wxWidgets itself or applications can +use to alter behaviour at run-time. + +It can be used to optimize behaviour that doesn't deserve a distinct API, but is still +important to be able to configure. + +System options can be set by the program itself using `setOption/2` method and they also can be set +from the program environment by defining an environment variable `wx_option` to set the +given option for all wxWidgets applications or `wx_appname_option` to set it just for the +application with the given name (as returned by `wxApp::GetAppName()` (not implemented in +wx)). Notice that any characters not allowed in the environment variables names, such as +periods and dashes, should be replaced with underscores. E.g. to define a system option "foo-bar" you need to define the environment variable "wx_foo_bar". -The program may use system options for its own needs but they are mostly used to -control the behaviour of wxWidgets library itself. +The program may use system options for its own needs but they are mostly used to control +the behaviour of wxWidgets library itself. These options are currently recognised by wxWidgets: All platforms +* exit-on-assert: If set to non-zero value, abort the program if an assertion fails. The +default behaviour in case of assertion failure depends on the build mode and can be +changed by overriding `wxApp::OnAssertFailure()` (not implemented in wx) but setting this +option allows changing it without modifying the program code and also applies to asserts +which may happen before the `wxApp` (not implemented in wx) object creation or after its +destruction. + Windows +* no-maskblt: 1 to never use WIN32's MaskBlt function, 0 to allow it to be used where +possible. Default: 0. In some circumstances the MaskBlt function can be slower than using +the fallback code, especially if using DC caching. By default, MaskBlt will be used where +it is implemented by the operating system and driver. + +* msw.remap: If 1 (the default), `m:wxToolBar` bitmap colours will be remapped to the +current theme's values. Set this to 0 to disable this functionality, for example if you're +using more than 16 colours in your tool bitmaps. + +* msw.window.no-clip-children: If 1, windows will not automatically get the WS_CLIPCHILDREN +style. This restores the way windows are refreshed back to the method used in versions of +wxWidgets earlier than 2.5.4, and for some complex window hierarchies it can reduce +apparent refresh delays. You may still specify wxCLIP_CHILDREN for individual windows. + +* msw.notebook.themed-background: If set to 0, globally disables themed backgrounds on +notebook pages. Note that this won't disable the theme on the actual notebook background +(noticeable only if there are no pages). + +* msw.staticbox.optimized-paint: If set to 0, switches off optimized `m:wxStaticBox` +painting. Setting this to 0 causes more flicker, but allows applications to paint graphics +on the parent of a static box (the optimized refresh causes any such drawing to +disappear). + +* msw.font.no-proof-quality: If set to 1, use default fonts quality instead of proof +quality when creating fonts. With proof quality the fonts have slightly better appearance +but not all fonts are available in this quality, e.g. the Terminal font in small sizes is +not and this option may be used if wider fonts selection is more important than higher +quality. + GTK+ +* gtk.tlw.can-set-transparent: `wxTopLevelWindow::CanSetTransparent()` (not implemented in +wx) method normally tries to detect automatically whether transparency for top level +windows is currently supported, however this may sometimes fail and this option allows +overriding the automatic detection. Setting it to 1 makes the transparency be always +available (setting it can still fail, of course) and setting it to 0 makes it always +unavailable. + +* gtk.desktop: This option can be set to override the default desktop environment +determination. Supported values are GNOME and KDE. + +* gtk.window.force-background-colour: If 1, the backgrounds of windows with the +wxBG_STYLE_COLOUR background style are cleared forcibly instead of relying on the +underlying GTK+ window colour. This works around a display problem when running +applications under KDE with the gtk-qt theme installed (0.6 and below). + Mac +* mac.window-plain-transition: If 1, uses a plainer transition when showing a window. You +can also use the symbol wxMAC_WINDOW_PLAIN_TRANSITION. + +* window-default-variant: The default variant used by windows (cast to integer from the +wxWindowVariant enum). Also known as wxWINDOW_DEFAULT_VARIANT. + +* mac.listctrl.always_use_generic: Tells `m:wxListCtrl` to use the generic control even +when it is capable of using the native control instead. Also known as +wxMAC_ALWAYS_USE_GENERIC_LISTCTRL. + +* mac.textcontrol-use-spell-checker: If 1 activates the spell checking in `m:wxTextCtrl`. + +* osx.openfiledialog.always-show-types: Per default a `m:wxFileDialog` with wxFD_OPEN does +not show a types-popup on macOS but allows the selection of files from any of the +supported types. Setting this to 1 shows a `m:wxChoice` for selection (if there is more +than one supported filetype). + Motif -The compile-time option to include or exclude this functionality is -wxUSE_SYSTEM_OPTIONS. +* motif.largebuttons: If 1, uses a bigger default size for wxButtons. + +The compile-time option to include or exclude this functionality is wxUSE_SYSTEM_OPTIONS. See: `m:wxSystemSettings` -wxWidgets docs: -[wxSystemOptions](https://docs.wxwidgets.org/3.1/classwx_system_options.html) +wxWidgets docs: [wxSystemOptions](https://docs.wxwidgets.org/3.2/classwx_system_options.html) """. -include("wxe.hrl"). -export([getOption/1,getOptionInt/1,hasOption/1,isFalse/1,setOption/2]). @@ -67,18 +133,21 @@ wxWidgets docs: -type wxSystemOptions() :: wx:wx_object(). -export_type([wxSystemOptions/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemoptions.html#wxsystemoptionsgetoption">external documentation</a>. -doc """ Gets an option. -The function is case-insensitive to `name`. Returns empty string if the option -hasn't been set. +The function is case-insensitive to `name`. Returns empty string if the option hasn't +been set. + +See: +* `setOption/2` -See: `setOption/2`, `getOptionInt/1`, `hasOption/1` +* `getOptionInt/1` + +* `hasOption/1` """. -spec getOption(Name) -> unicode:charlist() when Name::unicode:chardata(). @@ -88,14 +157,18 @@ getOption(Name) wxe_util:queue_cmd(Name_UC,?get_env(),?wxSystemOptions_GetOption), wxe_util:rec(?wxSystemOptions_GetOption). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemoptions.html#wxsystemoptionsgetoptionint">external documentation</a>. -doc """ Gets an option as an integer. -The function is case-insensitive to `name`. If the option hasn't been set, this -function returns 0. +The function is case-insensitive to `name`. If the option hasn't been set, this function +returns 0. + +See: +* `setOption/2` + +* `getOption/1` -See: `setOption/2`, `getOption/1`, `hasOption/1` +* `hasOption/1` """. -spec getOptionInt(Name) -> integer() when Name::unicode:chardata(). @@ -105,13 +178,17 @@ getOptionInt(Name) wxe_util:queue_cmd(Name_UC,?get_env(),?wxSystemOptions_GetOptionInt), wxe_util:rec(?wxSystemOptions_GetOptionInt). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemoptions.html#wxsystemoptionshasoption">external documentation</a>. -doc """ Returns true if the given option is present. The function is case-insensitive to `name`. -See: `setOption/2`, `getOption/1`, `getOptionInt/1` +See: +* `setOption/2` + +* `getOption/1` + +* `getOptionInt/1` """. -spec hasOption(Name) -> boolean() when Name::unicode:chardata(). @@ -121,13 +198,11 @@ hasOption(Name) wxe_util:queue_cmd(Name_UC,?get_env(),?wxSystemOptions_HasOption), wxe_util:rec(?wxSystemOptions_HasOption). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemoptions.html#wxsystemoptionsisfalse">external documentation</a>. -doc """ Returns true if the option with the given `name` had been set to 0 value. -This is mostly useful for boolean options for which you can't use -`GetOptionInt(name)` == 0 as this would also be true if the option hadn't been -set at all. +This is mostly useful for boolean options for which you can't use `GetOptionInt(name)` == +0 as this would also be true if the option hadn't been set at all. """. -spec isFalse(Name) -> boolean() when Name::unicode:chardata(). @@ -137,11 +212,6 @@ isFalse(Name) wxe_util:queue_cmd(Name_UC,?get_env(),?wxSystemOptions_IsFalse), wxe_util:rec(?wxSystemOptions_IsFalse). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemoptions.html#wxsystemoptionssetoption">external documentation</a>. -%% <br /> Also:<br /> -%% setOption(Name, Value) -> 'ok' when<br /> -%% Name::unicode:chardata(), Value::unicode:chardata().<br /> -%% -doc """ Sets an option. diff --git a/lib/wx/src/gen/wxSystemSettings.erl b/lib/wx/src/gen/wxSystemSettings.erl index 50455565530f..54295bcf1e0d 100644 --- a/lib/wx/src/gen/wxSystemSettings.erl +++ b/lib/wx/src/gen/wxSystemSettings.erl @@ -20,17 +20,18 @@ -module(wxSystemSettings). -moduledoc """ -Functions for wxSystemSettings class - `m:wxSystemSettings` allows the application to ask for details about the system. -This can include settings such as standard colours, fonts, and user interface -element sizes. +This can include settings such as standard colours, fonts, and user interface element sizes. + +See: +* `m:wxFont` + +* `wx_color()` -See: `m:wxFont`, [`wx_color()`](`t:wx:wx_colour/0`), `m:wxSystemOptions` +* `m:wxSystemOptions` -wxWidgets docs: -[wxSystemSettings](https://docs.wxwidgets.org/3.1/classwx_system_settings.html) +wxWidgets docs: [wxSystemSettings](https://docs.wxwidgets.org/3.2/classwx_system_settings.html) """. -include("wxe.hrl"). -export([getColour/1,getFont/1,getMetric/1,getMetric/2,getScreenType/0]). @@ -40,17 +41,15 @@ wxWidgets docs: -type wxSystemSettings() :: wx:wx_object(). -export_type([wxSystemSettings/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemsettings.html#wxsystemsettingsgetcolour">external documentation</a>. -%%<br /> Index = ?wxSYS_COLOUR_SCROLLBAR | ?wxSYS_COLOUR_DESKTOP | ?wxSYS_COLOUR_ACTIVECAPTION | ?wxSYS_COLOUR_INACTIVECAPTION | ?wxSYS_COLOUR_MENU | ?wxSYS_COLOUR_WINDOW | ?wxSYS_COLOUR_WINDOWFRAME | ?wxSYS_COLOUR_MENUTEXT | ?wxSYS_COLOUR_WINDOWTEXT | ?wxSYS_COLOUR_CAPTIONTEXT | ?wxSYS_COLOUR_ACTIVEBORDER | ?wxSYS_COLOUR_INACTIVEBORDER | ?wxSYS_COLOUR_APPWORKSPACE | ?wxSYS_COLOUR_HIGHLIGHT | ?wxSYS_COLOUR_HIGHLIGHTTEXT | ?wxSYS_COLOUR_BTNFACE | ?wxSYS_COLOUR_BTNSHADOW | ?wxSYS_COLOUR_GRAYTEXT | ?wxSYS_COLOUR_BTNTEXT | ?wxSYS_COLOUR_INACTIVECAPTIONTEXT | ?wxSYS_COLOUR_BTNHIGHLIGHT | ?wxSYS_COLOUR_3DDKSHADOW | ?wxSYS_COLOUR_3DLIGHT | ?wxSYS_COLOUR_INFOTEXT | ?wxSYS_COLOUR_INFOBK | ?wxSYS_COLOUR_LISTBOX | ?wxSYS_COLOUR_HOTLIGHT | ?wxSYS_COLOUR_GRADIENTACTIVECAPTION | ?wxSYS_COLOUR_GRADIENTINACTIVECAPTION | ?wxSYS_COLOUR_MENUHILIGHT | ?wxSYS_COLOUR_MENUBAR | ?wxSYS_COLOUR_LISTBOXTEXT | ?wxSYS_COLOUR_LISTBOXHIGHLIGHTTEXT | ?wxSYS_COLOUR_BACKGROUND | ?wxSYS_COLOUR_3DFACE | ?wxSYS_COLOUR_3DSHADOW | ?wxSYS_COLOUR_BTNHILIGHT | ?wxSYS_COLOUR_3DHIGHLIGHT | ?wxSYS_COLOUR_3DHILIGHT | ?wxSYS_COLOUR_FRAMEBK -doc """ Returns a system colour. Return: The returned colour is always valid. """. +%% Index = ?wxSYS_COLOUR_SCROLLBAR | ?wxSYS_COLOUR_DESKTOP | ?wxSYS_COLOUR_ACTIVECAPTION | ?wxSYS_COLOUR_INACTIVECAPTION | ?wxSYS_COLOUR_MENU | ?wxSYS_COLOUR_WINDOW | ?wxSYS_COLOUR_WINDOWFRAME | ?wxSYS_COLOUR_MENUTEXT | ?wxSYS_COLOUR_WINDOWTEXT | ?wxSYS_COLOUR_CAPTIONTEXT | ?wxSYS_COLOUR_ACTIVEBORDER | ?wxSYS_COLOUR_INACTIVEBORDER | ?wxSYS_COLOUR_APPWORKSPACE | ?wxSYS_COLOUR_HIGHLIGHT | ?wxSYS_COLOUR_HIGHLIGHTTEXT | ?wxSYS_COLOUR_BTNFACE | ?wxSYS_COLOUR_BTNSHADOW | ?wxSYS_COLOUR_GRAYTEXT | ?wxSYS_COLOUR_BTNTEXT | ?wxSYS_COLOUR_INACTIVECAPTIONTEXT | ?wxSYS_COLOUR_BTNHIGHLIGHT | ?wxSYS_COLOUR_3DDKSHADOW | ?wxSYS_COLOUR_3DLIGHT | ?wxSYS_COLOUR_INFOTEXT | ?wxSYS_COLOUR_INFOBK | ?wxSYS_COLOUR_LISTBOX | ?wxSYS_COLOUR_HOTLIGHT | ?wxSYS_COLOUR_GRADIENTACTIVECAPTION | ?wxSYS_COLOUR_GRADIENTINACTIVECAPTION | ?wxSYS_COLOUR_MENUHILIGHT | ?wxSYS_COLOUR_MENUBAR | ?wxSYS_COLOUR_LISTBOXTEXT | ?wxSYS_COLOUR_LISTBOXHIGHLIGHTTEXT | ?wxSYS_COLOUR_BACKGROUND | ?wxSYS_COLOUR_3DFACE | ?wxSYS_COLOUR_3DSHADOW | ?wxSYS_COLOUR_BTNHILIGHT | ?wxSYS_COLOUR_3DHIGHLIGHT | ?wxSYS_COLOUR_3DHILIGHT | ?wxSYS_COLOUR_FRAMEBK -spec getColour(Index) -> wx:wx_colour4() when Index::wx:wx_enum(). getColour(Index) @@ -58,13 +57,12 @@ getColour(Index) wxe_util:queue_cmd(Index,?get_env(),?wxSystemSettings_GetColour), wxe_util:rec(?wxSystemSettings_GetColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemsettings.html#wxsystemsettingsgetfont">external documentation</a>. -%%<br /> Index = ?wxSYS_OEM_FIXED_FONT | ?wxSYS_ANSI_FIXED_FONT | ?wxSYS_ANSI_VAR_FONT | ?wxSYS_SYSTEM_FONT | ?wxSYS_DEVICE_DEFAULT_FONT | ?wxSYS_DEFAULT_GUI_FONT -doc """ Returns a system font. Return: The returned font is always valid. """. +%% Index = ?wxSYS_OEM_FIXED_FONT | ?wxSYS_ANSI_FIXED_FONT | ?wxSYS_ANSI_VAR_FONT | ?wxSYS_SYSTEM_FONT | ?wxSYS_DEVICE_DEFAULT_FONT | ?wxSYS_DEFAULT_GUI_FONT -spec getFont(Index) -> wxFont:wxFont() when Index::wx:wx_enum(). getFont(Index) @@ -72,7 +70,7 @@ getFont(Index) wxe_util:queue_cmd(Index,?get_env(),?wxSystemSettings_GetFont), wxe_util:rec(?wxSystemSettings_GetFont). -%% @equiv getMetric(Index, []) +-doc(#{equiv => getMetric(Index, [])}). -spec getMetric(Index) -> integer() when Index::wx:wx_enum(). @@ -80,27 +78,24 @@ getMetric(Index) when is_integer(Index) -> getMetric(Index, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemsettings.html#wxsystemsettingsgetmetric">external documentation</a>. -%%<br /> Index = ?wxSYS_MOUSE_BUTTONS | ?wxSYS_BORDER_X | ?wxSYS_BORDER_Y | ?wxSYS_CURSOR_X | ?wxSYS_CURSOR_Y | ?wxSYS_DCLICK_X | ?wxSYS_DCLICK_Y | ?wxSYS_DRAG_X | ?wxSYS_DRAG_Y | ?wxSYS_EDGE_X | ?wxSYS_EDGE_Y | ?wxSYS_HSCROLL_ARROW_X | ?wxSYS_HSCROLL_ARROW_Y | ?wxSYS_HTHUMB_X | ?wxSYS_ICON_X | ?wxSYS_ICON_Y | ?wxSYS_ICONSPACING_X | ?wxSYS_ICONSPACING_Y | ?wxSYS_WINDOWMIN_X | ?wxSYS_WINDOWMIN_Y | ?wxSYS_SCREEN_X | ?wxSYS_SCREEN_Y | ?wxSYS_FRAMESIZE_X | ?wxSYS_FRAMESIZE_Y | ?wxSYS_SMALLICON_X | ?wxSYS_SMALLICON_Y | ?wxSYS_HSCROLL_Y | ?wxSYS_VSCROLL_X | ?wxSYS_VSCROLL_ARROW_X | ?wxSYS_VSCROLL_ARROW_Y | ?wxSYS_VTHUMB_Y | ?wxSYS_CAPTION_Y | ?wxSYS_MENU_Y | ?wxSYS_NETWORK_PRESENT | ?wxSYS_PENWINDOWS_PRESENT | ?wxSYS_SHOW_SOUNDS | ?wxSYS_SWAP_BUTTONS | ?wxSYS_DCLICK_MSEC | ?wxSYS_CARET_ON_MSEC | ?wxSYS_CARET_OFF_MSEC | ?wxSYS_CARET_TIMEOUT_MSEC -doc """ -Returns the value of a system metric, or -1 if the metric is not supported on -the current system. +Returns the value of a system metric, or -1 if the metric is not supported on the current +system. -The value of `win` determines if the metric returned is a global value or a -`m:wxWindow` based value, in which case it might determine the widget, the -display the window is on, or something similar. The window given should be as -close to the metric as possible (e.g. a `m:wxTopLevelWindow` in case of the -wxSYS_CAPTION_Y metric). +The value of `win` determines if the metric returned is a global value or a `m:wxWindow` +based value, in which case it might determine the widget, the display the window is on, or +something similar. The window given should be as close to the metric as possible (e.g. a `m:wxTopLevelWindow` +in case of the wxSYS_CAPTION_Y metric). `index` can be one of the ?wxSystemMetric enum values. -`win` is a pointer to the window for which the metric is requested. Specifying -the `win` parameter is encouraged, because some metrics on some ports are not -supported without one,or they might be capable of reporting better values if -given one. If a window does not make sense for a metric, one should still be -given, as for example it might determine which displays cursor width is -requested with wxSYS_CURSOR_X. +`win` is a pointer to the window for which the metric is requested. Specifying the `win` +parameter is encouraged, because some metrics on some ports are not supported without +one,or they might be capable of reporting better values if given one. If a window does not +make sense for a metric, one should still be given, as for example it might determine +which displays cursor width is requested with wxSYS_CURSOR_X. """. +%% Index = ?wxSYS_MOUSE_BUTTONS | ?wxSYS_BORDER_X | ?wxSYS_BORDER_Y | ?wxSYS_CURSOR_X | ?wxSYS_CURSOR_Y | ?wxSYS_DCLICK_X | ?wxSYS_DCLICK_Y | ?wxSYS_DRAG_X | ?wxSYS_DRAG_Y | ?wxSYS_EDGE_X | ?wxSYS_EDGE_Y | ?wxSYS_HSCROLL_ARROW_X | ?wxSYS_HSCROLL_ARROW_Y | ?wxSYS_HTHUMB_X | ?wxSYS_ICON_X | ?wxSYS_ICON_Y | ?wxSYS_ICONSPACING_X | ?wxSYS_ICONSPACING_Y | ?wxSYS_WINDOWMIN_X | ?wxSYS_WINDOWMIN_Y | ?wxSYS_SCREEN_X | ?wxSYS_SCREEN_Y | ?wxSYS_FRAMESIZE_X | ?wxSYS_FRAMESIZE_Y | ?wxSYS_SMALLICON_X | ?wxSYS_SMALLICON_Y | ?wxSYS_HSCROLL_Y | ?wxSYS_VSCROLL_X | ?wxSYS_VSCROLL_ARROW_X | ?wxSYS_VSCROLL_ARROW_Y | ?wxSYS_VTHUMB_Y | ?wxSYS_CAPTION_Y | ?wxSYS_MENU_Y | ?wxSYS_NETWORK_PRESENT | ?wxSYS_PENWINDOWS_PRESENT | ?wxSYS_SHOW_SOUNDS | ?wxSYS_SWAP_BUTTONS | ?wxSYS_DCLICK_MSEC | ?wxSYS_CARET_ON_MSEC | ?wxSYS_CARET_OFF_MSEC | ?wxSYS_CARET_TIMEOUT_MSEC -spec getMetric(Index, [Option]) -> integer() when Index::wx:wx_enum(), Option :: {'win', wxWindow:wxWindow()}. @@ -112,13 +107,12 @@ getMetric(Index, Options) wxe_util:queue_cmd(Index, Opts,?get_env(),?wxSystemSettings_GetMetric), wxe_util:rec(?wxSystemSettings_GetMetric). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxsystemsettings.html#wxsystemsettingsgetscreentype">external documentation</a>. -%%<br /> Res = ?wxSYS_SCREEN_NONE | ?wxSYS_SCREEN_TINY | ?wxSYS_SCREEN_PDA | ?wxSYS_SCREEN_SMALL | ?wxSYS_SCREEN_DESKTOP -doc """ Returns the screen type. The return value is one of the ?wxSystemScreenType enum values. """. +%% Res = ?wxSYS_SCREEN_NONE | ?wxSYS_SCREEN_TINY | ?wxSYS_SCREEN_PDA | ?wxSYS_SCREEN_SMALL | ?wxSYS_SCREEN_DESKTOP -spec getScreenType() -> wx:wx_enum(). getScreenType() -> wxe_util:queue_cmd(?get_env(), ?wxSystemSettings_GetScreenType), diff --git a/lib/wx/src/gen/wxTaskBarIcon.erl b/lib/wx/src/gen/wxTaskBarIcon.erl index e8586f79e638..22464b035d12 100644 --- a/lib/wx/src/gen/wxTaskBarIcon.erl +++ b/lib/wx/src/gen/wxTaskBarIcon.erl @@ -20,42 +20,47 @@ -module(wxTaskBarIcon). -moduledoc """ -Functions for wxTaskBarIcon class +This class represents a taskbar icon. -This class represents a taskbar icon. A taskbar icon is an icon that appears in -the 'system tray' and responds to mouse clicks, optionally with a tooltip above -it to help provide information. +A taskbar icon is an icon that appears in the 'system tray' and responds to mouse clicks, +optionally with a tooltip above it to help provide information. X Window System Note -Under X Window System, the window manager must support either the "System Tray -Protocol" (see -[http://freedesktop.org/wiki/Specifications/systemtray-spec](http://freedesktop.org/wiki/Specifications/systemtray-spec)) -by freedesktop.org (WMs used by modern desktop environments such as GNOME >= 2, -KDE >= 3 and XFCE >= 4 all do) or the older methods used in GNOME 1.2 and KDE 1 -and 2. +Under X Window System, the window manager must support either the "System Tray Protocol" +(see [http://freedesktop.org/wiki/Specifications/systemtray-spec](http://freedesktop.org/wiki/Specifications/systemtray-spec)) +by freedesktop.org (WMs used by modern desktop environments such as GNOME >= 2, KDE >= 3 +and XFCE >= 4 all do) or the older methods used in GNOME 1.2 and KDE 1 and 2. -If it doesn't, the icon will appear as a toplevel window on user's desktop. -Because not all window managers have system tray, there's no guarantee that -`m:wxTaskBarIcon` will work correctly under X Window System and so the -applications should use it only as an optional component of their user -interface. The user should be required to explicitly enable the taskbar icon on -Unix, it shouldn't be on by default. +If it doesn't, the icon will appear as a toplevel window on user's desktop. Because not +all window managers have system tray, there's no guarantee that `m:wxTaskBarIcon` will +work correctly under X Window System and so the applications should use it only as an +optional component of their user interface. The user should be required to explicitly +enable the taskbar icon on Unix, it shouldn't be on by default. -This class is derived (and can use functions) from: `m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxTaskBarIcon](https://docs.wxwidgets.org/3.1/classwx_task_bar_icon.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxTaskBarIcon](https://docs.wxwidgets.org/3.2/classwx_task_bar_icon.html) ## Events -Event types emitted from this class: [`taskbar_move`](`m:wxTaskBarIconEvent`), -[`taskbar_left_down`](`m:wxTaskBarIconEvent`), -[`taskbar_left_up`](`m:wxTaskBarIconEvent`), -[`taskbar_right_down`](`m:wxTaskBarIconEvent`), -[`taskbar_right_up`](`m:wxTaskBarIconEvent`), -[`taskbar_left_dclick`](`m:wxTaskBarIconEvent`), -[`taskbar_right_dclick`](`m:wxTaskBarIconEvent`) +Event types emitted from this class: + +* [`taskbar_move`](`m:wxTaskBarIconEvent`) + +* [`taskbar_left_down`](`m:wxTaskBarIconEvent`) + +* [`taskbar_left_up`](`m:wxTaskBarIconEvent`) + +* [`taskbar_right_down`](`m:wxTaskBarIconEvent`) + +* [`taskbar_right_up`](`m:wxTaskBarIconEvent`) + +* [`taskbar_left_dclick`](`m:wxTaskBarIconEvent`) + +* [`taskbar_right_dclick`](`m:wxTaskBarIconEvent`) """. -include("wxe.hrl"). -export([ new/0, new/1 ,destroy/1,popupMenu/2,removeIcon/1,setIcon/2,setIcon/3]). @@ -65,13 +70,11 @@ Event types emitted from this class: [`taskbar_move`](`m:wxTaskBarIconEvent`), -type wxTaskBarIcon() :: wx:wx_object(). -export_type([wxTaskBarIcon/0]). -%% @hidden -doc false. parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). --doc false. -spec new() -> wxTaskBarIcon(). new() -> new([]). @@ -79,11 +82,6 @@ new() -> %% @doc Creates a TaskBarIcon with a callback function for CreatePopupMenu: %% <pre>Callback() -> term()</pre> %% --doc """ -Default constructor. - -The iconType is only applicable on wxOSX/Cocoa. -""". -spec new([Option]) -> wxTaskBarIcon() when Option :: {'iconType', wx:wx_enum()} | {'createPopupMenu', fun(() -> wxMenu:wxMenu())}. @@ -97,15 +95,14 @@ new(Options) when is_list(Options) -> wxe_util:queue_cmd(Opts,?get_env(), Op), wxe_util:rec(Op). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtaskbaricon.html#wxtaskbariconpopupmenu">external documentation</a>. -doc """ Pops up a menu at the current mouse position. The events can be handled by a class derived from `m:wxTaskBarIcon`. -Note: It is recommended to override `CreatePopupMenu()` (not implemented in wx) -callback instead of calling this method from event handler, because some ports -(e.g. wxCocoa) may not implement `popupMenu/2` and mouse click events at all. +Note: It is recommended to override `CreatePopupMenu()` (not implemented in wx) callback +instead of calling this method from event handler, because some ports (e.g. wxCocoa) may +not implement `popupMenu/2` and mouse click events at all. """. -spec popupMenu(This, Menu) -> boolean() when This::wxTaskBarIcon(), Menu::wxMenu:wxMenu(). @@ -115,7 +112,6 @@ popupMenu(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu) -> wxe_util:queue_cmd(This,Menu,?get_env(),?wxTaskBarIcon_PopupMenu), wxe_util:rec(?wxTaskBarIcon_PopupMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtaskbaricon.html#wxtaskbariconremoveicon">external documentation</a>. -doc "Removes the icon previously set with `setIcon/3`.". -spec removeIcon(This) -> boolean() when This::wxTaskBarIcon(). @@ -124,7 +120,7 @@ removeIcon(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTaskBarIcon_RemoveIcon), wxe_util:rec(?wxTaskBarIcon_RemoveIcon). -%% @equiv setIcon(This,Icon, []) +-doc(#{equiv => setIcon(This,Icon, [])}). -spec setIcon(This, Icon) -> boolean() when This::wxTaskBarIcon(), Icon::wxIcon:wxIcon(). @@ -132,7 +128,6 @@ setIcon(This,Icon) when is_record(This, wx_ref),is_record(Icon, wx_ref) -> setIcon(This,Icon, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtaskbaricon.html#wxtaskbariconseticon">external documentation</a>. -doc "Sets the icon, and optional tooltip text.". -spec setIcon(This, Icon, [Option]) -> boolean() when This::wxTaskBarIcon(), Icon::wxIcon:wxIcon(), @@ -147,26 +142,20 @@ setIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon, Options) wxe_util:queue_cmd(This,Icon, Opts,?get_env(),?wxTaskBarIcon_SetIcon), wxe_util:rec(?wxTaskBarIcon_SetIcon). -%% @doc Destroys this object, do not use object again --doc "Destroys the `m:wxTaskBarIcon` object, removing the icon if not already removed.". +-doc "Destroys the object". -spec destroy(This::wxTaskBarIcon()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTaskBarIcon), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxTaskBarIconEvent.erl b/lib/wx/src/gen/wxTaskBarIconEvent.erl index 435253a2a374..4aee54dc85b0 100644 --- a/lib/wx/src/gen/wxTaskBarIconEvent.erl +++ b/lib/wx/src/gen/wxTaskBarIconEvent.erl @@ -20,16 +20,16 @@ -module(wxTaskBarIconEvent). -moduledoc """ -Functions for wxTaskBarIconEvent class +The event class used by `m:wxTaskBarIcon`. -The event class used by `m:wxTaskBarIcon`. For a list of the event macros meant -to be used with `m:wxTaskBarIconEvent`, please look at `m:wxTaskBarIcon` -description. +For a list of the event macros meant to be used with `m:wxTaskBarIconEvent`, please look +at `m:wxTaskBarIcon` description. -This class is derived (and can use functions) from: `m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxTaskBarIconEvent](https://docs.wxwidgets.org/3.1/classwx_task_bar_icon_event.html) +* `m:wxEvent` + +wxWidgets docs: [wxTaskBarIconEvent](https://docs.wxwidgets.org/3.2/classwx_task_bar_icon_event.html) """. -include("wxe.hrl"). -export([]). @@ -42,36 +42,26 @@ wxWidgets docs: -include("wx.hrl"). -type wxTaskBarIconEventType() :: 'taskbar_move' | 'taskbar_left_down' | 'taskbar_left_up' | 'taskbar_right_down' | 'taskbar_right_up' | 'taskbar_left_dclick' | 'taskbar_right_dclick'. -export_type([wxTaskBarIconEvent/0, wxTaskBarIcon/0, wxTaskBarIconEventType/0]). -%% @hidden -doc false. parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxTextAttr.erl b/lib/wx/src/gen/wxTextAttr.erl index 817aa01222a8..bff26836811b 100644 --- a/lib/wx/src/gen/wxTextAttr.erl +++ b/lib/wx/src/gen/wxTextAttr.erl @@ -20,19 +20,16 @@ -module(wxTextAttr). -moduledoc """ -Functions for wxTextAttr class +`m:wxTextAttr` represents the character and paragraph attributes, or style, for a range +of text in a `m:wxTextCtrl` or `wxRichTextCtrl` (not implemented in wx). -`m:wxTextAttr` represents the character and paragraph attributes, or style, for -a range of text in a `m:wxTextCtrl` or `wxRichTextCtrl` (not implemented in wx). +When setting up a `m:wxTextAttr` object, pass a bitlist mask to `setFlags/2` to indicate which style +elements should be changed. As a convenience, when you call a setter such as SetFont, the +relevant bit will be set. -When setting up a `m:wxTextAttr` object, pass a bitlist mask to `setFlags/2` to -indicate which style elements should be changed. As a convenience, when you call -a setter such as SetFont, the relevant bit will be set. +See: `m:wxTextCtrl` -See: `m:wxTextCtrl`, `wxRichTextCtrl` (not implemented in wx) - -wxWidgets docs: -[wxTextAttr](https://docs.wxwidgets.org/3.1/classwx_text_attr.html) +wxWidgets docs: [wxTextAttr](https://docs.wxwidgets.org/3.2/classwx_text_attr.html) """. -include("wxe.hrl"). -export([destroy/1,getAlignment/1,getBackgroundColour/1,getFlags/1,getFont/1, @@ -50,23 +47,17 @@ wxWidgets docs: -type wxTextAttr() :: wx:wx_object(). -export_type([wxTextAttr/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrwxtextattr">external documentation</a>. -doc "Constructors.". -spec new() -> wxTextAttr(). new() -> wxe_util:queue_cmd(?get_env(), ?wxTextAttr_new_0), wxe_util:rec(?wxTextAttr_new_0). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrwxtextattr">external documentation</a>. -%% <br /> Also:<br /> -%% new(Attr) -> wxTextAttr() when<br /> -%% Attr::wxTextAttr().<br /> -%% -%%<br /> Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED +-doc "". +%% Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -spec new(ColText) -> wxTextAttr() when ColText::wx:wx_colour(); (Attr) -> wxTextAttr() when @@ -80,8 +71,8 @@ new(#wx_ref{type=AttrT}=Attr) -> wxe_util:queue_cmd(Attr,?get_env(),?wxTextAttr_new_1), wxe_util:rec(?wxTextAttr_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrwxtextattr">external documentation</a>. -%%<br /> Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED +-doc "". +%% Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -spec new(ColText, [Option]) -> wxTextAttr() when ColText::wx:wx_colour(), Option :: {'colBack', wx:wx_colour()} @@ -97,13 +88,12 @@ new(ColText, Options) wxe_util:queue_cmd(wxe_util:color(ColText), Opts,?get_env(),?wxTextAttr_new_2), wxe_util:rec(?wxTextAttr_new_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetalignment">external documentation</a>. -%%<br /> Res = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -doc """ Returns the alignment flags. See ?wxTextAttrAlignment for a list of available styles. """. +%% Res = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -spec getAlignment(This) -> wx:wx_enum() when This::wxTextAttr(). getAlignment(#wx_ref{type=ThisT}=This) -> @@ -111,7 +101,6 @@ getAlignment(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetAlignment), wxe_util:rec(?wxTextAttr_GetAlignment). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetbackgroundcolour">external documentation</a>. -doc "Returns the background colour.". -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxTextAttr(). @@ -120,13 +109,10 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetBackgroundColour), wxe_util:rec(?wxTextAttr_GetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfont">external documentation</a>. -doc """ -Creates and returns a font specified by the font attributes in the -`m:wxTextAttr` object. +Creates and returns a font specified by the font attributes in the `m:wxTextAttr` object. -Note that `m:wxTextAttr` does not store a `m:wxFont` object, so this is only a -temporary font. +Note that `m:wxTextAttr` does not store a `m:wxFont` object, so this is only a temporary font. For greater efficiency, access the font attributes directly. """. @@ -137,9 +123,8 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFont), wxe_util:rec(?wxTextAttr_GetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontencoding">external documentation</a>. -%%<br /> Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc "Returns the font encoding.". +%% Res = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec getFontEncoding(This) -> wx:wx_enum() when This::wxTextAttr(). getFontEncoding(#wx_ref{type=ThisT}=This) -> @@ -147,7 +132,6 @@ getFontEncoding(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontEncoding), wxe_util:rec(?wxTextAttr_GetFontEncoding). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontfacename">external documentation</a>. -doc "Returns the font face name.". -spec getFontFaceName(This) -> unicode:charlist() when This::wxTextAttr(). @@ -156,7 +140,6 @@ getFontFaceName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontFaceName), wxe_util:rec(?wxTextAttr_GetFontFaceName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontsize">external documentation</a>. -doc "Returns the font size in points.". -spec getFontSize(This) -> integer() when This::wxTextAttr(). @@ -165,9 +148,8 @@ getFontSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontSize), wxe_util:rec(?wxTextAttr_GetFontSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontstyle">external documentation</a>. -%%<br /> Res = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -doc "Returns the font style.". +%% Res = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -spec getFontStyle(This) -> wx:wx_enum() when This::wxTextAttr(). getFontStyle(#wx_ref{type=ThisT}=This) -> @@ -175,7 +157,6 @@ getFontStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontStyle), wxe_util:rec(?wxTextAttr_GetFontStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontunderlined">external documentation</a>. -doc "Returns true if the font is underlined.". -spec getFontUnderlined(This) -> boolean() when This::wxTextAttr(). @@ -184,9 +165,8 @@ getFontUnderlined(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontUnderlined), wxe_util:rec(?wxTextAttr_GetFontUnderlined). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetfontweight">external documentation</a>. -%%<br /> Res = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -doc "Returns the font weight.". +%% Res = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec getFontWeight(This) -> wx:wx_enum() when This::wxTextAttr(). getFontWeight(#wx_ref{type=ThisT}=This) -> @@ -194,7 +174,6 @@ getFontWeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFontWeight), wxe_util:rec(?wxTextAttr_GetFontWeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetleftindent">external documentation</a>. -doc "Returns the left indent in tenths of a millimetre.". -spec getLeftIndent(This) -> integer() when This::wxTextAttr(). @@ -203,7 +182,6 @@ getLeftIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetLeftIndent), wxe_util:rec(?wxTextAttr_GetLeftIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetleftsubindent">external documentation</a>. -doc "Returns the left sub-indent in tenths of a millimetre.". -spec getLeftSubIndent(This) -> integer() when This::wxTextAttr(). @@ -212,7 +190,6 @@ getLeftSubIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetLeftSubIndent), wxe_util:rec(?wxTextAttr_GetLeftSubIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetrightindent">external documentation</a>. -doc "Returns the right indent in tenths of a millimeter.". -spec getRightIndent(This) -> integer() when This::wxTextAttr(). @@ -221,12 +198,11 @@ getRightIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetRightIndent), wxe_util:rec(?wxTextAttr_GetRightIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgettabs">external documentation</a>. -doc """ Returns an array of tab stops, each expressed in tenths of a millimeter. -Each stop is measured from the left margin and therefore each value must be -larger than the last. +Each stop is measured from the left margin and therefore each value must be larger than +the last. """. -spec getTabs(This) -> [integer()] when This::wxTextAttr(). @@ -235,7 +211,6 @@ getTabs(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetTabs), wxe_util:rec(?wxTextAttr_GetTabs). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgettextcolour">external documentation</a>. -doc "Returns the text foreground colour.". -spec getTextColour(This) -> wx:wx_colour4() when This::wxTextAttr(). @@ -244,7 +219,6 @@ getTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetTextColour), wxe_util:rec(?wxTextAttr_GetTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrhasbackgroundcolour">external documentation</a>. -doc "Returns true if the attribute object specifies a background colour.". -spec hasBackgroundColour(This) -> boolean() when This::wxTextAttr(). @@ -253,7 +227,6 @@ hasBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_HasBackgroundColour), wxe_util:rec(?wxTextAttr_HasBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrhasfont">external documentation</a>. -doc "Returns true if the attribute object specifies any font attributes.". -spec hasFont(This) -> boolean() when This::wxTextAttr(). @@ -262,7 +235,6 @@ hasFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_HasFont), wxe_util:rec(?wxTextAttr_HasFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrhastextcolour">external documentation</a>. -doc "Returns true if the attribute object specifies a text foreground colour.". -spec hasTextColour(This) -> boolean() when This::wxTextAttr(). @@ -271,7 +243,6 @@ hasTextColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_HasTextColour), wxe_util:rec(?wxTextAttr_HasTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrgetflags">external documentation</a>. -doc """ Returns flags indicating which attributes are applicable. @@ -284,7 +255,6 @@ getFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_GetFlags), wxe_util:rec(?wxTextAttr_GetFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrisdefault">external documentation</a>. -doc "Returns false if we have any attributes set, true otherwise.". -spec isDefault(This) -> boolean() when This::wxTextAttr(). @@ -293,16 +263,15 @@ isDefault(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextAttr_IsDefault), wxe_util:rec(?wxTextAttr_IsDefault). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetalignment">external documentation</a>. -%%<br /> Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -doc """ Sets the paragraph alignment. See ?wxTextAttrAlignment enumeration values. -Of these, wxTEXT_ALIGNMENT_JUSTIFIED is unimplemented. In future justification -may be supported when printing or previewing, only. +Of these, wxTEXT_ALIGNMENT_JUSTIFIED is unimplemented. In future justification may be +supported when printing or previewing, only. """. +%% Alignment = ?wxTEXT_ALIGNMENT_DEFAULT | ?wxTEXT_ALIGNMENT_LEFT | ?wxTEXT_ALIGNMENT_CENTRE | ?wxTEXT_ALIGNMENT_CENTER | ?wxTEXT_ALIGNMENT_RIGHT | ?wxTEXT_ALIGNMENT_JUSTIFIED -spec setAlignment(This, Alignment) -> 'ok' when This::wxTextAttr(), Alignment::wx:wx_enum(). setAlignment(#wx_ref{type=ThisT}=This,Alignment) @@ -310,7 +279,6 @@ setAlignment(#wx_ref{type=ThisT}=This,Alignment) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Alignment,?get_env(),?wxTextAttr_SetAlignment). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetbackgroundcolour">external documentation</a>. -doc "Sets the background colour.". -spec setBackgroundColour(This, ColBack) -> 'ok' when This::wxTextAttr(), ColBack::wx:wx_colour(). @@ -319,7 +287,6 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,ColBack) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,wxe_util:color(ColBack),?get_env(),?wxTextAttr_SetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetflags">external documentation</a>. -doc """ Sets the flags determining which styles are being specified. @@ -332,7 +299,7 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Flags,?get_env(),?wxTextAttr_SetFlags). -%% @equiv setFont(This,Font, []) +-doc(#{equiv => setFont(This,Font, [])}). -spec setFont(This, Font) -> 'ok' when This::wxTextAttr(), Font::wxFont:wxFont(). @@ -340,7 +307,6 @@ setFont(This,Font) when is_record(This, wx_ref),is_record(Font, wx_ref) -> setFont(This,Font, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfont">external documentation</a>. -doc """ Sets the attributes for the given font. @@ -358,9 +324,8 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Font, Opts,?get_env(),?wxTextAttr_SetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontencoding">external documentation</a>. -%%<br /> Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -doc "Sets the font encoding.". +%% Encoding = ?wxFONTENCODING_SYSTEM | ?wxFONTENCODING_DEFAULT | ?wxFONTENCODING_ISO8859_1 | ?wxFONTENCODING_ISO8859_2 | ?wxFONTENCODING_ISO8859_3 | ?wxFONTENCODING_ISO8859_4 | ?wxFONTENCODING_ISO8859_5 | ?wxFONTENCODING_ISO8859_6 | ?wxFONTENCODING_ISO8859_7 | ?wxFONTENCODING_ISO8859_8 | ?wxFONTENCODING_ISO8859_9 | ?wxFONTENCODING_ISO8859_10 | ?wxFONTENCODING_ISO8859_11 | ?wxFONTENCODING_ISO8859_12 | ?wxFONTENCODING_ISO8859_13 | ?wxFONTENCODING_ISO8859_14 | ?wxFONTENCODING_ISO8859_15 | ?wxFONTENCODING_ISO8859_MAX | ?wxFONTENCODING_KOI8 | ?wxFONTENCODING_KOI8_U | ?wxFONTENCODING_ALTERNATIVE | ?wxFONTENCODING_BULGARIAN | ?wxFONTENCODING_CP437 | ?wxFONTENCODING_CP850 | ?wxFONTENCODING_CP852 | ?wxFONTENCODING_CP855 | ?wxFONTENCODING_CP866 | ?wxFONTENCODING_CP874 | ?wxFONTENCODING_CP932 | ?wxFONTENCODING_CP936 | ?wxFONTENCODING_CP949 | ?wxFONTENCODING_CP950 | ?wxFONTENCODING_CP1250 | ?wxFONTENCODING_CP1251 | ?wxFONTENCODING_CP1252 | ?wxFONTENCODING_CP1253 | ?wxFONTENCODING_CP1254 | ?wxFONTENCODING_CP1255 | ?wxFONTENCODING_CP1256 | ?wxFONTENCODING_CP1257 | ?wxFONTENCODING_CP1258 | ?wxFONTENCODING_CP1361 | ?wxFONTENCODING_CP12_MAX | ?wxFONTENCODING_UTF7 | ?wxFONTENCODING_UTF8 | ?wxFONTENCODING_EUC_JP | ?wxFONTENCODING_UTF16BE | ?wxFONTENCODING_UTF16LE | ?wxFONTENCODING_UTF32BE | ?wxFONTENCODING_UTF32LE | ?wxFONTENCODING_MACROMAN | ?wxFONTENCODING_MACJAPANESE | ?wxFONTENCODING_MACCHINESETRAD | ?wxFONTENCODING_MACKOREAN | ?wxFONTENCODING_MACARABIC | ?wxFONTENCODING_MACHEBREW | ?wxFONTENCODING_MACGREEK | ?wxFONTENCODING_MACCYRILLIC | ?wxFONTENCODING_MACDEVANAGARI | ?wxFONTENCODING_MACGURMUKHI | ?wxFONTENCODING_MACGUJARATI | ?wxFONTENCODING_MACORIYA | ?wxFONTENCODING_MACBENGALI | ?wxFONTENCODING_MACTAMIL | ?wxFONTENCODING_MACTELUGU | ?wxFONTENCODING_MACKANNADA | ?wxFONTENCODING_MACMALAJALAM | ?wxFONTENCODING_MACSINHALESE | ?wxFONTENCODING_MACBURMESE | ?wxFONTENCODING_MACKHMER | ?wxFONTENCODING_MACTHAI | ?wxFONTENCODING_MACLAOTIAN | ?wxFONTENCODING_MACGEORGIAN | ?wxFONTENCODING_MACARMENIAN | ?wxFONTENCODING_MACCHINESESIMP | ?wxFONTENCODING_MACTIBETAN | ?wxFONTENCODING_MACMONGOLIAN | ?wxFONTENCODING_MACETHIOPIC | ?wxFONTENCODING_MACCENTRALEUR | ?wxFONTENCODING_MACVIATNAMESE | ?wxFONTENCODING_MACARABICEXT | ?wxFONTENCODING_MACSYMBOL | ?wxFONTENCODING_MACDINGBATS | ?wxFONTENCODING_MACTURKISH | ?wxFONTENCODING_MACCROATIAN | ?wxFONTENCODING_MACICELANDIC | ?wxFONTENCODING_MACROMANIAN | ?wxFONTENCODING_MACCELTIC | ?wxFONTENCODING_MACGAELIC | ?wxFONTENCODING_MACKEYBOARD | ?wxFONTENCODING_ISO2022_JP | ?wxFONTENCODING_MAX | ?wxFONTENCODING_MACMIN | ?wxFONTENCODING_MACMAX | ?wxFONTENCODING_UTF16 | ?wxFONTENCODING_UTF32 | ?wxFONTENCODING_UNICODE | ?wxFONTENCODING_GB2312 | ?wxFONTENCODING_BIG5 | ?wxFONTENCODING_SHIFT_JIS | ?wxFONTENCODING_EUC_KR | ?wxFONTENCODING_JOHAB | ?wxFONTENCODING_VIETNAMESE -spec setFontEncoding(This, Encoding) -> 'ok' when This::wxTextAttr(), Encoding::wx:wx_enum(). setFontEncoding(#wx_ref{type=ThisT}=This,Encoding) @@ -368,7 +333,6 @@ setFontEncoding(#wx_ref{type=ThisT}=This,Encoding) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Encoding,?get_env(),?wxTextAttr_SetFontEncoding). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontfacename">external documentation</a>. -doc "Sets the font face name.". -spec setFontFaceName(This, FaceName) -> 'ok' when This::wxTextAttr(), FaceName::unicode:chardata(). @@ -378,9 +342,8 @@ setFontFaceName(#wx_ref{type=ThisT}=This,FaceName) FaceName_UC = unicode:characters_to_binary(FaceName), wxe_util:queue_cmd(This,FaceName_UC,?get_env(),?wxTextAttr_SetFontFaceName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontfamily">external documentation</a>. -%%<br /> Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -doc "Sets the font family.". +%% Family = ?wxFONTFAMILY_DEFAULT | ?wxFONTFAMILY_DECORATIVE | ?wxFONTFAMILY_ROMAN | ?wxFONTFAMILY_SCRIPT | ?wxFONTFAMILY_SWISS | ?wxFONTFAMILY_MODERN | ?wxFONTFAMILY_TELETYPE | ?wxFONTFAMILY_MAX | ?wxFONTFAMILY_UNKNOWN -spec setFontFamily(This, Family) -> 'ok' when This::wxTextAttr(), Family::wx:wx_enum(). setFontFamily(#wx_ref{type=ThisT}=This,Family) @@ -388,7 +351,6 @@ setFontFamily(#wx_ref{type=ThisT}=This,Family) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Family,?get_env(),?wxTextAttr_SetFontFamily). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontsize">external documentation</a>. -doc "Sets the font size in points.". -spec setFontSize(This, PointSize) -> 'ok' when This::wxTextAttr(), PointSize::integer(). @@ -397,7 +359,6 @@ setFontSize(#wx_ref{type=ThisT}=This,PointSize) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,PointSize,?get_env(),?wxTextAttr_SetFontSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontpointsize">external documentation</a>. -doc "Sets the font size in points.". -spec setFontPointSize(This, PointSize) -> 'ok' when This::wxTextAttr(), PointSize::integer(). @@ -406,7 +367,6 @@ setFontPointSize(#wx_ref{type=ThisT}=This,PointSize) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,PointSize,?get_env(),?wxTextAttr_SetFontPointSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontpixelsize">external documentation</a>. -doc "Sets the font size in pixels.". -spec setFontPixelSize(This, PixelSize) -> 'ok' when This::wxTextAttr(), PixelSize::integer(). @@ -415,9 +375,8 @@ setFontPixelSize(#wx_ref{type=ThisT}=This,PixelSize) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,PixelSize,?get_env(),?wxTextAttr_SetFontPixelSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontstyle">external documentation</a>. -%%<br /> FontStyle = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -doc "Sets the font style (normal, italic or slanted).". +%% FontStyle = ?wxFONTSTYLE_NORMAL | ?wxFONTSTYLE_ITALIC | ?wxFONTSTYLE_SLANT | ?wxFONTSTYLE_MAX -spec setFontStyle(This, FontStyle) -> 'ok' when This::wxTextAttr(), FontStyle::wx:wx_enum(). setFontStyle(#wx_ref{type=ThisT}=This,FontStyle) @@ -425,7 +384,6 @@ setFontStyle(#wx_ref{type=ThisT}=This,FontStyle) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,FontStyle,?get_env(),?wxTextAttr_SetFontStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontunderlined">external documentation</a>. -doc "Sets the font underlining (solid line, text colour).". -spec setFontUnderlined(This, Underlined) -> 'ok' when This::wxTextAttr(), Underlined::boolean(). @@ -434,9 +392,8 @@ setFontUnderlined(#wx_ref{type=ThisT}=This,Underlined) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Underlined,?get_env(),?wxTextAttr_SetFontUnderlined). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetfontweight">external documentation</a>. -%%<br /> FontWeight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -doc "Sets the font weight.". +%% FontWeight = ?wxFONTWEIGHT_INVALID | ?wxFONTWEIGHT_THIN | ?wxFONTWEIGHT_EXTRALIGHT | ?wxFONTWEIGHT_LIGHT | ?wxFONTWEIGHT_NORMAL | ?wxFONTWEIGHT_MEDIUM | ?wxFONTWEIGHT_SEMIBOLD | ?wxFONTWEIGHT_BOLD | ?wxFONTWEIGHT_EXTRABOLD | ?wxFONTWEIGHT_HEAVY | ?wxFONTWEIGHT_EXTRAHEAVY | ?wxFONTWEIGHT_MAX -spec setFontWeight(This, FontWeight) -> 'ok' when This::wxTextAttr(), FontWeight::wx:wx_enum(). setFontWeight(#wx_ref{type=ThisT}=This,FontWeight) @@ -444,7 +401,7 @@ setFontWeight(#wx_ref{type=ThisT}=This,FontWeight) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,FontWeight,?get_env(),?wxTextAttr_SetFontWeight). -%% @equiv setLeftIndent(This,Indent, []) +-doc(#{equiv => setLeftIndent(This,Indent, [])}). -spec setLeftIndent(This, Indent) -> 'ok' when This::wxTextAttr(), Indent::integer(). @@ -452,22 +409,19 @@ setLeftIndent(This,Indent) when is_record(This, wx_ref),is_integer(Indent) -> setLeftIndent(This,Indent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetleftindent">external documentation</a>. -doc """ Sets the left indent and left subindent in tenths of a millimetre. -The sub-indent is an offset from the left of the paragraph, and is used for all -but the first line in a paragraph. +The sub-indent is an offset from the left of the paragraph, and is used for all but the +first line in a paragraph. -A positive value will cause the first line to appear to the left of the -subsequent lines, and a negative value will cause the first line to be indented -relative to the subsequent lines. +A positive value will cause the first line to appear to the left of the subsequent lines, +and a negative value will cause the first line to be indented relative to the subsequent lines. -`wxRichTextBuffer` (not implemented in wx) uses indentation to render a bulleted -item. The left indent is the distance between the margin and the bullet. The -content of the paragraph, including the first line, starts at leftMargin + -leftSubIndent. So the distance between the left edge of the bullet and the left -of the actual paragraph is leftSubIndent. +`wxRichTextBuffer` (not implemented in wx) uses indentation to render a bulleted item. +The left indent is the distance between the margin and the bullet. The content of the +paragraph, including the first line, starts at leftMargin + leftSubIndent. So the distance +between the left edge of the bullet and the left of the actual paragraph is leftSubIndent. """. -spec setLeftIndent(This, Indent, [Option]) -> 'ok' when This::wxTextAttr(), Indent::integer(), @@ -480,7 +434,6 @@ setLeftIndent(#wx_ref{type=ThisT}=This,Indent, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Indent, Opts,?get_env(),?wxTextAttr_SetLeftIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsetrightindent">external documentation</a>. -doc "Sets the right indent in tenths of a millimetre.". -spec setRightIndent(This, Indent) -> 'ok' when This::wxTextAttr(), Indent::integer(). @@ -489,12 +442,11 @@ setRightIndent(#wx_ref{type=ThisT}=This,Indent) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Indent,?get_env(),?wxTextAttr_SetRightIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsettabs">external documentation</a>. -doc """ Sets the tab stops, expressed in tenths of a millimetre. -Each stop is measured from the left margin and therefore each value must be -larger than the last. +Each stop is measured from the left margin and therefore each value must be larger than +the last. """. -spec setTabs(This, Tabs) -> 'ok' when This::wxTextAttr(), Tabs::[integer()]. @@ -503,7 +455,6 @@ setTabs(#wx_ref{type=ThisT}=This,Tabs) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,Tabs,?get_env(),?wxTextAttr_SetTabs). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextattr.html#wxtextattrsettextcolour">external documentation</a>. -doc "Sets the text foreground colour.". -spec setTextColour(This, ColText) -> 'ok' when This::wxTextAttr(), ColText::wx:wx_colour(). @@ -512,8 +463,7 @@ setTextColour(#wx_ref{type=ThisT}=This,ColText) ?CLASS(ThisT,wxTextAttr), wxe_util:queue_cmd(This,wxe_util:color(ColText),?get_env(),?wxTextAttr_SetTextColour). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxTextAttr()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTextAttr), diff --git a/lib/wx/src/gen/wxTextCtrl.erl b/lib/wx/src/gen/wxTextCtrl.erl index 28898ed15d68..0a718bb485a2 100644 --- a/lib/wx/src/gen/wxTextCtrl.erl +++ b/lib/wx/src/gen/wxTextCtrl.erl @@ -20,124 +20,181 @@ -module(wxTextCtrl). -moduledoc """ -Functions for wxTextCtrl class - A text control allows text to be displayed and edited. -It may be single line or multi-line. Notice that a lot of methods of the text -controls are found in the base `wxTextEntry` (not implemented in wx) class which -is a common base class for `m:wxTextCtrl` and other controls using a single line -text entry field (e.g. `m:wxComboBox`). +It may be single line or multi-line. Notice that a lot of methods of the text controls +are found in the base `wxTextEntry` (not implemented in wx) class which is a common base +class for `m:wxTextCtrl` and other controls using a single line text entry field (e.g. `m:wxComboBox`). -Styles +## Styles This class supports the following styles: +* wxTE_PROCESS_ENTER: The control will generate the event `wxEVT_TEXT_ENTER` that can be +handled by the program. Otherwise, i.e. either if this style not specified at all, or it +is used, but there is no event handler for this event or the event handler called `wxEvent:skip/2` to +avoid overriding the default handling, pressing Enter key is either processed internally +by the control or used to activate the default button of the dialog, if any. + +* wxTE_PROCESS_TAB: Normally, TAB key is used for keyboard navigation and pressing it in a +control switches focus to the next one. With this style, this won't happen and if the TAB +is not otherwise processed (e.g. by `wxEVT_CHAR` event handler), a literal TAB character +is inserted into the control. Notice that this style has no effect for single-line text +controls when using wxGTK. + +* wxTE_MULTILINE: The text control allows multiple lines. If this style is not specified, +line break characters should not be used in the controls value. + +* wxTE_PASSWORD: The text will be echoed as asterisks. + +* wxTE_READONLY: The text will not be user-editable. + +* wxTE_RICH: Use rich text control under MSW, this allows having more than 64KB of text in +the control. This style is ignored under other platforms. + +* wxTE_RICH2: Use rich text control version 2.0 or higher under MSW, this style is ignored +under other platforms + +* wxTE_AUTO_URL: Highlight the URLs and generate the wxTextUrlEvents when mouse events +occur over them. + +* wxTE_NOHIDESEL: By default, the Windows text control doesn't show the selection when it +doesn't have focus - use this style to force it to always show it. It doesn't do anything +under other platforms. + +* wxHSCROLL: A horizontal scrollbar will be created and used, so that text won't be +wrapped. No effect under wxGTK1. + +* wxTE_NO_VSCROLL: For multiline controls only: vertical scrollbar will never be created. +This limits the amount of text which can be entered into the control to what can be +displayed in it under wxMSW but not under wxGTK or wxOSX. Currently not implemented for +the other platforms. + +* wxTE_LEFT: The text in the control will be left-justified (default). + +* wxTE_CENTRE: The text in the control will be centered (wxMSW, wxGTK, wxOSX). + +* wxTE_RIGHT: The text in the control will be right-justified (wxMSW, wxGTK, wxOSX). + +* wxTE_DONTWRAP: Same as wxHSCROLL style: don't wrap at all, show horizontal scrollbar +instead. + +* wxTE_CHARWRAP: For multiline controls only: wrap the lines too long to be shown entirely +at any position (wxUniv, wxGTK, wxOSX). + +* wxTE_WORDWRAP: For multiline controls only: wrap the lines too long to be shown entirely +at word boundaries (wxUniv, wxMSW, wxGTK, wxOSX). + +* wxTE_BESTWRAP: For multiline controls only: wrap the lines at word boundaries or at any +other character if there are words longer than the window width (this is the default). + +* wxTE_CAPITALIZE: On PocketPC and Smartphone, causes the first letter to be capitalized. +Note that alignment styles (wxTE_LEFT, wxTE_CENTRE and wxTE_RIGHT) can be changed +dynamically after control creation on wxMSW, wxGTK and wxOSX. wxTE_READONLY, wxTE_PASSWORD +and wrapping styles can be dynamically changed under wxGTK but not wxMSW. The other styles +can be only set during control creation. + wxTextCtrl Text Format -The multiline text controls always store the text as a sequence of lines -separated by `'\n'` characters, i.e. in the Unix text format even on non-Unix -platforms. This allows the user code to ignore the differences between the -platforms but at a price: the indices in the control such as those returned by -`getInsertionPoint/1` or `getSelection/1` can `not` be used as indices into the -string returned by `getValue/1` as they're going to be slightly off for -platforms using `"\\r\\n"` as separator (as Windows does). - -Instead, if you need to obtain a substring between the 2 indices obtained from -the control with the help of the functions mentioned above, you should use -`getRange/3`. And the indices themselves can only be passed to other methods, -for example `setInsertionPoint/2` or `setSelection/3`. - -To summarize: never use the indices returned by (multiline) `m:wxTextCtrl` as -indices into the string it contains, but only as arguments to be passed back to -the other `m:wxTextCtrl` methods. This problem doesn't arise for single-line -platforms however where the indices in the control do correspond to the -positions in the value string. +The multiline text controls always store the text as a sequence of lines separated by `'\n'` +characters, i.e. in the Unix text format even on non-Unix platforms. This allows the user +code to ignore the differences between the platforms but at a price: the indices in the +control such as those returned by `getInsertionPoint/1` or `getSelection/1` can `not` be used as indices into the string +returned by `getValue/1` as they're going to be slightly off for platforms using `"\\r\\n"` as +separator (as Windows does). + +Instead, if you need to obtain a substring between the 2 indices obtained from the +control with the help of the functions mentioned above, you should use `getRange/3`. And the indices +themselves can only be passed to other methods, for example `setInsertionPoint/2` or `setSelection/3`. + +To summarize: never use the indices returned by (multiline) `m:wxTextCtrl` as indices +into the string it contains, but only as arguments to be passed back to the other `m:wxTextCtrl` +methods. This problem doesn't arise for single-line platforms however where the indices +in the control do correspond to the positions in the value string. wxTextCtrl Positions and Coordinates -It is possible to use either linear positions, i.e. roughly (but `not` always -exactly, as explained in the previous section) the index of the character in the -text contained in the control or X-Y coordinates, i.e. column and line of the -character when working with this class and it provides the functions -`positionToXY/2` and `xYToPosition/3` to convert between the two. - -Additionally, a position in the control can be converted to its coordinates in -pixels using `PositionToCoords()` (not implemented in wx) which can be useful to -e.g. show a popup menu near the given character. And, in the other direction, -`HitTest()` (not implemented in wx) can be used to find the character under, or -near, the given pixel coordinates. - -To be more precise, positions actually refer to the gaps between characters and -not the characters themselves. Thus, position 0 is the one before the very first -character in the control and so is a valid position even when the control is -empty. And if the control contains a single character, it has two valid -positions: 0 before this character and 1 - after it. This, when the -documentation of various functions mentions "invalid position", it doesn't -consider the position just after the last character of the line to be invalid, -only the positions beyond that one (e.g. 2 and greater in the single character -example) are actually invalid. +It is possible to use either linear positions, i.e. roughly (but `not` always exactly, as +explained in the previous section) the index of the character in the text contained in the +control or X-Y coordinates, i.e. column and line of the character when working with this +class and it provides the functions `positionToXY/2` and `xYToPosition/3` to convert between the two. + +Additionally, a position in the control can be converted to its coordinates in pixels +using `PositionToCoords()` (not implemented in wx) which can be useful to e.g. show a +popup menu near the given character. And, in the other direction, `HitTest()` (not +implemented in wx) can be used to find the character under, or near, the given pixel coordinates. + +To be more precise, positions actually refer to the gaps between characters and not the +characters themselves. Thus, position 0 is the one before the very first character in the +control and so is a valid position even when the control is empty. And if the control +contains a single character, it has two valid positions: 0 before this character and 1 - +after it. This, when the documentation of various functions mentions "invalid position", +it doesn't consider the position just after the last character of the line to be invalid, +only the positions beyond that one (e.g. 2 and greater in the single character example) +are actually invalid. wxTextCtrl Styles. -Multi-line text controls support styling, i.e. provide a possibility to set -colours and font for individual characters in it (note that under Windows -`wxTE_RICH` style is required for style support). To use the styles you can -either call `setDefaultStyle/2` before inserting the text or call `setStyle/4` -later to change the style of the text already in the control (the first solution -is much more efficient). +Multi-line text controls support styling, i.e. provide a possibility to set colours and +font for individual characters in it (note that under Windows `wxTE_RICH` style is +required for style support). To use the styles you can either call `setDefaultStyle/2` before inserting the +text or call `setStyle/4` later to change the style of the text already in the control (the first +solution is much more efficient). -In either case, if the style doesn't specify some of the attributes (for example -you only want to set the text colour but without changing the font nor the text -background), the values of the default style will be used for them. If there is -no default style, the attributes of the text control itself are used. +In either case, if the style doesn't specify some of the attributes (for example you only +want to set the text colour but without changing the font nor the text background), the +values of the default style will be used for them. If there is no default style, the +attributes of the text control itself are used. -So the following code correctly describes what it does: the second call to -`setDefaultStyle/2` doesn't change the text foreground colour (which stays red) -while the last one doesn't change the background colour (which stays grey): +So the following code correctly describes what it does: the second call to `setDefaultStyle/2` doesn't +change the text foreground colour (which stays red) while the last one doesn't change the +background colour (which stays grey): wxTextCtrl and C++ Streams -This class multiply-inherits from `std::streambuf` (except for some really old -compilers using non-standard iostream library), allowing code such as the -following: +This class multiply-inherits from `std::streambuf` (except for some really old compilers +using non-standard iostream library), allowing code such as the following: -Note that even if your build of wxWidgets doesn't support this (the symbol -`wxHAS_TEXT_WINDOW_STREAM` has value of 0 then) you can still use `m:wxTextCtrl` -itself in a stream-like manner: +Note that even if your build of wxWidgets doesn't support this (the symbol `wxHAS_TEXT_WINDOW_STREAM` +has value of 0 then) you can still use `m:wxTextCtrl` itself in a stream-like manner: -However the possibility to create a `std::ostream` associated with -`m:wxTextCtrl` may be useful if you need to redirect the output of a function -taking a `std::ostream` as parameter to a text control. +However the possibility to create a `std::ostream` associated with `m:wxTextCtrl` may be +useful if you need to redirect the output of a function taking a `std::ostream` as +parameter to a text control. -Another commonly requested need is to redirect `std::cout` to the text control. -This may be done in the following way: +Another commonly requested need is to redirect `std::cout` to the text control. This may +be done in the following way: -But wxWidgets provides a convenient class to make it even simpler so instead you -may just do +But wxWidgets provides a convenient class to make it even simpler so instead you may just do See `wxStreamToTextRedirector` (not implemented in wx) for more details. Event Handling. -The following commands are processed by default event handlers in -`m:wxTextCtrl`: `wxID_CUT`, `wxID_COPY`, `wxID_PASTE`, `wxID_UNDO`, `wxID_REDO`. -The associated UI update events are also processed automatically, when the -control has the focus. +The following commands are processed by default event handlers in `m:wxTextCtrl`: `wxID_CUT`, `wxID_COPY`, `wxID_PASTE`, `wxID_UNDO`, `wxID_REDO`. +The associated UI update events are also processed automatically, when the control has the focus. -See: `create/4`, `wxValidator` (not implemented in wx) +See: `create/4` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxTextCtrl](https://docs.wxwidgets.org/3.1/classwx_text_ctrl.html) +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxTextCtrl](https://docs.wxwidgets.org/3.2/classwx_text_ctrl.html) ## Events Event types emitted from this class: -[`command_text_updated`](`m:wxCommandEvent`), -[`command_text_enter`](`m:wxCommandEvent`), [`text_maxlen`](`m:wxCommandEvent`) + +* [`command_text_updated`](`m:wxCommandEvent`) + +* [`command_text_enter`](`m:wxCommandEvent`) + +* [`text_maxlen`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([appendText/2,canCopy/1,canCut/1,canPaste/1,canRedo/1,canUndo/1,changeValue/2, @@ -192,21 +249,19 @@ Event types emitted from this class: -type wxTextCtrl() :: wx:wx_object(). -export_type([wxTextCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlwxtextctrl">external documentation</a>. -doc "Default ctor.". -spec new() -> wxTextCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxTextCtrl_new_0), wxe_util:rec(?wxTextCtrl_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxTextCtrl() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -214,17 +269,16 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlwxtextctrl">external documentation</a>. -doc """ Constructor, creating and showing a text control. Remark: The horizontal scrollbar (wxHSCROLL style flag) will only be created for -multi-line text controls. Without a horizontal scrollbar, text lines that don't -fit in the control's size will be wrapped (but no newline character is -inserted). Single line controls don't have a horizontal scrollbar, the text is -automatically scrolled so that the insertion point is always visible. +multi-line text controls. Without a horizontal scrollbar, text lines that don't fit in the +control's size will be wrapped (but no newline character is inserted). Single line +controls don't have a horizontal scrollbar, the text is automatically scrolled so that the +insertion point is always visible. -See: `create/4`, `wxValidator` (not implemented in wx) +See: `create/4` """. -spec new(Parent, Id, [Option]) -> wxTextCtrl() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -246,13 +300,11 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxTextCtrl_new_3), wxe_util:rec(?wxTextCtrl_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlappendtext">external documentation</a>. -doc """ Appends the text to the end of the text control. -Remark: After the text is appended, the insertion point will be at the end of -the text control. If this behaviour is not desired, the programmer should use -`getInsertionPoint/1` and `setInsertionPoint/2`. +Remark: After the text is appended, the insertion point will be at the end of the text +control. If this behaviour is not desired, the programmer should use `getInsertionPoint/1` and `setInsertionPoint/2`. See: `writeText/2` """. @@ -264,7 +316,6 @@ appendText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxTextCtrl_AppendText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcancopy">external documentation</a>. -doc "Returns true if the selection can be copied to the clipboard.". -spec canCopy(This) -> boolean() when This::wxTextCtrl(). @@ -273,7 +324,6 @@ canCopy(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_CanCopy), wxe_util:rec(?wxTextCtrl_CanCopy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcancut">external documentation</a>. -doc "Returns true if the selection can be cut to the clipboard.". -spec canCut(This) -> boolean() when This::wxTextCtrl(). @@ -282,13 +332,11 @@ canCut(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_CanCut), wxe_util:rec(?wxTextCtrl_CanCut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcanpaste">external documentation</a>. -doc """ -Returns true if the contents of the clipboard can be pasted into the text -control. +Returns true if the contents of the clipboard can be pasted into the text control. -On some platforms (Motif, GTK) this is an approximation and returns true if the -control is editable, false otherwise. +On some platforms (Motif, GTK) this is an approximation and returns true if the control +is editable, false otherwise. """. -spec canPaste(This) -> boolean() when This::wxTextCtrl(). @@ -297,11 +345,7 @@ canPaste(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_CanPaste), wxe_util:rec(?wxTextCtrl_CanPaste). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcanredo">external documentation</a>. --doc """ -Returns true if there is a redo facility available and the last operation can be -redone. -""". +-doc "Returns true if there is a redo facility available and the last operation can be redone.". -spec canRedo(This) -> boolean() when This::wxTextCtrl(). canRedo(#wx_ref{type=ThisT}=This) -> @@ -309,11 +353,7 @@ canRedo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_CanRedo), wxe_util:rec(?wxTextCtrl_CanRedo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcanundo">external documentation</a>. --doc """ -Returns true if there is an undo facility available and the last operation can -be undone. -""". +-doc "Returns true if there is an undo facility available and the last operation can be undone.". -spec canUndo(This) -> boolean() when This::wxTextCtrl(). canUndo(#wx_ref{type=ThisT}=This) -> @@ -321,12 +361,11 @@ canUndo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_CanUndo), wxe_util:rec(?wxTextCtrl_CanUndo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlclear">external documentation</a>. -doc """ Clears the text in the control. -Note that this function will generate a `wxEVT_TEXT` event, i.e. its effect is -identical to calling `SetValue`(""). +Note that this function will generate a `wxEVT_TEXT` event, i.e. its effect is identical +to calling `SetValue`(""). """. -spec clear(This) -> 'ok' when This::wxTextCtrl(). @@ -334,7 +373,6 @@ clear(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Clear). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcopy">external documentation</a>. -doc "Copies the selected text to the clipboard.". -spec copy(This) -> 'ok' when This::wxTextCtrl(). @@ -342,7 +380,7 @@ copy(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Copy). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxTextCtrl(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -350,13 +388,11 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcreate">external documentation</a>. -doc """ Creates the text control for two-step construction. This method should be called if the default constructor was used for the control -creation. Its parameters have the same meaning as for the non-default -constructor. +creation. Its parameters have the same meaning as for the non-default constructor. """. -spec create(This, Parent, Id, [Option]) -> boolean() when This::wxTextCtrl(), Parent::wxWindow:wxWindow(), Id::integer(), @@ -379,7 +415,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxTextCtrl_Create), wxe_util:rec(?wxTextCtrl_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlcut">external documentation</a>. -doc "Copies the selected text to the clipboard and removes it from the control.". -spec cut(This) -> 'ok' when This::wxTextCtrl(). @@ -387,7 +422,6 @@ cut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Cut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrldiscardedits">external documentation</a>. -doc "Resets the internal modified flag as if the current changes had been saved.". -spec discardEdits(This) -> 'ok' when This::wxTextCtrl(). @@ -395,18 +429,15 @@ discardEdits(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_DiscardEdits). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlchangevalue">external documentation</a>. -doc """ Sets the new text control value. -It also marks the control as not-modified which means that IsModified() would -return false immediately after the call to `changeValue/2`. +It also marks the control as not-modified which means that IsModified() would return +false immediately after the call to `changeValue/2`. -The insertion point is set to the start of the control (i.e. position 0) by this -function. +The insertion point is set to the start of the control (i.e. position 0) by this function. -This functions does not generate the `wxEVT_TEXT` event but otherwise is -identical to `setValue/2`. +This functions does not generate the `wxEVT_TEXT` event but otherwise is identical to `setValue/2`. See overview_events_prog for more information. @@ -420,14 +451,13 @@ changeValue(#wx_ref{type=ThisT}=This,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Value_UC,?get_env(),?wxTextCtrl_ChangeValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlemulatekeypress">external documentation</a>. -doc """ -This function inserts into the control the character which would have been -inserted if the given key event had occurred in the text control. +This function inserts into the control the character which would have been inserted if +the given key event had occurred in the text control. -The `event` object should be the same as the one passed to `EVT_KEY_DOWN` -handler previously by wxWidgets. Please note that this function doesn't -currently work correctly for all keys under any platform but MSW. +The `event` object should be the same as the one passed to `EVT_KEY_DOWN` handler +previously by wxWidgets. Please note that this function doesn't currently work correctly +for all keys under any platform but MSW. Return: true if the event resulted in a change to the control, false otherwise. """. @@ -439,7 +469,6 @@ emulateKeyPress(#wx_ref{type=ThisT}=This,#wx_ref{type=EventT}=Event) -> wxe_util:queue_cmd(This,Event,?get_env(),?wxTextCtrl_EmulateKeyPress), wxe_util:rec(?wxTextCtrl_EmulateKeyPress). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetdefaultstyle">external documentation</a>. -doc """ Returns the style currently used for the new text. @@ -452,24 +481,21 @@ getDefaultStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetDefaultStyle), wxe_util:rec(?wxTextCtrl_GetDefaultStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetinsertionpoint">external documentation</a>. -doc """ Returns the insertion point, or cursor, position. -This is defined as the zero based index of the character position to the right -of the insertion point. For example, if the insertion point is at the end of the -single-line text control, it is equal to `getLastPosition/1`. +This is defined as the zero based index of the character position to the right of the +insertion point. For example, if the insertion point is at the end of the single-line text +control, it is equal to `getLastPosition/1`. -Notice that insertion position is, in general, different from the index of the -character the cursor position at in the string returned by `getValue/1`. While -this is always the case for the single line controls, multi-line controls can -use two characters `"\\r\\n"` as line separator (this is notably the case under -MSW) meaning that indices in the control and its string value are offset by 1 -for every line. +Notice that insertion position is, in general, different from the index of the character +the cursor position at in the string returned by `getValue/1`. While this is always the case for the +single line controls, multi-line controls can use two characters `"\\r\\n"` as line +separator (this is notably the case under MSW) meaning that indices in the control and its +string value are offset by 1 for every line. -Hence to correctly get the character at the current cursor position, taking into -account that there can be none if the cursor is at the end of the string, you -could do the following: +Hence to correctly get the character at the current cursor position, taking into account +that there can be none if the cursor is at the end of the string, you could do the following: """. -spec getInsertionPoint(This) -> integer() when This::wxTextCtrl(). @@ -478,10 +504,9 @@ getInsertionPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetInsertionPoint), wxe_util:rec(?wxTextCtrl_GetInsertionPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetlastposition">external documentation</a>. -doc """ -Returns the zero based index of the last position in the text control, which is -equal to the number of characters in the control. +Returns the zero based index of the last position in the text control, which is equal to +the number of characters in the control. """. -spec getLastPosition(This) -> integer() when This::wxTextCtrl(). @@ -490,10 +515,8 @@ getLastPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetLastPosition), wxe_util:rec(?wxTextCtrl_GetLastPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetlinelength">external documentation</a>. -doc """ -Gets the length of the specified line, not including any trailing newline -character(s). +Gets the length of the specified line, not including any trailing newline character(s). Return: The length of the line, or -1 if `lineNo` was invalid. """. @@ -505,10 +528,9 @@ getLineLength(#wx_ref{type=ThisT}=This,LineNo) wxe_util:queue_cmd(This,LineNo,?get_env(),?wxTextCtrl_GetLineLength), wxe_util:rec(?wxTextCtrl_GetLineLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetlinetext">external documentation</a>. -doc """ -Returns the contents of a given line in the text control, not including any -trailing newline character(s). +Returns the contents of a given line in the text control, not including any trailing +newline character(s). Return: The contents of the line. """. @@ -520,18 +542,16 @@ getLineText(#wx_ref{type=ThisT}=This,LineNo) wxe_util:queue_cmd(This,LineNo,?get_env(),?wxTextCtrl_GetLineText), wxe_util:rec(?wxTextCtrl_GetLineText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetnumberoflines">external documentation</a>. -doc """ Returns the number of lines in the text control buffer. -The returned number is the number of logical lines, i.e. just the count of the -number of newline characters in the control + 1, for wxGTK and wxOSX/Cocoa ports -while it is the number of physical lines, i.e. the count of lines actually shown -in the control, in wxMSW. Because of this discrepancy, it is not recommended to -use this function. +The returned number is the number of logical lines, i.e. just the count of the number of +newline characters in the control + 1, for wxGTK and wxOSX/Cocoa ports while it is the +number of physical lines, i.e. the count of lines actually shown in the control, in wxMSW. +Because of this discrepancy, it is not recommended to use this function. -Remark: Note that even empty text controls have one line (where the insertion -point is), so `getNumberOfLines/1` never returns 0. +Remark: Note that even empty text controls have one line (where the insertion point is), +so `getNumberOfLines/1` never returns 0. """. -spec getNumberOfLines(This) -> integer() when This::wxTextCtrl(). @@ -540,17 +560,16 @@ getNumberOfLines(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetNumberOfLines), wxe_util:rec(?wxTextCtrl_GetNumberOfLines). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetrange">external documentation</a>. -doc """ -Returns the string containing the text starting in the positions `from` and up -to `to` in the control. - -The positions must have been returned by another `m:wxTextCtrl` method. Please -note that the positions in a multiline `m:wxTextCtrl` do `not` correspond to the -indices in the string returned by `getValue/1` because of the different new line -representations (`CR` or `CR` LF) and so this method should be used to obtain -the correct results instead of extracting parts of the entire value. It may also -be more efficient, especially if the control contains a lot of data. +Returns the string containing the text starting in the positions `from` and up to `to` in +the control. + +The positions must have been returned by another `m:wxTextCtrl` method. Please note that +the positions in a multiline `m:wxTextCtrl` do `not` correspond to the indices in the +string returned by `getValue/1` because of the different new line representations (`CR` or `CR` LF) +and so this method should be used to obtain the correct results instead of extracting +parts of the entire value. It may also be more efficient, especially if the control +contains a lot of data. """. -spec getRange(This, From, To) -> unicode:charlist() when This::wxTextCtrl(), From::integer(), To::integer(). @@ -560,15 +579,13 @@ getRange(#wx_ref{type=ThisT}=This,From,To) wxe_util:queue_cmd(This,From,To,?get_env(),?wxTextCtrl_GetRange), wxe_util:rec(?wxTextCtrl_GetRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetselection">external documentation</a>. -doc """ Gets the current selection span. -If the returned values are equal, there was no selection. Please note that the -indices returned may be used with the other `m:wxTextCtrl` methods but don't -necessarily represent the correct indices into the string returned by -`getValue/1` for multiline controls under Windows (at least,) you should use -`getStringSelection/1` to get the selected text. +If the returned values are equal, there was no selection. Please note that the indices +returned may be used with the other `m:wxTextCtrl` methods but don't necessarily represent +the correct indices into the string returned by `getValue/1` for multiline controls under Windows (at +least,) you should use `getStringSelection/1` to get the selected text. """. -spec getSelection(This) -> {From::integer(), To::integer()} when This::wxTextCtrl(). @@ -577,7 +594,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetSelection), wxe_util:rec(?wxTextCtrl_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetstringselection">external documentation</a>. -doc """ Gets the text currently selected in the control. @@ -590,16 +606,18 @@ getStringSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetStringSelection), wxe_util:rec(?wxTextCtrl_GetStringSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetstyle">external documentation</a>. -doc """ Returns the style at this position in the text control. Not all platforms support this function. -Return: true on success, false if an error occurred (this may also mean that the -styles are not supported under this platform). +Return: true on success, false if an error occurred (this may also mean that the styles +are not supported under this platform). + +See: +* `setStyle/4` -See: `setStyle/4`, `m:wxTextAttr` +* `m:wxTextAttr` """. -spec getStyle(This, Position, Style) -> boolean() when This::wxTextCtrl(), Position::integer(), Style::wxTextAttr:wxTextAttr(). @@ -610,13 +628,12 @@ getStyle(#wx_ref{type=ThisT}=This,Position,#wx_ref{type=StyleT}=Style) wxe_util:queue_cmd(This,Position,Style,?get_env(),?wxTextCtrl_GetStyle), wxe_util:rec(?wxTextCtrl_GetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlgetvalue">external documentation</a>. -doc """ Gets the contents of the control. -Notice that for a multiline text control, the lines will be separated by -(Unix-style) `\n` characters, even under Windows where they are separated by a -`\r\n` sequence in the native control. +Notice that for a multiline text control, the lines will be separated by (Unix-style) `\n` +characters, even under Windows where they are separated by a `\r\n` sequence in the +native control. """. -spec getValue(This) -> unicode:charlist() when This::wxTextCtrl(). @@ -625,13 +642,12 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_GetValue), wxe_util:rec(?wxTextCtrl_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrliseditable">external documentation</a>. -doc """ -Returns true if the controls contents may be edited by user (note that it always -can be changed by the program). +Returns true if the controls contents may be edited by user (note that it always can be +changed by the program). -In other words, this functions returns true if the control hasn't been put in -read-only mode by a previous call to `setEditable/2`. +In other words, this functions returns true if the control hasn't been put in read-only +mode by a previous call to `setEditable/2`. """. -spec isEditable(This) -> boolean() when This::wxTextCtrl(). @@ -640,7 +656,6 @@ isEditable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_IsEditable), wxe_util:rec(?wxTextCtrl_IsEditable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlismodified">external documentation</a>. -doc """ Returns true if the text has been modified by user. @@ -655,7 +670,6 @@ isModified(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_IsModified), wxe_util:rec(?wxTextCtrl_IsModified). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlismultiline">external documentation</a>. -doc """ Returns true if this is a multi line edit control and false otherwise. @@ -668,11 +682,13 @@ isMultiLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_IsMultiLine), wxe_util:rec(?wxTextCtrl_IsMultiLine). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlissingleline">external documentation</a>. -doc """ Returns true if this is a single line edit control and false otherwise. -See: `isSingleLine/1`, `isMultiLine/1` +See: +* `isSingleLine/1` + +* `isMultiLine/1` """. -spec isSingleLine(This) -> boolean() when This::wxTextCtrl(). @@ -681,7 +697,7 @@ isSingleLine(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_IsSingleLine), wxe_util:rec(?wxTextCtrl_IsSingleLine). -%% @equiv loadFile(This,Filename, []) +-doc(#{equiv => loadFile(This,Filename, [])}). -spec loadFile(This, Filename) -> boolean() when This::wxTextCtrl(), Filename::unicode:chardata(). @@ -689,7 +705,6 @@ loadFile(This,Filename) when is_record(This, wx_ref),?is_chardata(Filename) -> loadFile(This,Filename, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlloadfile">external documentation</a>. -doc """ Loads and displays the named file, if it exists. @@ -708,7 +723,6 @@ loadFile(#wx_ref{type=ThisT}=This,Filename, Options) wxe_util:queue_cmd(This,Filename_UC, Opts,?get_env(),?wxTextCtrl_LoadFile), wxe_util:rec(?wxTextCtrl_LoadFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlmarkdirty">external documentation</a>. -doc """ Mark text as modified (dirty). @@ -720,7 +734,6 @@ markDirty(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_MarkDirty). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlpaste">external documentation</a>. -doc "Pastes text from the clipboard to the text item.". -spec paste(This) -> 'ok' when This::wxTextCtrl(). @@ -728,12 +741,10 @@ paste(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Paste). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlpositiontoxy">external documentation</a>. -doc """ Converts given position to a zero-based column, line number pair. -Return: true on success, false on failure (most likely due to a too large -position parameter). +Return: true on success, false on failure (most likely due to a too large position parameter). See: `xYToPosition/3` """. @@ -746,10 +757,9 @@ positionToXY(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxTextCtrl_PositionToXY), wxe_util:rec(?wxTextCtrl_PositionToXY). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlredo">external documentation</a>. -doc """ -If there is a redo facility and the last operation can be redone, redoes the -last operation. +If there is a redo facility and the last operation can be redone, redoes the last +operation. Does nothing if there is no redo facility. """. @@ -759,13 +769,11 @@ redo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Redo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlremove">external documentation</a>. -doc """ -Removes the text starting at the first given position up to (but not including) -the character at the last position. +Removes the text starting at the first given position up to (but not including) the +character at the last position. -This function puts the current insertion point position at `to` as a side -effect. +This function puts the current insertion point position at `to` as a side effect. """. -spec remove(This, From, To) -> 'ok' when This::wxTextCtrl(), From::integer(), To::integer(). @@ -774,13 +782,11 @@ remove(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,From,To,?get_env(),?wxTextCtrl_Remove). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlreplace">external documentation</a>. -doc """ -Replaces the text starting at the first position up to (but not including) the -character at the last position with the given text. +Replaces the text starting at the first position up to (but not including) the character +at the last position with the given text. -This function puts the current insertion point position at `to` as a side -effect. +This function puts the current insertion point position at `to` as a side effect. """. -spec replace(This, From, To, Value) -> 'ok' when This::wxTextCtrl(), From::integer(), To::integer(), Value::unicode:chardata(). @@ -790,7 +796,7 @@ replace(#wx_ref{type=ThisT}=This,From,To,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,From,To,Value_UC,?get_env(),?wxTextCtrl_Replace). -%% @equiv saveFile(This, []) +-doc(#{equiv => saveFile(This, [])}). -spec saveFile(This) -> boolean() when This::wxTextCtrl(). @@ -798,7 +804,6 @@ saveFile(This) when is_record(This, wx_ref) -> saveFile(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsavefile">external documentation</a>. -doc """ Saves the contents of the control in a text file. @@ -818,25 +823,22 @@ saveFile(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxTextCtrl_SaveFile), wxe_util:rec(?wxTextCtrl_SaveFile). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetdefaultstyle">external documentation</a>. -doc """ -Changes the default style to use for the new text which is going to be added to -the control. +Changes the default style to use for the new text which is going to be added to the +control. -This applies both to the text added programmatically using `writeText/2` or -`appendText/2` and to the text entered by the user interactively. +This applies both to the text added programmatically using `writeText/2` or `appendText/2` and to the text entered +by the user interactively. -If either of the font, foreground, or background colour is not set in `style`, -the values of the previous default style are used for them. If the previous -default style didn't set them neither, the global font or colours of the text -control itself are used as fall back. +If either of the font, foreground, or background colour is not set in `style`, the values +of the previous default style are used for them. If the previous default style didn't set +them neither, the global font or colours of the text control itself are used as fall back. -However if the `style` parameter is the default `m:wxTextAttr`, then the default -style is just reset (instead of being combined with the new style which wouldn't -change it at all). +However if the `style` parameter is the default `m:wxTextAttr`, then the default style is +just reset (instead of being combined with the new style which wouldn't change it at all). -Return: true on success, false if an error occurred (this may also mean that the -styles are not supported under this platform). +Return: true on success, false if an error occurred (this may also mean that the styles +are not supported under this platform). See: `getDefaultStyle/1` """. @@ -848,9 +850,8 @@ setDefaultStyle(#wx_ref{type=ThisT}=This,#wx_ref{type=StyleT}=Style) -> wxe_util:queue_cmd(This,Style,?get_env(),?wxTextCtrl_SetDefaultStyle), wxe_util:rec(?wxTextCtrl_SetDefaultStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlseteditable">external documentation</a>. -doc """ -Makes the text item editable or read-only, overriding the `wxTE_READONLY` flag. +Makes the text item editable or read-only, overriding the `wxTE\_READONLY` flag. See: `isEditable/1` """. @@ -861,7 +862,6 @@ setEditable(#wx_ref{type=ThisT}=This,Editable) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,Editable,?get_env(),?wxTextCtrl_SetEditable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetinsertionpoint">external documentation</a>. -doc "Sets the insertion point at the given position.". -spec setInsertionPoint(This, Pos) -> 'ok' when This::wxTextCtrl(), Pos::integer(). @@ -870,12 +870,10 @@ setInsertionPoint(#wx_ref{type=ThisT}=This,Pos) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,Pos,?get_env(),?wxTextCtrl_SetInsertionPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetinsertionpointend">external documentation</a>. -doc """ Sets the insertion point at the end of the text control. -This is equivalent to calling `setInsertionPoint/2` with `getLastPosition/1` -argument. +This is equivalent to calling `setInsertionPoint/2` with `getLastPosition/1` argument. """. -spec setInsertionPointEnd(This) -> 'ok' when This::wxTextCtrl(). @@ -883,24 +881,20 @@ setInsertionPointEnd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_SetInsertionPointEnd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetmaxlength">external documentation</a>. -doc """ -This function sets the maximum number of characters the user can enter into the -control. +This function sets the maximum number of characters the user can enter into the control. -In other words, it allows limiting the text value length to `len` not counting -the terminating `NUL` character. +In other words, it allows limiting the text value length to `len` not counting the +terminating `NUL` character. -If `len` is 0, the previously set max length limit, if any, is discarded and the -user may enter as much text as the underlying native text control widget -supports (typically at least 32Kb). If the user tries to enter more characters -into the text control when it already is filled up to the maximal length, a -`wxEVT_TEXT_MAXLEN` event is sent to notify the program about it (giving it the -possibility to show an explanatory message, for example) and the extra input is -discarded. +If `len` is 0, the previously set max length limit, if any, is discarded and the user may +enter as much text as the underlying native text control widget supports (typically at +least 32Kb). If the user tries to enter more characters into the text control when it +already is filled up to the maximal length, a `wxEVT_TEXT_MAXLEN` event is sent to notify +the program about it (giving it the possibility to show an explanatory message, for +example) and the extra input is discarded. -Note that in wxGTK this function may only be used with single line text -controls. +Note that in wxGTK this function may only be used with single line text controls. """. -spec setMaxLength(This, Len) -> 'ok' when This::wxTextCtrl(), Len::integer(). @@ -909,16 +903,13 @@ setMaxLength(#wx_ref{type=ThisT}=This,Len) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,Len,?get_env(),?wxTextCtrl_SetMaxLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetselection">external documentation</a>. -doc """ -Selects the text starting at the first position up to (but not including) the -character at the last position. +Selects the text starting at the first position up to (but not including) the character +at the last position. If both parameters are equal to -1 all text in the control is selected. Notice that the insertion point will be moved to `from` by this function. - -See: `SelectAll()` (not implemented in wx) """. -spec setSelection(This, From, To) -> 'ok' when This::wxTextCtrl(), From::integer(), To::integer(). @@ -927,17 +918,18 @@ setSelection(#wx_ref{type=ThisT}=This,From,To) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,From,To,?get_env(),?wxTextCtrl_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetstyle">external documentation</a>. -doc """ Changes the style of the given range. -If any attribute within `style` is not set, the corresponding attribute from -`getDefaultStyle/1` is used. +If any attribute within `style` is not set, the corresponding attribute from `getDefaultStyle/1` is used. + +Return: true on success, false if an error occurred (this may also mean that the styles +are not supported under this platform). -Return: true on success, false if an error occurred (this may also mean that the -styles are not supported under this platform). +See: +* `getStyle/3` -See: `getStyle/3`, `m:wxTextAttr` +* `m:wxTextAttr` """. -spec setStyle(This, Start, End, Style) -> boolean() when This::wxTextCtrl(), Start::integer(), End::integer(), Style::wxTextAttr:wxTextAttr(). @@ -948,20 +940,18 @@ setStyle(#wx_ref{type=ThisT}=This,Start,End,#wx_ref{type=StyleT}=Style) wxe_util:queue_cmd(This,Start,End,Style,?get_env(),?wxTextCtrl_SetStyle), wxe_util:rec(?wxTextCtrl_SetStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlsetvalue">external documentation</a>. -doc """ Sets the new text control value. -It also marks the control as not-modified which means that IsModified() would -return false immediately after the call to `setValue/2`. +It also marks the control as not-modified which means that IsModified() would return +false immediately after the call to `setValue/2`. -The insertion point is set to the start of the control (i.e. position 0) by this -function unless the control value doesn't change at all, in which case the -insertion point is left at its original position. +The insertion point is set to the start of the control (i.e. position 0) by this function +unless the control value doesn't change at all, in which case the insertion point is left +at its original position. -Note that, unlike most other functions changing the controls values, this -function generates a `wxEVT_TEXT` event. To avoid this you can use -`changeValue/2` instead. +Note that, unlike most other functions changing the controls values, this function +generates a `wxEVT_TEXT` event. To avoid this you can use `changeValue/2` instead. """. -spec setValue(This, Value) -> 'ok' when This::wxTextCtrl(), Value::unicode:chardata(). @@ -971,7 +961,6 @@ setValue(#wx_ref{type=ThisT}=This,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Value_UC,?get_env(),?wxTextCtrl_SetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlshowposition">external documentation</a>. -doc "Makes the line containing the given position visible.". -spec showPosition(This, Pos) -> 'ok' when This::wxTextCtrl(), Pos::integer(). @@ -980,10 +969,9 @@ showPosition(#wx_ref{type=ThisT}=This,Pos) ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,Pos,?get_env(),?wxTextCtrl_ShowPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlundo">external documentation</a>. -doc """ -If there is an undo facility and the last operation can be undone, undoes the -last operation. +If there is an undo facility and the last operation can be undone, undoes the last +operation. Does nothing if there is no undo facility. """. @@ -993,16 +981,14 @@ undo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTextCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTextCtrl_Undo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlwritetext">external documentation</a>. -doc """ Writes the text into the text control at the current insertion position. -Remark: Newlines in the text string are the only control characters allowed, and -they will cause appropriate line breaks. See operator<<() and `appendText/2` for -more convenient ways of writing to the window. After the write operation, the -insertion point will be at the end of the inserted text, so subsequent write -operations will be appended. To append text after the user may have interacted -with the control, call `setInsertionPointEnd/1` before writing. +Remark: Newlines in the text string are the only control characters allowed, and they +will cause appropriate line breaks. See operator<<() and `appendText/2` for more convenient ways of +writing to the window. After the write operation, the insertion point will be at the end +of the inserted text, so subsequent write operations will be appended. To append text +after the user may have interacted with the control, call `setInsertionPointEnd/1` before writing. """. -spec writeText(This, Text) -> 'ok' when This::wxTextCtrl(), Text::unicode:chardata(). @@ -1012,7 +998,6 @@ writeText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxTextCtrl_WriteText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextctrl.html#wxtextctrlxytoposition">external documentation</a>. -doc """ Converts the given zero based column and line number to a position. @@ -1026,562 +1011,378 @@ xYToPosition(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxTextCtrl_XYToPosition), wxe_util:rec(?wxTextCtrl_XYToPosition). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the text control.". +-doc "Destroys the object". -spec destroy(This::wxTextCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTextCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxTextDataObject.erl b/lib/wx/src/gen/wxTextDataObject.erl index 4d2fddc10bd3..fe88273ce3f5 100644 --- a/lib/wx/src/gen/wxTextDataObject.erl +++ b/lib/wx/src/gen/wxTextDataObject.erl @@ -20,31 +20,34 @@ -module(wxTextDataObject). -moduledoc """ -Functions for wxTextDataObject class +`m:wxTextDataObject` is a specialization of `wxDataObjectSimple` (not implemented in wx) +for text data. -`m:wxTextDataObject` is a specialization of `wxDataObjectSimple` (not -implemented in wx) for text data. It can be used without change to paste data -into the `m:wxClipboard` or a `wxDropSource` (not implemented in wx). A user may -wish to derive a new class from this class for providing text on-demand in order -to minimize memory consumption when offering data in several formats, such as -plain text and RTF because by default the text is stored in a string in this -class, but it might as well be generated when requested. For this, -`getTextLength/1` and `getText/1` will have to be overridden. +It can be used without change to paste data into the `m:wxClipboard` or a `wxDropSource` +(not implemented in wx). A user may wish to derive a new class from this class for +providing text on-demand in order to minimize memory consumption when offering data in +several formats, such as plain text and RTF because by default the text is stored in a +string in this class, but it might as well be generated when requested. For this, `getTextLength/1` and `getText/1` +will have to be overridden. Note that if you already have the text inside a string, you will not achieve any -efficiency gain by overriding these functions because copying wxStrings is -already a very efficient operation (data is not actually copied because -wxStrings are reference counted). +efficiency gain by overriding these functions because copying wxStrings is already a very +efficient operation (data is not actually copied because wxStrings are reference counted). See: -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd), -`m:wxDataObject`, `wxDataObjectSimple` (not implemented in wx), -`m:wxFileDataObject`, `m:wxBitmapDataObject` +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) -This class is derived (and can use functions) from: `m:wxDataObject` +* `m:wxDataObject` -wxWidgets docs: -[wxTextDataObject](https://docs.wxwidgets.org/3.1/classwx_text_data_object.html) +* `m:wxFileDataObject` + +* `m:wxBitmapDataObject` + +This class is derived, and can use functions, from: + +* `m:wxDataObject` + +wxWidgets docs: [wxTextDataObject](https://docs.wxwidgets.org/3.2/classwx_text_data_object.html) """. -include("wxe.hrl"). -export([destroy/1,getText/1,getTextLength/1,new/0,new/1,setText/2]). @@ -54,21 +57,19 @@ wxWidgets docs: -type wxTextDataObject() :: wx:wx_object(). -export_type([wxTextDataObject/0]). -%% @hidden -doc false. parent_class(wxDataObject) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxTextDataObject(). new() -> new([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextdataobject.html#wxtextdataobjectwxtextdataobject">external documentation</a>. -doc """ -Constructor, may be used to initialise the text (otherwise `setText/2` should be -used later). +Constructor, may be used to initialise the text (otherwise `setText/2` should be used +later). """. -spec new([Option]) -> wxTextDataObject() when Option :: {'text', unicode:chardata()}. @@ -80,14 +81,12 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxTextDataObject_new), wxe_util:rec(?wxTextDataObject_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextdataobject.html#wxtextdataobjectgettextlength">external documentation</a>. -doc """ Returns the data size. -By default, returns the size of the text data set in the constructor or using -`setText/2`. This can be overridden to provide text size data on-demand. It is -recommended to return the text length plus 1 for a trailing zero, but this is -not strictly required. +By default, returns the size of the text data set in the constructor or using `setText/2`. This can +be overridden to provide text size data on-demand. It is recommended to return the text +length plus 1 for a trailing zero, but this is not strictly required. """. -spec getTextLength(This) -> integer() when This::wxTextDataObject(). @@ -96,13 +95,11 @@ getTextLength(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextDataObject_GetTextLength), wxe_util:rec(?wxTextDataObject_GetTextLength). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextdataobject.html#wxtextdataobjectgettext">external documentation</a>. -doc """ Returns the text associated with the data object. -You may wish to override this method when offering data on-demand, but this is -not required by wxWidgets' internals. Use this method to get data in text form -from the `m:wxClipboard`. +You may wish to override this method when offering data on-demand, but this is not +required by wxWidgets' internals. Use this method to get data in text form from the `m:wxClipboard`. """. -spec getText(This) -> unicode:charlist() when This::wxTextDataObject(). @@ -111,13 +108,12 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextDataObject_GetText), wxe_util:rec(?wxTextDataObject_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextdataobject.html#wxtextdataobjectsettext">external documentation</a>. -doc """ Sets the text associated with the data object. -This method is called when the data object receives the data and, by default, -copies the text into the member variable. If you want to process the text on the -fly you may wish to override this function. +This method is called when the data object receives the data and, by default, copies the +text into the member variable. If you want to process the text on the fly you may wish to +override this function. """. -spec setText(This, StrText) -> 'ok' when This::wxTextDataObject(), StrText::unicode:chardata(). @@ -127,8 +123,7 @@ setText(#wx_ref{type=ThisT}=This,StrText) StrText_UC = unicode:characters_to_binary(StrText), wxe_util:queue_cmd(This,StrText_UC,?get_env(),?wxTextDataObject_SetText). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxTextDataObject()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTextDataObject), diff --git a/lib/wx/src/gen/wxTextEntryDialog.erl b/lib/wx/src/gen/wxTextEntryDialog.erl index 8fecc809a657..e5d5900c388f 100644 --- a/lib/wx/src/gen/wxTextEntryDialog.erl +++ b/lib/wx/src/gen/wxTextEntryDialog.erl @@ -20,19 +20,23 @@ -module(wxTextEntryDialog). -moduledoc """ -Functions for wxTextEntryDialog class +This class represents a dialog that requests a one-line text string from the user. -This class represents a dialog that requests a one-line text string from the -user. It is implemented as a generic wxWidgets dialog. +It is implemented as a generic wxWidgets dialog. -See: -[Overview cmndlg](https://docs.wxwidgets.org/3.1/overview_cmndlg.html#overview_cmndlg_textentry) +See: [Overview cmndlg](https://docs.wxwidgets.org/3.2/overview_cmndlg.html#overview_cmndlg_textentry) -This class is derived (and can use functions) from: `m:wxDialog` -`m:wxTopLevelWindow` `m:wxWindow` `m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxTextEntryDialog](https://docs.wxwidgets.org/3.1/classwx_text_entry_dialog.html) +* `m:wxDialog` + +* `m:wxTopLevelWindow` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxTextEntryDialog](https://docs.wxwidgets.org/3.2/classwx_text_entry_dialog.html) """. -include("wxe.hrl"). -export([destroy/1,getValue/1,new/0,new/2,new/3,setValue/2]). @@ -84,7 +88,6 @@ wxWidgets docs: -type wxTextEntryDialog() :: wx:wx_object(). -export_type([wxTextEntryDialog/0]). -%% @hidden -doc false. parent_class(wxDialog) -> true; parent_class(wxTopLevelWindow) -> true; @@ -92,7 +95,6 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextentrydialog.html#wxtextentrydialogwxtextentrydialog">external documentation</a>. -doc """ Default constructor. @@ -105,7 +107,7 @@ new() -> wxe_util:queue_cmd(?get_env(), ?wxTextEntryDialog_new_0), wxe_util:rec(?wxTextEntryDialog_new_0). -%% @equiv new(Parent,Message, []) +-doc(#{equiv => new(Parent,Message, [])}). -spec new(Parent, Message) -> wxTextEntryDialog() when Parent::wxWindow:wxWindow(), Message::unicode:chardata(). @@ -113,7 +115,6 @@ new(Parent,Message) when is_record(Parent, wx_ref),?is_chardata(Message) -> new(Parent,Message, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextentrydialog.html#wxtextentrydialogwxtextentrydialog">external documentation</a>. -doc """ Constructor. @@ -140,10 +141,9 @@ new(#wx_ref{type=ParentT}=Parent,Message, Options) wxe_util:queue_cmd(Parent,Message_UC, Opts,?get_env(),?wxTextEntryDialog_new_3), wxe_util:rec(?wxTextEntryDialog_new_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextentrydialog.html#wxtextentrydialoggetvalue">external documentation</a>. -doc """ -Returns the text that the user has entered if the user has pressed OK, or the -original value if the user has pressed Cancel. +Returns the text that the user has entered if the user has pressed OK, or the original +value if the user has pressed Cancel. """. -spec getValue(This) -> unicode:charlist() when This::wxTextEntryDialog(). @@ -152,7 +152,6 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTextEntryDialog_GetValue), wxe_util:rec(?wxTextEntryDialog_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtextentrydialog.html#wxtextentrydialogsetvalue">external documentation</a>. -doc "Sets the default text value.". -spec setValue(This, Value) -> 'ok' when This::wxTextEntryDialog(), Value::unicode:chardata(). @@ -162,659 +161,443 @@ setValue(#wx_ref{type=ThisT}=This,Value) Value_UC = unicode:characters_to_binary(Value), wxe_util:queue_cmd(This,Value_UC,?get_env(),?wxTextEntryDialog_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxTextEntryDialog()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTextEntryDialog), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDialog -%% @hidden -doc false. showModal(This) -> wxDialog:showModal(This). -%% @hidden -doc false. show(This, Options) -> wxDialog:show(This, Options). -%% @hidden -doc false. show(This) -> wxDialog:show(This). -%% @hidden -doc false. setReturnCode(This,RetCode) -> wxDialog:setReturnCode(This,RetCode). -%% @hidden -doc false. setAffirmativeId(This,Id) -> wxDialog:setAffirmativeId(This,Id). -%% @hidden -doc false. isModal(This) -> wxDialog:isModal(This). -%% @hidden -doc false. getReturnCode(This) -> wxDialog:getReturnCode(This). -%% @hidden -doc false. getAffirmativeId(This) -> wxDialog:getAffirmativeId(This). -%% @hidden -doc false. endModal(This,RetCode) -> wxDialog:endModal(This,RetCode). -%% @hidden -doc false. createStdDialogButtonSizer(This,Flags) -> wxDialog:createStdDialogButtonSizer(This,Flags). -%% @hidden -doc false. createButtonSizer(This,Flags) -> wxDialog:createButtonSizer(This,Flags). %% From wxTopLevelWindow -%% @hidden -doc false. showFullScreen(This,Show, Options) -> wxTopLevelWindow:showFullScreen(This,Show, Options). -%% @hidden -doc false. showFullScreen(This,Show) -> wxTopLevelWindow:showFullScreen(This,Show). -%% @hidden -doc false. setTitle(This,Title) -> wxTopLevelWindow:setTitle(This,Title). -%% @hidden -doc false. setShape(This,Region) -> wxTopLevelWindow:setShape(This,Region). -%% @hidden -doc false. centreOnScreen(This, Options) -> wxTopLevelWindow:centreOnScreen(This, Options). -%% @hidden -doc false. centerOnScreen(This, Options) -> wxTopLevelWindow:centerOnScreen(This, Options). -%% @hidden -doc false. centreOnScreen(This) -> wxTopLevelWindow:centreOnScreen(This). -%% @hidden -doc false. centerOnScreen(This) -> wxTopLevelWindow:centerOnScreen(This). -%% @hidden -doc false. setIcons(This,Icons) -> wxTopLevelWindow:setIcons(This,Icons). -%% @hidden -doc false. setIcon(This,Icon) -> wxTopLevelWindow:setIcon(This,Icon). -%% @hidden -doc false. requestUserAttention(This, Options) -> wxTopLevelWindow:requestUserAttention(This, Options). -%% @hidden -doc false. requestUserAttention(This) -> wxTopLevelWindow:requestUserAttention(This). -%% @hidden -doc false. maximize(This, Options) -> wxTopLevelWindow:maximize(This, Options). -%% @hidden -doc false. maximize(This) -> wxTopLevelWindow:maximize(This). -%% @hidden -doc false. isMaximized(This) -> wxTopLevelWindow:isMaximized(This). -%% @hidden -doc false. isIconized(This) -> wxTopLevelWindow:isIconized(This). -%% @hidden -doc false. isFullScreen(This) -> wxTopLevelWindow:isFullScreen(This). -%% @hidden -doc false. iconize(This, Options) -> wxTopLevelWindow:iconize(This, Options). -%% @hidden -doc false. iconize(This) -> wxTopLevelWindow:iconize(This). -%% @hidden -doc false. isActive(This) -> wxTopLevelWindow:isActive(This). -%% @hidden -doc false. getTitle(This) -> wxTopLevelWindow:getTitle(This). -%% @hidden -doc false. getIcons(This) -> wxTopLevelWindow:getIcons(This). -%% @hidden -doc false. getIcon(This) -> wxTopLevelWindow:getIcon(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxToggleButton.erl b/lib/wx/src/gen/wxToggleButton.erl index 4cdd2583c041..395b41a1ba36 100644 --- a/lib/wx/src/gen/wxToggleButton.erl +++ b/lib/wx/src/gen/wxToggleButton.erl @@ -20,29 +20,34 @@ -module(wxToggleButton). -moduledoc """ -Functions for wxToggleButton class +`m:wxToggleButton` is a button that stays pressed when clicked by the user. -`m:wxToggleButton` is a button that stays pressed when clicked by the user. In -other words, it is similar to `m:wxCheckBox` in functionality but looks like a -`m:wxButton`. +In other words, it is similar to `m:wxCheckBox` in functionality but looks like a `m:wxButton`. Since wxWidgets version 2.9.0 this control emits an update UI event. You can see `m:wxToggleButton` in action in page_samples_widgets. -See: `m:wxCheckBox`, `m:wxButton`, `wxBitmapToggleButton` (not implemented in -wx) +See: +* `m:wxCheckBox` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxButton` -wxWidgets docs: -[wxToggleButton](https://docs.wxwidgets.org/3.1/classwx_toggle_button.html) +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxToggleButton](https://docs.wxwidgets.org/3.2/classwx_toggle_button.html) ## Events Event types emitted from this class: -[`command_togglebutton_clicked`](`m:wxCommandEvent`) + +* [`command_togglebutton_clicked`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([create/4,create/5,destroy/1,getValue/1,new/0,new/3,new/4,setValue/2]). @@ -89,21 +94,19 @@ Event types emitted from this class: -type wxToggleButton() :: wx:wx_object(). -export_type([wxToggleButton/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtogglebutton.html#wxtogglebuttonwxtogglebutton">external documentation</a>. -doc "Default constructor.". -spec new() -> wxToggleButton(). new() -> wxe_util:queue_cmd(?get_env(), ?wxToggleButton_new_0), wxe_util:rec(?wxToggleButton_new_0). -%% @equiv new(Parent,Id,Label, []) +-doc(#{equiv => new(Parent,Id,Label, [])}). -spec new(Parent, Id, Label) -> wxToggleButton() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -111,11 +114,10 @@ new(Parent,Id,Label) when is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> new(Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtogglebutton.html#wxtogglebuttonwxtogglebutton">external documentation</a>. -doc """ Constructor, creating and showing a toggle button. -See: `create/5`, `wxValidator` (not implemented in wx) +See: `create/5` """. -spec new(Parent, Id, Label, [Option]) -> wxToggleButton() when Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(), @@ -136,7 +138,7 @@ new(#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(Parent,Id,Label_UC, Opts,?get_env(),?wxToggleButton_new_4), wxe_util:rec(?wxToggleButton_new_4). -%% @equiv create(This,Parent,Id,Label, []) +-doc(#{equiv => create(This,Parent,Id,Label, [])}). -spec create(This, Parent, Id, Label) -> boolean() when This::wxToggleButton(), Parent::wxWindow:wxWindow(), Id::integer(), Label::unicode:chardata(). @@ -144,7 +146,6 @@ create(This,Parent,Id,Label) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id),?is_chardata(Label) -> create(This,Parent,Id,Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtogglebutton.html#wxtogglebuttoncreate">external documentation</a>. -doc """ Creates the toggle button for two-step construction. @@ -170,7 +171,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id,Label, Options) wxe_util:queue_cmd(This,Parent,Id,Label_UC, Opts,?get_env(),?wxToggleButton_Create), wxe_util:rec(?wxToggleButton_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtogglebutton.html#wxtogglebuttongetvalue">external documentation</a>. -doc """ Gets the state of the toggle button. @@ -183,7 +183,6 @@ getValue(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToggleButton_GetValue), wxe_util:rec(?wxToggleButton_GetValue). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtogglebutton.html#wxtogglebuttonsetvalue">external documentation</a>. -doc """ Sets the toggle button to the given state. @@ -196,562 +195,378 @@ setValue(#wx_ref{type=ThisT}=This,State) ?CLASS(ThisT,wxToggleButton), wxe_util:queue_cmd(This,State,?get_env(),?wxToggleButton_SetValue). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the toggle button.". +-doc "Destroys the object". -spec destroy(This::wxToggleButton()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxToggleButton), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxToolBar.erl b/lib/wx/src/gen/wxToolBar.erl index 420a18abb4ee..790b3e40a557 100644 --- a/lib/wx/src/gen/wxToolBar.erl +++ b/lib/wx/src/gen/wxToolBar.erl @@ -20,59 +20,94 @@ -module(wxToolBar). -moduledoc """ -Functions for wxToolBar class - -A toolbar is a bar of buttons and/or other controls usually placed below the -menu bar in a `m:wxFrame`. - -You may create a toolbar that is managed by a frame calling -`wxFrame:createToolBar/2`. Under Pocket PC, you should always use this function -for creating the toolbar to be managed by the frame, so that wxWidgets can use a -combined menubar and toolbar. Where you manage your own toolbars, create -`m:wxToolBar` as usual. - -There are several different types of tools you can add to a toolbar. These types -are controlled by the ?wxItemKind enumeration. - -Note that many methods in `m:wxToolBar` such as `addTool/6` return a -`wxToolBarToolBase*` object. This should be regarded as an opaque handle -representing the newly added toolbar item, providing access to its id and -position within the toolbar. Changes to the item's state should be made through -calls to `m:wxToolBar` methods, for example `enableTool/3`. Calls to -`wxToolBarToolBase` (not implemented in wx) methods (undocumented by purpose) -will not change the visible state of the item within the tool bar. - -After you have added all the tools you need, you must call `realize/1` to -effectively construct and display the toolbar. - -`wxMSW note`: Note that under wxMSW toolbar paints tools to reflect system-wide -colours. If you use more than 16 colours in your tool bitmaps, you may wish to -suppress this behaviour, otherwise system colours in your bitmaps will -inadvertently be mapped to system colours. To do this, set the msw.remap system -option before creating the toolbar: If you wish to use 32-bit images (which -include an alpha channel for transparency) use: Then colour remapping is -switched off, and a transparent background used. But only use this option under -Windows XP with true colour: - -Styles +A toolbar is a bar of buttons and/or other controls usually placed below the menu bar in +a `m:wxFrame`. + +You may create a toolbar that is managed by a frame calling `wxFrame:createToolBar/2`. Under Pocket PC, you should +always use this function for creating the toolbar to be managed by the frame, so that +wxWidgets can use a combined menubar and toolbar. Where you manage your own toolbars, +create `m:wxToolBar` as usual. + +There are several different types of tools you can add to a toolbar. These types are +controlled by the ?wxItemKind enumeration. + +Note that many methods in `m:wxToolBar` such as `addTool/6` return a `wxToolBarToolBase*` object. +This should be regarded as an opaque handle representing the newly added toolbar item, +providing access to its id and position within the toolbar. Changes to the item's state +should be made through calls to `m:wxToolBar` methods, for example `enableTool/3`. Calls to `wxToolBarToolBase` +(not implemented in wx) methods (undocumented by purpose) will not change the visible +state of the item within the tool bar. + +After you have added all the tools you need, you must call `realize/1` to effectively construct and +display the toolbar. + +`wxMSW note`: Note that under wxMSW toolbar paints tools to reflect system-wide colours. +If you use more than 16 colours in your tool bitmaps, you may wish to suppress this +behaviour, otherwise system colours in your bitmaps will inadvertently be mapped to system +colours. To do this, set the msw.remap system option before creating the toolbar: If you +wish to use 32-bit images (which include an alpha channel for transparency) use: Then +colour remapping is switched off, and a transparent background used. But only use this +option under Windows XP with true colour: + +## Styles This class supports the following styles: -See: -[Overview toolbar](https://docs.wxwidgets.org/3.1/overview_toolbar.html#overview_toolbar) +* wxTB_FLAT: Gives the toolbar a flat look (Windows and GTK only). + +* wxTB_DOCKABLE: Makes the toolbar floatable and dockable (GTK only). + +* wxTB_HORIZONTAL: Specifies horizontal layout (default). + +* wxTB_VERTICAL: Specifies vertical layout. + +* wxTB_TEXT: Shows the text in the toolbar buttons; by default only icons are shown. + +* wxTB_NOICONS: Specifies no icons in the toolbar buttons; by default they are shown. + +* wxTB_NODIVIDER: Specifies no divider (border) above the toolbar (Windows only) + +* wxTB_NOALIGN: Specifies no alignment with the parent window (Windows only, not very +useful). + +* wxTB_HORZ_LAYOUT: Shows the text and the icons alongside, not vertically stacked (Windows +and GTK 2 only). This style must be used with `wxTB_TEXT`. + +* wxTB_HORZ_TEXT: Combination of `wxTB_HORZ_LAYOUT` and `wxTB_TEXT`. + +* wxTB_NO_TOOLTIPS: Don't show the short help tooltips for the tools when the mouse hovers +over them. + +* wxTB_BOTTOM: Align the toolbar at the bottom of parent window. + +* wxTB_RIGHT: Align the toolbar at the right side of parent window. + +* wxTB_DEFAULT_STYLE: Combination of `wxTB_HORIZONTAL` and `wxTB_FLAT`. This style is new +since wxWidgets 2.9.5. See also overview_windowstyles. Note that the wxMSW native toolbar +ignores `wxTB_NOICONS` style. Also, toggling the `wxTB_TEXT` works only if the style was +initially on. -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +See: [Overview toolbar](https://docs.wxwidgets.org/3.2/overview_toolbar.html#overview_toolbar) -wxWidgets docs: -[wxToolBar](https://docs.wxwidgets.org/3.1/classwx_tool_bar.html) +This class is derived, and can use functions, from: + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxToolBar](https://docs.wxwidgets.org/3.2/classwx_tool_bar.html) ## Events Event types emitted from this class: -[`command_tool_rclicked`](`m:wxCommandEvent`), -[`command_tool_enter`](`m:wxCommandEvent`), -[`tool_dropdown`](`m:wxCommandEvent`) + +* [`command_tool_rclicked`](`m:wxCommandEvent`) + +* [`command_tool_enter`](`m:wxCommandEvent`) + +* [`tool_dropdown`](`m:wxCommandEvent`) """. -include("wxe.hrl"). -export([addCheckTool/4,addCheckTool/5,addControl/2,addControl/3,addRadioTool/4, @@ -128,14 +163,13 @@ Event types emitted from this class: -type wxToolBar() :: wx:wx_object(). -export_type([wxToolBar/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv addControl(This,Control, []) +-doc(#{equiv => addControl(This,Control, [])}). -spec addControl(This, Control) -> wx:wx_object() when This::wxToolBar(), Control::wxControl:wxControl(). @@ -143,12 +177,11 @@ addControl(This,Control) when is_record(This, wx_ref),is_record(Control, wx_ref) -> addControl(This,Control, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddcontrol">external documentation</a>. -doc """ Adds any control to the toolbar, typically e.g. a `m:wxComboBox`. -Remark: wxMac: labels are only displayed if wxWidgets is built with -`wxMAC_USE_NATIVE_TOOLBAR` set to 1 +Remark: wxMac: labels are only displayed if wxWidgets is built with `wxMAC_USE_NATIVE_TOOLBAR` +set to 1 """. -spec addControl(This, Control, [Option]) -> wx:wx_object() when This::wxToolBar(), Control::wxControl:wxControl(), @@ -163,15 +196,18 @@ addControl(#wx_ref{type=ThisT}=This,#wx_ref{type=ControlT}=Control, Options) wxe_util:queue_cmd(This,Control, Opts,?get_env(),?wxToolBar_AddControl), wxe_util:rec(?wxToolBar_AddControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddseparator">external documentation</a>. -doc """ Adds a separator for spacing groups of tools. -Notice that the separator uses the look appropriate for the current platform so -it can be a vertical line (MSW, some versions of GTK) or just an empty space or -something else. +Notice that the separator uses the look appropriate for the current platform so it can be +a vertical line (MSW, some versions of GTK) or just an empty space or something else. + +See: +* `addTool/6` + +* `setToolSeparation/2` -See: `addTool/6`, `setToolSeparation/2`, `addStretchableSpace/1` +* `addStretchableSpace/1` """. -spec addSeparator(This) -> wx:wx_object() when This::wxToolBar(). @@ -180,15 +216,24 @@ addSeparator(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_AddSeparator), wxe_util:rec(?wxToolBar_AddSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddtool">external documentation</a>. -doc """ Adds a tool to the toolbar. -Remark: After you have added tools to a toolbar, you must call `realize/1` in -order to have the tools appear. +Remark: After you have added tools to a toolbar, you must call `realize/1` in order to have the +tools appear. -See: `addSeparator/1`, `addCheckTool/5`, `addRadioTool/5`, `insertTool/6`, -`deleteTool/2`, `realize/1`, `SetDropdownMenu()` (not implemented in wx) +See: +* `addSeparator/1` + +* `addCheckTool/5` + +* `addRadioTool/5` + +* `insertTool/6` + +* `deleteTool/2` + +* `realize/1` """. -spec addTool(This, Tool) -> wx:wx_object() when This::wxToolBar(), Tool::wx:wx_object(). @@ -198,7 +243,7 @@ addTool(#wx_ref{type=ThisT}=This,#wx_ref{type=ToolT}=Tool) -> wxe_util:queue_cmd(This,Tool,?get_env(),?wxToolBar_AddTool_1), wxe_util:rec(?wxToolBar_AddTool_1). -%% @equiv addTool(This,ToolId,Label,Bitmap, []) +-doc(#{equiv => addTool(This,ToolId,Label,Bitmap, [])}). -spec addTool(This, ToolId, Label, Bitmap) -> wx:wx_object() when This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(). @@ -206,26 +251,29 @@ addTool(This,ToolId,Label,Bitmap) when is_record(This, wx_ref),is_integer(ToolId),?is_chardata(Label),is_record(Bitmap, wx_ref) -> addTool(This,ToolId,Label,Bitmap, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddtool">external documentation</a>. -%% <br /> Also:<br /> -%% addTool(This, ToolId, Label, Bitmap, [Option]) -> wx:wx_object() when<br /> -%% This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(),<br /> -%% Option :: {'shortHelp', unicode:chardata()}<br /> -%% | {'kind', wx:wx_enum()}.<br /> -%% -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Adds a tool to the toolbar. -This most commonly used version has fewer parameters than the full version below -which specifies the more rarely used button features. +This most commonly used version has fewer parameters than the full version below which +specifies the more rarely used button features. + +Remark: After you have added tools to a toolbar, you must call `realize/1` in order to have the +tools appear. + +See: +* `addSeparator/1` + +* `addCheckTool/5` -Remark: After you have added tools to a toolbar, you must call `realize/1` in -order to have the tools appear. +* `addRadioTool/5` -See: `addSeparator/1`, `addCheckTool/5`, `addRadioTool/5`, `insertTool/6`, -`deleteTool/2`, `realize/1`, `SetDropdownMenu()` (not implemented in wx) +* `insertTool/6` + +* `deleteTool/2` + +* `realize/1` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec addTool(This, ToolId, Label, Bitmap, BmpDisabled) -> wx:wx_object() when This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(), BmpDisabled::wxBitmap:wxBitmap(); (This, ToolId, Label, Bitmap, [Option]) -> wx:wx_object() when @@ -248,17 +296,26 @@ addTool(#wx_ref{type=ThisT}=This,ToolId,Label,#wx_ref{type=BitmapT}=Bitmap, Opti wxe_util:queue_cmd(This,ToolId,Label_UC,Bitmap, Opts,?get_env(),?wxToolBar_AddTool_4), wxe_util:rec(?wxToolBar_AddTool_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddtool">external documentation</a>. -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ Adds a tool to the toolbar. -Remark: After you have added tools to a toolbar, you must call `realize/1` in -order to have the tools appear. +Remark: After you have added tools to a toolbar, you must call `realize/1` in order to have the +tools appear. + +See: +* `addSeparator/1` + +* `addCheckTool/5` -See: `addSeparator/1`, `addCheckTool/5`, `addRadioTool/5`, `insertTool/6`, -`deleteTool/2`, `realize/1`, `SetDropdownMenu()` (not implemented in wx) +* `addRadioTool/5` + +* `insertTool/6` + +* `deleteTool/2` + +* `realize/1` """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec addTool(This, ToolId, Label, Bitmap, BmpDisabled, [Option]) -> wx:wx_object() when This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(), BmpDisabled::wxBitmap:wxBitmap(), Option :: {'kind', wx:wx_enum()} @@ -280,7 +337,7 @@ addTool(#wx_ref{type=ThisT}=This,ToolId,Label,#wx_ref{type=BitmapT}=Bitmap,#wx_r wxe_util:queue_cmd(This,ToolId,Label_UC,Bitmap,BmpDisabled, Opts,?get_env(),?wxToolBar_AddTool_5), wxe_util:rec(?wxToolBar_AddTool_5). -%% @equiv addCheckTool(This,ToolId,Label,Bitmap1, []) +-doc(#{equiv => addCheckTool(This,ToolId,Label,Bitmap1, [])}). -spec addCheckTool(This, ToolId, Label, Bitmap1) -> wx:wx_object() when This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap1::wxBitmap:wxBitmap(). @@ -288,7 +345,6 @@ addCheckTool(This,ToolId,Label,Bitmap1) when is_record(This, wx_ref),is_integer(ToolId),?is_chardata(Label),is_record(Bitmap1, wx_ref) -> addCheckTool(This,ToolId,Label,Bitmap1, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddchecktool">external documentation</a>. -doc """ Adds a new check (or toggle) tool to the toolbar. @@ -316,7 +372,7 @@ addCheckTool(#wx_ref{type=ThisT}=This,ToolId,Label,#wx_ref{type=Bitmap1T}=Bitmap wxe_util:queue_cmd(This,ToolId,Label_UC,Bitmap1, Opts,?get_env(),?wxToolBar_AddCheckTool), wxe_util:rec(?wxToolBar_AddCheckTool). -%% @equiv addRadioTool(This,ToolId,Label,Bitmap1, []) +-doc(#{equiv => addRadioTool(This,ToolId,Label,Bitmap1, [])}). -spec addRadioTool(This, ToolId, Label, Bitmap1) -> wx:wx_object() when This::wxToolBar(), ToolId::integer(), Label::unicode:chardata(), Bitmap1::wxBitmap:wxBitmap(). @@ -324,18 +380,15 @@ addRadioTool(This,ToolId,Label,Bitmap1) when is_record(This, wx_ref),is_integer(ToolId),?is_chardata(Label),is_record(Bitmap1, wx_ref) -> addRadioTool(This,ToolId,Label,Bitmap1, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddradiotool">external documentation</a>. -doc """ Adds a new radio tool to the toolbar. -Consecutive radio tools form a radio group such that exactly one button in the -group is pressed at any moment, in other words whenever a button in the group is -pressed the previously pressed button is automatically released. You should -avoid having the radio groups of only one element as it would be impossible for -the user to use such button. +Consecutive radio tools form a radio group such that exactly one button in the group is +pressed at any moment, in other words whenever a button in the group is pressed the +previously pressed button is automatically released. You should avoid having the radio +groups of only one element as it would be impossible for the user to use such button. -By default, the first button in the radio group is initially pressed, the others -are not. +By default, the first button in the radio group is initially pressed, the others are not. See: `addTool/6` """. @@ -359,18 +412,22 @@ addRadioTool(#wx_ref{type=ThisT}=This,ToolId,Label,#wx_ref{type=Bitmap1T}=Bitmap wxe_util:queue_cmd(This,ToolId,Label_UC,Bitmap1, Opts,?get_env(),?wxToolBar_AddRadioTool), wxe_util:rec(?wxToolBar_AddRadioTool). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbaraddstretchablespace">external documentation</a>. -doc """ Adds a stretchable space to the toolbar. -Any space not taken up by the fixed items (all items except for stretchable -spaces) is distributed in equal measure between the stretchable spaces in the -toolbar. The most common use for this method is to add a single stretchable -space before the items which should be right-aligned in the toolbar, but more -exotic possibilities are possible, e.g. a stretchable space may be added in the -beginning and the end of the toolbar to centre all toolbar items. +Any space not taken up by the fixed items (all items except for stretchable spaces) is +distributed in equal measure between the stretchable spaces in the toolbar. The most +common use for this method is to add a single stretchable space before the items which +should be right-aligned in the toolbar, but more exotic possibilities are possible, e.g. a +stretchable space may be added in the beginning and the end of the toolbar to centre all +toolbar items. + +See: +* `addTool/6` + +* `addSeparator/1` -See: `addTool/6`, `addSeparator/1`, `insertStretchableSpace/2` +* `insertStretchableSpace/2` Since: 2.9.1 """. @@ -381,13 +438,15 @@ addStretchableSpace(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_AddStretchableSpace), wxe_util:rec(?wxToolBar_AddStretchableSpace). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarinsertstretchablespace">external documentation</a>. -doc """ Inserts a stretchable space at the given position. See `addStretchableSpace/1` for details about stretchable spaces. -See: `insertTool/6`, `insertSeparator/2` +See: +* `insertTool/6` + +* `insertSeparator/2` Since: 2.9.1 """. @@ -399,15 +458,13 @@ insertStretchableSpace(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxToolBar_InsertStretchableSpace), wxe_util:rec(?wxToolBar_InsertStretchableSpace). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbardeletetool">external documentation</a>. -doc """ Removes the specified tool from the toolbar and deletes it. -If you don't want to delete the tool, but just to remove it from the toolbar (to -possibly add it back later), you may use `removeTool/2` instead. +If you don't want to delete the tool, but just to remove it from the toolbar (to possibly +add it back later), you may use `removeTool/2` instead. -Note: It is unnecessary to call `realize/1` for the change to take place, it -will happen immediately. +Note: It is unnecessary to call `realize/1` for the change to take place, it will happen immediately. Return: true if the tool was deleted, false otherwise. @@ -421,10 +478,9 @@ deleteTool(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_DeleteTool), wxe_util:rec(?wxToolBar_DeleteTool). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbardeletetoolbypos">external documentation</a>. -doc """ -This function behaves like `deleteTool/2` but it deletes the tool at the -specified position and not the one with the given id. +This function behaves like `deleteTool/2` but it deletes the tool at the specified +position and not the one with the given id. """. -spec deleteToolByPos(This, Pos) -> boolean() when This::wxToolBar(), Pos::integer(). @@ -434,14 +490,16 @@ deleteToolByPos(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxToolBar_DeleteToolByPos), wxe_util:rec(?wxToolBar_DeleteToolByPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarenabletool">external documentation</a>. -doc """ Enables or disables the tool. -Remark: Some implementations will change the visible state of the tool to -indicate that it is disabled. +Remark: Some implementations will change the visible state of the tool to indicate that +it is disabled. + +See: +* `getToolEnabled/2` -See: `getToolEnabled/2`, `toggleTool/3` +* `toggleTool/3` """. -spec enableTool(This, ToolId, Enable) -> 'ok' when This::wxToolBar(), ToolId::integer(), Enable::boolean(). @@ -450,10 +508,9 @@ enableTool(#wx_ref{type=ThisT}=This,ToolId,Enable) ?CLASS(ThisT,wxToolBar), wxe_util:queue_cmd(This,ToolId,Enable,?get_env(),?wxToolBar_EnableTool). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarfindbyid">external documentation</a>. -doc """ -Returns a pointer to the tool identified by `id` or NULL if no corresponding -tool is found. +Returns a pointer to the tool identified by `id` or NULL if no corresponding tool is +found. """. -spec findById(This, Id) -> wx:wx_object() when This::wxToolBar(), Id::integer(). @@ -463,10 +520,9 @@ findById(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxToolBar_FindById), wxe_util:rec(?wxToolBar_FindById). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarfindcontrol">external documentation</a>. -doc """ -Returns a pointer to the control identified by `id` or NULL if no corresponding -control is found. +Returns a pointer to the control identified by `id` or NULL if no corresponding control +is found. """. -spec findControl(This, Id) -> wxControl:wxControl() when This::wxToolBar(), Id::integer(). @@ -476,7 +532,6 @@ findControl(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxToolBar_FindControl), wxe_util:rec(?wxToolBar_FindControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarfindtoolforposition">external documentation</a>. -doc """ Finds a tool for the given mouse position. @@ -492,12 +547,14 @@ findToolForPosition(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxToolBar_FindToolForPosition), wxe_util:rec(?wxToolBar_FindToolForPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolsize">external documentation</a>. -doc """ -Returns the size of a whole button, which is usually larger than a tool bitmap -because of added 3D effects. +Returns the size of a whole button, which is usually larger than a tool bitmap because of +added 3D effects. + +See: +* `setToolBitmapSize/2` -See: `setToolBitmapSize/2`, `getToolBitmapSize/1` +* `getToolBitmapSize/1` """. -spec getToolSize(This) -> {W::integer(), H::integer()} when This::wxToolBar(). @@ -506,22 +563,22 @@ getToolSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_GetToolSize), wxe_util:rec(?wxToolBar_GetToolSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolbitmapsize">external documentation</a>. -doc """ Returns the size of bitmap that the toolbar expects to have. -The default bitmap size is platform-dependent: for example, it is 16*15 for MSW -and 24*24 for GTK. This size does `not` necessarily indicate the best size to -use for the toolbars on the given platform, for this you should use -`wxArtProvider::GetNativeSizeHint(wxART_TOOLBAR)` but in any case, as the bitmap -size is deduced automatically from the size of the bitmaps associated with the -tools added to the toolbar, it is usually unnecessary to call -`setToolBitmapSize/2` explicitly. +The default bitmap size is platform-dependent: for example, it is 16*15 for MSW and 24*24 +for GTK. This size does `not` necessarily indicate the best size to use for the toolbars +on the given platform, for this you should use `wxArtProvider::GetNativeSizeHint(wxART_TOOLBAR)` +but in any case, as the bitmap size is deduced automatically from the size of the bitmaps +associated with the tools added to the toolbar, it is usually unnecessary to call `setToolBitmapSize/2` explicitly. -Remark: Note that this is the size of the bitmap you pass to `addTool/6`, and -not the eventual size of the tool button. +Remark: Note that this is the size of the bitmap you pass to `addTool/6`, and not the eventual size +of the tool button. + +See: +* `setToolBitmapSize/2` -See: `setToolBitmapSize/2`, `getToolSize/1` +* `getToolSize/1` """. -spec getToolBitmapSize(This) -> {W::integer(), H::integer()} when This::wxToolBar(). @@ -530,10 +587,8 @@ getToolBitmapSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_GetToolBitmapSize), wxe_util:rec(?wxToolBar_GetToolBitmapSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargetmargins">external documentation</a>. -doc """ -Returns the left/right and top/bottom margins, which are also used for -inter-toolspacing. +Returns the left/right and top/bottom margins, which are also used for inter-toolspacing. See: `setMargins/3` """. @@ -544,7 +599,6 @@ getMargins(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_GetMargins), wxe_util:rec(?wxToolBar_GetMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolenabled">external documentation</a>. -doc """ Called to determine whether a tool is enabled (responds to user input). @@ -560,11 +614,13 @@ getToolEnabled(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_GetToolEnabled), wxe_util:rec(?wxToolBar_GetToolEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoollonghelp">external documentation</a>. -doc """ Returns the long help for the given tool. -See: `setToolLongHelp/3`, `setToolShortHelp/3` +See: +* `setToolLongHelp/3` + +* `setToolShortHelp/3` """. -spec getToolLongHelp(This, ToolId) -> unicode:charlist() when This::wxToolBar(), ToolId::integer(). @@ -574,7 +630,6 @@ getToolLongHelp(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_GetToolLongHelp), wxe_util:rec(?wxToolBar_GetToolLongHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolpacking">external documentation</a>. -doc """ Returns the value used for packing tools. @@ -587,11 +642,7 @@ getToolPacking(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_GetToolPacking), wxe_util:rec(?wxToolBar_GetToolPacking). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolpos">external documentation</a>. --doc """ -Returns the tool position in the toolbar, or `wxNOT_FOUND` if the tool is not -found. -""". +-doc "Returns the tool position in the toolbar, or `wxNOT\_FOUND` if the tool is not found.". -spec getToolPos(This, ToolId) -> integer() when This::wxToolBar(), ToolId::integer(). getToolPos(#wx_ref{type=ThisT}=This,ToolId) @@ -600,7 +651,6 @@ getToolPos(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_GetToolPos), wxe_util:rec(?wxToolBar_GetToolPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolseparation">external documentation</a>. -doc """ Returns the default separator size. @@ -613,11 +663,13 @@ getToolSeparation(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_GetToolSeparation), wxe_util:rec(?wxToolBar_GetToolSeparation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolshorthelp">external documentation</a>. -doc """ Returns the short help for the given tool. -See: `getToolLongHelp/2`, `setToolShortHelp/3` +See: +* `getToolLongHelp/2` + +* `setToolShortHelp/3` """. -spec getToolShortHelp(This, ToolId) -> unicode:charlist() when This::wxToolBar(), ToolId::integer(). @@ -627,7 +679,6 @@ getToolShortHelp(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_GetToolShortHelp), wxe_util:rec(?wxToolBar_GetToolShortHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbargettoolstate">external documentation</a>. -doc """ Gets the on/off state of a toggle tool. @@ -643,7 +694,7 @@ getToolState(#wx_ref{type=ThisT}=This,ToolId) wxe_util:queue_cmd(This,ToolId,?get_env(),?wxToolBar_GetToolState), wxe_util:rec(?wxToolBar_GetToolState). -%% @equiv insertControl(This,Pos,Control, []) +-doc(#{equiv => insertControl(This,Pos,Control, [])}). -spec insertControl(This, Pos, Control) -> wx:wx_object() when This::wxToolBar(), Pos::integer(), Control::wxControl:wxControl(). @@ -651,13 +702,15 @@ insertControl(This,Pos,Control) when is_record(This, wx_ref),is_integer(Pos),is_record(Control, wx_ref) -> insertControl(This,Pos,Control, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarinsertcontrol">external documentation</a>. -doc """ Inserts the control into the toolbar at the given position. You must call `realize/1` for the change to take place. -See: `addControl/3`, `insertTool/6` +See: +* `addControl/3` + +* `insertTool/6` """. -spec insertControl(This, Pos, Control, [Option]) -> wx:wx_object() when This::wxToolBar(), Pos::integer(), Control::wxControl:wxControl(), @@ -672,13 +725,15 @@ insertControl(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=ControlT}=Control, Optio wxe_util:queue_cmd(This,Pos,Control, Opts,?get_env(),?wxToolBar_InsertControl), wxe_util:rec(?wxToolBar_InsertControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarinsertseparator">external documentation</a>. -doc """ Inserts the separator into the toolbar at the given position. You must call `realize/1` for the change to take place. -See: `addSeparator/1`, `insertTool/6` +See: +* `addSeparator/1` + +* `insertTool/6` """. -spec insertSeparator(This, Pos) -> wx:wx_object() when This::wxToolBar(), Pos::integer(). @@ -688,7 +743,7 @@ insertSeparator(#wx_ref{type=ThisT}=This,Pos) wxe_util:queue_cmd(This,Pos,?get_env(),?wxToolBar_InsertSeparator), wxe_util:rec(?wxToolBar_InsertSeparator). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarinserttool">external documentation</a>. +-doc "". -spec insertTool(This, Pos, Tool) -> wx:wx_object() when This::wxToolBar(), Pos::integer(), Tool::wx:wx_object(). insertTool(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=ToolT}=Tool) @@ -698,7 +753,7 @@ insertTool(#wx_ref{type=ThisT}=This,Pos,#wx_ref{type=ToolT}=Tool) wxe_util:queue_cmd(This,Pos,Tool,?get_env(),?wxToolBar_InsertTool_2), wxe_util:rec(?wxToolBar_InsertTool_2). -%% @equiv insertTool(This,Pos,ToolId,Label,Bitmap, []) +-doc(#{equiv => insertTool(This,Pos,ToolId,Label,Bitmap, [])}). -spec insertTool(This, Pos, ToolId, Label, Bitmap) -> wx:wx_object() when This::wxToolBar(), Pos::integer(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(). @@ -706,20 +761,22 @@ insertTool(This,Pos,ToolId,Label,Bitmap) when is_record(This, wx_ref),is_integer(Pos),is_integer(ToolId),?is_chardata(Label),is_record(Bitmap, wx_ref) -> insertTool(This,Pos,ToolId,Label,Bitmap, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarinserttool">external documentation</a>. -%%<br /> Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -doc """ -Inserts the tool with the specified attributes into the toolbar at the given -position. +Inserts the tool with the specified attributes into the toolbar at the given position. You must call `realize/1` for the change to take place. -See: `addTool/6`, `insertControl/4`, `insertSeparator/2` +See: +* `addTool/6` + +* `insertControl/4` -Return: The newly inserted tool or NULL on failure. Notice that with the -overload taking `tool` parameter the caller is responsible for deleting the tool -in the latter case. +* `insertSeparator/2` + +Return: The newly inserted tool or NULL on failure. Notice that with the overload taking `tool` +parameter the caller is responsible for deleting the tool in the latter case. """. +%% Kind = ?wxITEM_SEPARATOR | ?wxITEM_NORMAL | ?wxITEM_CHECK | ?wxITEM_RADIO | ?wxITEM_DROPDOWN | ?wxITEM_MAX -spec insertTool(This, Pos, ToolId, Label, Bitmap, [Option]) -> wx:wx_object() when This::wxToolBar(), Pos::integer(), ToolId::integer(), Label::unicode:chardata(), Bitmap::wxBitmap:wxBitmap(), Option :: {'bmpDisabled', wxBitmap:wxBitmap()} @@ -742,7 +799,6 @@ insertTool(#wx_ref{type=ThisT}=This,Pos,ToolId,Label,#wx_ref{type=BitmapT}=Bitma wxe_util:queue_cmd(This,Pos,ToolId,Label_UC,Bitmap, Opts,?get_env(),?wxToolBar_InsertTool_5), wxe_util:rec(?wxToolBar_InsertTool_5). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarrealize">external documentation</a>. -doc "This function should be called after you have added tools.". -spec realize(This) -> boolean() when This::wxToolBar(). @@ -751,14 +807,12 @@ realize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolBar_Realize), wxe_util:rec(?wxToolBar_Realize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarremovetool">external documentation</a>. -doc """ Removes the given tool from the toolbar but doesn't delete it. This allows inserting/adding this tool back to this (or another) toolbar later. -Note: It is unnecessary to call `realize/1` for the change to take place, it -will happen immediately. +Note: It is unnecessary to call `realize/1` for the change to take place, it will happen immediately. See: `deleteTool/2` """. @@ -770,12 +824,11 @@ removeTool(#wx_ref{type=ThisT}=This,Id) wxe_util:queue_cmd(This,Id,?get_env(),?wxToolBar_RemoveTool), wxe_util:rec(?wxToolBar_RemoveTool). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsetmargins">external documentation</a>. -doc """ Set the values to be used as margins for the toolbar. -Remark: This must be called before the tools are added if absolute positioning -is to be used, and the default (zero-size) margins are to be overridden. +Remark: This must be called before the tools are added if absolute positioning is to be +used, and the default (zero-size) margins are to be overridden. See: `getMargins/1` """. @@ -786,16 +839,18 @@ setMargins(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxToolBar), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxToolBar_SetMargins). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsettoolbitmapsize">external documentation</a>. -doc """ Sets the default size of each tool bitmap. The default bitmap size is 16 by 15 pixels. -Remark: This should be called to tell the toolbar what the tool bitmap size is. -Call it before you add tools. +Remark: This should be called to tell the toolbar what the tool bitmap size is. Call it +before you add tools. + +See: +* `getToolBitmapSize/1` -See: `getToolBitmapSize/1`, `getToolSize/1` +* `getToolSize/1` """. -spec setToolBitmapSize(This, Size) -> 'ok' when This::wxToolBar(), Size::{W::integer(), H::integer()}. @@ -804,14 +859,15 @@ setToolBitmapSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxToolBar), wxe_util:queue_cmd(This,Size,?get_env(),?wxToolBar_SetToolBitmapSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsettoollonghelp">external documentation</a>. -doc """ Sets the long help for the given tool. -Remark: You might use the long help for displaying the tool purpose on the -status line. +Remark: You might use the long help for displaying the tool purpose on the status line. + +See: +* `getToolLongHelp/2` -See: `getToolLongHelp/2`, `setToolShortHelp/3` +* `setToolShortHelp/3` """. -spec setToolLongHelp(This, ToolId, HelpString) -> 'ok' when This::wxToolBar(), ToolId::integer(), HelpString::unicode:chardata(). @@ -821,15 +877,13 @@ setToolLongHelp(#wx_ref{type=ThisT}=This,ToolId,HelpString) HelpString_UC = unicode:characters_to_binary(HelpString), wxe_util:queue_cmd(This,ToolId,HelpString_UC,?get_env(),?wxToolBar_SetToolLongHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsettoolpacking">external documentation</a>. -doc """ Sets the value used for spacing tools. The default value is 1. -Remark: The packing is used for spacing in the vertical direction if the toolbar -is horizontal, and for spacing in the horizontal direction if the toolbar is -vertical. +Remark: The packing is used for spacing in the vertical direction if the toolbar is +horizontal, and for spacing in the horizontal direction if the toolbar is vertical. See: `getToolPacking/1` """. @@ -840,14 +894,15 @@ setToolPacking(#wx_ref{type=ThisT}=This,Packing) ?CLASS(ThisT,wxToolBar), wxe_util:queue_cmd(This,Packing,?get_env(),?wxToolBar_SetToolPacking). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsettoolshorthelp">external documentation</a>. -doc """ Sets the short help for the given tool. -Remark: An application might use short help for identifying the tool purpose in -a tooltip. +Remark: An application might use short help for identifying the tool purpose in a tooltip. + +See: +* `getToolShortHelp/2` -See: `getToolShortHelp/2`, `setToolLongHelp/3` +* `setToolLongHelp/3` """. -spec setToolShortHelp(This, ToolId, HelpString) -> 'ok' when This::wxToolBar(), ToolId::integer(), HelpString::unicode:chardata(). @@ -857,7 +912,6 @@ setToolShortHelp(#wx_ref{type=ThisT}=This,ToolId,HelpString) HelpString_UC = unicode:characters_to_binary(HelpString), wxe_util:queue_cmd(This,ToolId,HelpString_UC,?get_env(),?wxToolBar_SetToolShortHelp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbarsettoolseparation">external documentation</a>. -doc """ Sets the default separator size. @@ -872,7 +926,6 @@ setToolSeparation(#wx_ref{type=ThisT}=This,Separation) ?CLASS(ThisT,wxToolBar), wxe_util:queue_cmd(This,Separation,?get_env(),?wxToolBar_SetToolSeparation). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbar.html#wxtoolbartoggletool">external documentation</a>. -doc """ Toggles a tool on or off. @@ -888,554 +941,371 @@ toggleTool(#wx_ref{type=ThisT}=This,ToolId,Toggle) wxe_util:queue_cmd(This,ToolId,Toggle,?get_env(),?wxToolBar_ToggleTool). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxToolTip.erl b/lib/wx/src/gen/wxToolTip.erl index 6ed92ab2350d..15cae6d85ac3 100644 --- a/lib/wx/src/gen/wxToolTip.erl +++ b/lib/wx/src/gen/wxToolTip.erl @@ -20,17 +20,12 @@ -module(wxToolTip). -moduledoc """ -Functions for wxToolTip class +This class holds information about a tooltip associated with a window (see `wxWindow:setToolTip/2`). -This class holds information about a tooltip associated with a window (see -`wxWindow:setToolTip/2`). +The four static methods, `enable/1`, `setDelay/1` `wxToolTip::SetAutoPop()` (not implemented in wx) and `wxToolTip::SetReshow()` +(not implemented in wx) can be used to globally alter tooltips behaviour. -The four static methods, `enable/1`, `setDelay/1` `wxToolTip::SetAutoPop()` (not -implemented in wx) and `wxToolTip::SetReshow()` (not implemented in wx) can be -used to globally alter tooltips behaviour. - -wxWidgets docs: -[wxToolTip](https://docs.wxwidgets.org/3.1/classwx_tool_tip.html) +wxWidgets docs: [wxToolTip](https://docs.wxwidgets.org/3.2/classwx_tool_tip.html) """. -include("wxe.hrl"). -export([destroy/1,enable/1,getTip/1,getWindow/1,new/1,setDelay/1,setTip/2]). @@ -40,11 +35,9 @@ wxWidgets docs: -type wxToolTip() :: wx:wx_object(). -export_type([wxToolTip/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipenable">external documentation</a>. -doc """ Enable or disable tooltips globally. @@ -56,7 +49,6 @@ enable(Flag) when is_boolean(Flag) -> wxe_util:queue_cmd(Flag,?get_env(),?wxToolTip_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipsetdelay">external documentation</a>. -doc """ Set the delay after which the tooltip appears. @@ -68,7 +60,6 @@ setDelay(Msecs) when is_integer(Msecs) -> wxe_util:queue_cmd(Msecs,?get_env(),?wxToolTip_SetDelay). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipwxtooltip">external documentation</a>. -doc "Constructor.". -spec new(Tip) -> wxToolTip() when Tip::unicode:chardata(). @@ -78,7 +69,6 @@ new(Tip) wxe_util:queue_cmd(Tip_UC,?get_env(),?wxToolTip_new), wxe_util:rec(?wxToolTip_new). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipsettip">external documentation</a>. -doc "Set the tooltip text.". -spec setTip(This, Tip) -> 'ok' when This::wxToolTip(), Tip::unicode:chardata(). @@ -88,7 +78,6 @@ setTip(#wx_ref{type=ThisT}=This,Tip) Tip_UC = unicode:characters_to_binary(Tip), wxe_util:queue_cmd(This,Tip_UC,?get_env(),?wxToolTip_SetTip). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipgettip">external documentation</a>. -doc "Get the tooltip text.". -spec getTip(This) -> unicode:charlist() when This::wxToolTip(). @@ -97,7 +86,6 @@ getTip(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolTip_GetTip), wxe_util:rec(?wxToolTip_GetTip). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtooltip.html#wxtooltipgetwindow">external documentation</a>. -doc "Get the associated window.". -spec getWindow(This) -> wxWindow:wxWindow() when This::wxToolTip(). @@ -106,8 +94,7 @@ getWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolTip_GetWindow), wxe_util:rec(?wxToolTip_GetWindow). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxToolTip()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxToolTip), diff --git a/lib/wx/src/gen/wxToolbook.erl b/lib/wx/src/gen/wxToolbook.erl index 05ea25502e43..3b4b5e0baae1 100644 --- a/lib/wx/src/gen/wxToolbook.erl +++ b/lib/wx/src/gen/wxToolbook.erl @@ -20,39 +20,55 @@ -module(wxToolbook). -moduledoc """ -Functions for wxToolbook class +`m:wxToolbook` is a class similar to `m:wxNotebook` but which uses a `m:wxToolBar` to +show the labels instead of the tabs. -`m:wxToolbook` is a class similar to `m:wxNotebook` but which uses a -`m:wxToolBar` to show the labels instead of the tabs. - -There is no documentation for this class yet but its usage is identical to -`m:wxNotebook` (except for the features clearly related to tabs only), so please -refer to that class documentation for now. You can also use the -page_samples_notebook to see `m:wxToolbook` in action. +There is no documentation for this class yet but its usage is identical to `m:wxNotebook` +(except for the features clearly related to tabs only), so please refer to that class +documentation for now. You can also use the page_samples_notebook to see `m:wxToolbook` in action. One feature of this class not supported by `m:wxBookCtrlBase` is the support for disabling some of the pages, see `EnablePage()` (not implemented in wx). -Styles +## Styles This class supports the following styles: +* wxTBK_BUTTONBAR: Use wxButtonToolBar-based implementation under macOS (ignored under +other platforms). + +* wxTBK_HORZ_LAYOUT: Shows the text and the icons alongside, not vertically stacked (only +implement under Windows and GTK 2 platforms as it relies on `wxTB_HORZ_LAYOUT` flag +support). The common wxBookCtrl styles described in the overview_bookctrl are also supported. + See: -[Overview bookctrl](https://docs.wxwidgets.org/3.1/overview_bookctrl.html#overview_bookctrl), -`m:wxBookCtrlBase`, `m:wxNotebook`, -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_notebook) +* [Overview bookctrl](https://docs.wxwidgets.org/3.2/overview_bookctrl.html#overview_bookctrl) + +* `m:wxBookCtrlBase` + +* `m:wxNotebook` + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_notebook) + +This class is derived, and can use functions, from: + +* `m:wxBookCtrlBase` + +* `m:wxControl` -This class is derived (and can use functions) from: `m:wxBookCtrlBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxWindow` -wxWidgets docs: -[wxToolbook](https://docs.wxwidgets.org/3.1/classwx_toolbook.html) +* `m:wxEvtHandler` + +wxWidgets docs: [wxToolbook](https://docs.wxwidgets.org/3.2/classwx_toolbook.html) ## Events Event types emitted from this class: -[`toolbook_page_changed`](`m:wxBookCtrlEvent`), -[`toolbook_page_changing`](`m:wxBookCtrlEvent`) + +* [`toolbook_page_changed`](`m:wxBookCtrlEvent`) + +* [`toolbook_page_changing`](`m:wxBookCtrlEvent`) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,advanceSelection/1,advanceSelection/2,assignImageList/2, @@ -103,7 +119,6 @@ Event types emitted from this class: -type wxToolbook() :: wx:wx_object(). -export_type([wxToolbook/0]). -%% @hidden -doc false. parent_class(wxBookCtrlBase) -> true; parent_class(wxControl) -> true; @@ -111,14 +126,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookwxtoolbook">external documentation</a>. -doc "Constructs a choicebook control.". -spec new() -> wxToolbook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxToolbook_new_0), wxe_util:rec(?wxToolbook_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxToolbook() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -126,7 +140,7 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookwxtoolbook">external documentation</a>. +-doc "". -spec new(Parent, Id, [Option]) -> wxToolbook() when Parent::wxWindow:wxWindow(), Id::integer(), Option :: {'pos', {X::integer(), Y::integer()}} @@ -143,7 +157,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxToolbook_new_3), wxe_util:rec(?wxToolbook_new_3). -%% @equiv addPage(This,Page,Text, []) +-doc(#{equiv => addPage(This,Page,Text, [])}). -spec addPage(This, Page, Text) -> boolean() when This::wxToolbook(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -151,17 +165,15 @@ addPage(This,Page,Text) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Text) -> addPage(This,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookaddpage">external documentation</a>. -doc """ Adds a new page. -The page must have the book control itself as the parent and must not have been -added to this control previously. +The page must have the book control itself as the parent and must not have been added to +this control previously. -The call to this function will generate the page changing and page changed -events if `select` is true, but not when inserting the very first page (as there -is no previous page selection to switch from in this case and so it wouldn't -make sense to e.g. veto such event). +The call to this function will generate the page changing and page changed events if `select` +is true, but not when inserting the very first page (as there is no previous page +selection to switch from in this case and so it wouldn't make sense to e.g. veto such event). Return: true if successful, false otherwise. @@ -185,7 +197,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text, Options) wxe_util:queue_cmd(This,Page,Text_UC, Opts,?get_env(),?wxToolbook_AddPage), wxe_util:rec(?wxToolbook_AddPage). -%% @equiv advanceSelection(This, []) +-doc(#{equiv => advanceSelection(This, [])}). -spec advanceSelection(This) -> 'ok' when This::wxToolbook(). @@ -193,7 +205,6 @@ advanceSelection(This) when is_record(This, wx_ref) -> advanceSelection(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookadvanceselection">external documentation</a>. -doc """ Cycles through the tabs. @@ -210,11 +221,13 @@ advanceSelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxToolbook_AdvanceSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookassignimagelist">external documentation</a>. -doc """ Sets the image list for the page control and takes ownership of the list. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec assignImageList(This, ImageList) -> 'ok' when This::wxToolbook(), ImageList::wxImageList:wxImageList(). @@ -223,7 +236,7 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxToolbook_AssignImageList). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxToolbook(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -231,7 +244,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookcreate">external documentation</a>. -doc """ Create the tool book control that has already been constructed with the default constructor. @@ -253,7 +265,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxToolbook_Create), wxe_util:rec(?wxToolbook_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookdeleteallpages">external documentation</a>. -doc "Deletes all pages.". -spec deleteAllPages(This) -> boolean() when This::wxToolbook(). @@ -262,7 +273,6 @@ deleteAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolbook_DeleteAllPages), wxe_util:rec(?wxToolbook_DeleteAllPages). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetcurrentpage">external documentation</a>. -doc "Returns the currently selected page or NULL.". -spec getCurrentPage(This) -> wxWindow:wxWindow() when This::wxToolbook(). @@ -271,11 +281,13 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolbook_GetCurrentPage), wxe_util:rec(?wxToolbook_GetCurrentPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetimagelist">external documentation</a>. -doc """ Returns the associated image list, may be NULL. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec getImageList(This) -> wxImageList:wxImageList() when This::wxToolbook(). @@ -284,7 +296,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolbook_GetImageList), wxe_util:rec(?wxToolbook_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetpage">external documentation</a>. -doc "Returns the window at the given page position.". -spec getPage(This, Page) -> wxWindow:wxWindow() when This::wxToolbook(), Page::integer(). @@ -294,7 +305,6 @@ getPage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxToolbook_GetPage), wxe_util:rec(?wxToolbook_GetPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetpagecount">external documentation</a>. -doc "Returns the number of pages in the control.". -spec getPageCount(This) -> integer() when This::wxToolbook(). @@ -303,7 +313,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolbook_GetPageCount), wxe_util:rec(?wxToolbook_GetPageCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetpageimage">external documentation</a>. -doc "Returns the image index for the given page.". -spec getPageImage(This, NPage) -> integer() when This::wxToolbook(), NPage::integer(). @@ -313,7 +322,6 @@ getPageImage(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxToolbook_GetPageImage), wxe_util:rec(?wxToolbook_GetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetpagetext">external documentation</a>. -doc "Returns the string for the given page.". -spec getPageText(This, NPage) -> unicode:charlist() when This::wxToolbook(), NPage::integer(). @@ -323,14 +331,12 @@ getPageText(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxToolbook_GetPageText), wxe_util:rec(?wxToolbook_GetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookgetselection">external documentation</a>. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note that this method may return either the previously or newly selected page -when called from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the -platform and so `wxBookCtrlEvent:getSelection/1` should be used instead in this -case. +Note that this method may return either the previously or newly selected page when called +from the `EVT_BOOKCTRL_PAGE_CHANGED` handler depending on the platform and so `wxBookCtrlEvent:getSelection/1` should be +used instead in this case. """. -spec getSelection(This) -> integer() when This::wxToolbook(). @@ -339,15 +345,13 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxToolbook_GetSelection), wxe_util:rec(?wxToolbook_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookhittest">external documentation</a>. -doc """ -Returns the index of the tab at the specified position or `wxNOT_FOUND` if none. +Returns the index of the tab at the specified position or `wxNOT\_FOUND` if none. -If `flags` parameter is non-NULL, the position of the point inside the tab is -returned as well. +If `flags` parameter is non-NULL, the position of the point inside the tab is returned as well. -Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at -the specified position. +Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at the +specified position. """. -spec hitTest(This, Pt) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -358,7 +362,7 @@ hitTest(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxToolbook_HitTest), wxe_util:rec(?wxToolbook_HitTest). -%% @equiv insertPage(This,Index,Page,Text, []) +-doc(#{equiv => insertPage(This,Index,Page,Text, [])}). -spec insertPage(This, Index, Page, Text) -> boolean() when This::wxToolbook(), Index::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -366,7 +370,6 @@ insertPage(This,Index,Page,Text) when is_record(This, wx_ref),is_integer(Index),is_record(Page, wx_ref),?is_chardata(Text) -> insertPage(This,Index,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookinsertpage">external documentation</a>. -doc """ Inserts a new page at the specified position. @@ -392,13 +395,15 @@ insertPage(#wx_ref{type=ThisT}=This,Index,#wx_ref{type=PageT}=Page,Text, Options wxe_util:queue_cmd(This,Index,Page,Text_UC, Opts,?get_env(),?wxToolbook_InsertPage), wxe_util:rec(?wxToolbook_InsertPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbooksetimagelist">external documentation</a>. -doc """ Sets the image list to use. It does not take ownership of the image list, you must delete it yourself. -See: `m:wxImageList`, `assignImageList/2` +See: +* `m:wxImageList` + +* `assignImageList/2` """. -spec setImageList(This, ImageList) -> 'ok' when This::wxToolbook(), ImageList::wxImageList:wxImageList(). @@ -407,7 +412,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxToolbook_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbooksetpagesize">external documentation</a>. -doc """ Sets the width and height of the pages. @@ -420,7 +424,6 @@ setPageSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxToolbook), wxe_util:queue_cmd(This,Size,?get_env(),?wxToolbook_SetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbooksetpageimage">external documentation</a>. -doc """ Sets the image index for the given page. @@ -434,7 +437,6 @@ setPageImage(#wx_ref{type=ThisT}=This,Page,Image) wxe_util:queue_cmd(This,Page,Image,?get_env(),?wxToolbook_SetPageImage), wxe_util:rec(?wxToolbook_SetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbooksetpagetext">external documentation</a>. -doc "Sets the text for the given page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxToolbook(), Page::integer(), Text::unicode:chardata(). @@ -445,12 +447,11 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:queue_cmd(This,Page,Text_UC,?get_env(),?wxToolbook_SetPageText), wxe_util:rec(?wxToolbook_SetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbooksetselection">external documentation</a>. -doc """ Sets the selection to the given page, returning the previous selection. -Notice that the call to this function generates the page changing events, use -the `changeSelection/2` function if you don't want these events to be generated. +Notice that the call to this function generates the page changing events, use the `changeSelection/2` +function if you don't want these events to be generated. See: `getSelection/1` """. @@ -462,12 +463,10 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxToolbook_SetSelection), wxe_util:rec(?wxToolbook_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoolbook.html#wxtoolbookchangeselection">external documentation</a>. -doc """ Changes the selection to the given page, returning the previous selection. -This function behaves as `setSelection/2` but does `not` generate the page -changing events. +This function behaves as `setSelection/2` but does `not` generate the page changing events. See overview_events_prog for more information. """. @@ -479,569 +478,383 @@ changeSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxToolbook_ChangeSelection), wxe_util:rec(?wxToolbook_ChangeSelection). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxToolbook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxToolbook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBookCtrlBase -%% @hidden -doc false. removePage(This,Page) -> wxBookCtrlBase:removePage(This,Page). -%% @hidden -doc false. deletePage(This,Page) -> wxBookCtrlBase:deletePage(This,Page). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxTopLevelWindow.erl b/lib/wx/src/gen/wxTopLevelWindow.erl index fab5f4891101..63e11410ad60 100644 --- a/lib/wx/src/gen/wxTopLevelWindow.erl +++ b/lib/wx/src/gen/wxTopLevelWindow.erl @@ -20,27 +20,36 @@ -module(wxTopLevelWindow). -moduledoc """ -Functions for wxTopLevelWindow class +`m:wxTopLevelWindow` is a common base class for `m:wxDialog` and `m:wxFrame`. -`m:wxTopLevelWindow` is a common base class for `m:wxDialog` and `m:wxFrame`. It -is an abstract base class meaning that you never work with objects of this class +It is an abstract base class meaning that you never work with objects of this class directly, but all of its methods are also applicable for the two classes above. -Note that the instances of `m:wxTopLevelWindow` are managed by wxWidgets in the -internal top level window list. +Note that the instances of `m:wxTopLevelWindow` are managed by wxWidgets in the internal +top level window list. -See: `m:wxDialog`, `m:wxFrame` +See: +* `m:wxDialog` -This class is derived (and can use functions) from: `m:wxWindow` -`m:wxEvtHandler` +* `m:wxFrame` -wxWidgets docs: -[wxTopLevelWindow](https://docs.wxwidgets.org/3.1/classwx_top_level_window.html) +This class is derived, and can use functions, from: + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxTopLevelWindow](https://docs.wxwidgets.org/3.2/classwx_top_level_window.html) ## Events -Event types emitted from this class: [`maximize`](`m:wxMaximizeEvent`), -[`move`](`m:wxMoveEvent`), [`show`](`m:wxShowEvent`) +Event types emitted from this class: + +* [`maximize`](`m:wxMaximizeEvent`) + +* [`move`](`m:wxMoveEvent`) + +* [`show`](`m:wxShowEvent`) """. -include("wxe.hrl"). -export([centerOnScreen/1,centerOnScreen/2,centreOnScreen/1,centreOnScreen/2, @@ -91,13 +100,11 @@ Event types emitted from this class: [`maximize`](`m:wxMaximizeEvent`), -type wxTopLevelWindow() :: wx:wx_object(). -export_type([wxTopLevelWindow/0]). -%% @hidden -doc false. parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowgeticon">external documentation</a>. -doc """ Returns the standard icon of the window. @@ -112,10 +119,9 @@ getIcon(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_GetIcon), wxe_util:rec(?wxTopLevelWindow_GetIcon). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowgeticons">external documentation</a>. -doc """ -Returns all icons associated with the window, there will be none of them if -neither `setIcon/2` nor `setIcons/2` had been called before. +Returns all icons associated with the window, there will be none of them if neither `setIcon/2` +nor `setIcons/2` had been called before. Use `getIcon/1` to get the main icon of the window. @@ -128,7 +134,6 @@ getIcons(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_GetIcons), wxe_util:rec(?wxTopLevelWindow_GetIcons). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowgettitle">external documentation</a>. -doc """ Gets a string containing the window title. @@ -141,10 +146,9 @@ getTitle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_GetTitle), wxe_util:rec(?wxTopLevelWindow_GetTitle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowisactive">external documentation</a>. -doc """ -Returns true if this window is currently active, i.e. if the user is currently -working with it. +Returns true if this window is currently active, i.e. if the user is currently working +with it. """. -spec isActive(This) -> boolean() when This::wxTopLevelWindow(). @@ -153,7 +157,7 @@ isActive(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_IsActive), wxe_util:rec(?wxTopLevelWindow_IsActive). -%% @equiv iconize(This, []) +-doc(#{equiv => iconize(This, [])}). -spec iconize(This) -> 'ok' when This::wxTopLevelWindow(). @@ -161,16 +165,18 @@ iconize(This) when is_record(This, wx_ref) -> iconize(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowiconize">external documentation</a>. -doc """ Iconizes or restores the window. -Note that in wxGTK the change to the window state is not immediate, i.e. -`isIconized/1` will typically return false right after a call to `iconize/2` and -its return value will only change after the control flow returns to the event -loop and the notification about the window being really iconized is received. +Note that in wxGTK the change to the window state is not immediate, i.e. `isIconized/1` will typically +return false right after a call to `iconize/2` and its return value will only change after the +control flow returns to the event loop and the notification about the window being really +iconized is received. + +See: +* `isIconized/1` -See: `isIconized/1`, `Restore()` (not implemented in wx), (), `m:wxIconizeEvent` +* `m:wxIconizeEvent` """. -spec iconize(This, [Option]) -> 'ok' when This::wxTopLevelWindow(), @@ -183,7 +189,6 @@ iconize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxTopLevelWindow_Iconize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowisfullscreen">external documentation</a>. -doc """ Returns true if the window is in fullscreen mode. @@ -196,7 +201,6 @@ isFullScreen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_IsFullScreen), wxe_util:rec(?wxTopLevelWindow_IsFullScreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowisiconized">external documentation</a>. -doc "Returns true if the window is iconized.". -spec isIconized(This) -> boolean() when This::wxTopLevelWindow(). @@ -205,7 +209,6 @@ isIconized(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_IsIconized), wxe_util:rec(?wxTopLevelWindow_IsIconized). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowismaximized">external documentation</a>. -doc "Returns true if the window is maximized.". -spec isMaximized(This) -> boolean() when This::wxTopLevelWindow(). @@ -214,7 +217,7 @@ isMaximized(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTopLevelWindow_IsMaximized), wxe_util:rec(?wxTopLevelWindow_IsMaximized). -%% @equiv maximize(This, []) +-doc(#{equiv => maximize(This, [])}). -spec maximize(This) -> 'ok' when This::wxTopLevelWindow(). @@ -222,14 +225,13 @@ maximize(This) when is_record(This, wx_ref) -> maximize(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowmaximize">external documentation</a>. -doc """ Maximizes or restores the window. -Note that, just as with `iconize/2`, the change to the window state is not -immediate in at least wxGTK port. +Note that, just as with `iconize/2`, the change to the window state is not immediate in at least +wxGTK port. -See: `Restore()` (not implemented in wx), `iconize/2` +See: `iconize/2` """. -spec maximize(This, [Option]) -> 'ok' when This::wxTopLevelWindow(), @@ -242,7 +244,7 @@ maximize(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxTopLevelWindow_Maximize). -%% @equiv requestUserAttention(This, []) +-doc(#{equiv => requestUserAttention(This, [])}). -spec requestUserAttention(This) -> 'ok' when This::wxTopLevelWindow(). @@ -250,20 +252,17 @@ requestUserAttention(This) when is_record(This, wx_ref) -> requestUserAttention(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowrequestuserattention">external documentation</a>. -doc """ -Use a system-dependent way to attract users attention to the window when it is -in background. +Use a system-dependent way to attract users attention to the window when it is in +background. -`flags` may have the value of either `?wxUSER_ATTENTION_INFO` (default) or -`?wxUSER_ATTENTION_ERROR` which results in a more drastic action. When in doubt, -use the default value. +`flags` may have the value of either `?wxUSER\_ATTENTION\_INFO` (default) or `?wxUSER\_ATTENTION\_ERROR` +which results in a more drastic action. When in doubt, use the default value. -Note: This function should normally be only used when the application is not -already in foreground. +Note: This function should normally be only used when the application is not already in foreground. -This function is currently implemented for Win32 where it flashes the window -icon in the taskbar, and for wxGTK with task bars supporting it. +This function is currently implemented for Win32 where it flashes the window icon in the +taskbar, and for wxGTK with task bars supporting it. """. -spec requestUserAttention(This, [Option]) -> 'ok' when This::wxTopLevelWindow(), @@ -276,17 +275,18 @@ requestUserAttention(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxTopLevelWindow_RequestUserAttention). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowseticon">external documentation</a>. -doc """ Sets the icon for this window. -Remark: The window takes a 'copy' of `icon`, but since it uses reference -counting, the copy is very quick. It is safe to delete `icon` after calling this -function. +Remark: The window takes a 'copy' of `icon`, but since it uses reference counting, the +copy is very quick. It is safe to delete `icon` after calling this function. Note: In wxMSW, `icon` must be either 16x16 or 32x32 icon. -See: `m:wxIcon`, `setIcons/2` +See: +* `m:wxIcon` + +* `setIcons/2` """. -spec setIcon(This, Icon) -> 'ok' when This::wxTopLevelWindow(), Icon::wxIcon:wxIcon(). @@ -295,13 +295,12 @@ setIcon(#wx_ref{type=ThisT}=This,#wx_ref{type=IconT}=Icon) -> ?CLASS(IconT,wxIcon), wxe_util:queue_cmd(This,Icon,?get_env(),?wxTopLevelWindow_SetIcon). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowseticons">external documentation</a>. -doc """ -Sets several icons of different sizes for this window: this allows using -different icons for different situations (e.g. +Sets several icons of different sizes for this window: this allows using different icons +for different situations (e.g. -task switching bar, taskbar, window title bar) instead of scaling, with possibly -bad looking results, the only icon set by `setIcon/2`. +task switching bar, taskbar, window title bar) instead of scaling, with possibly bad +looking results, the only icon set by `setIcon/2`. Note: In wxMSW, `icons` must contain a 16x16 or 32x32 icon, preferably both. @@ -314,7 +313,7 @@ setIcons(#wx_ref{type=ThisT}=This,#wx_ref{type=IconsT}=Icons) -> ?CLASS(IconsT,wxIconBundle), wxe_util:queue_cmd(This,Icons,?get_env(),?wxTopLevelWindow_SetIcons). -%% @equiv centerOnScreen(This, []) +-doc(#{equiv => centerOnScreen(This, [])}). -spec centerOnScreen(This) -> 'ok' when This::wxTopLevelWindow(). @@ -322,7 +321,7 @@ centerOnScreen(This) when is_record(This, wx_ref) -> centerOnScreen(This, []). -%% @equiv centreOnScreen(This, []) +-doc(#{equiv => centreOnScreen(This, [])}). -spec centreOnScreen(This) -> 'ok' when This::wxTopLevelWindow(). @@ -330,8 +329,7 @@ centreOnScreen(This) when is_record(This, wx_ref) -> centreOnScreen(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowcentreonscreen">external documentation</a>. --doc "See: `centreOnScreen/2`.". +-doc "Equivalent to: `centreOnScreen/2`". -spec centerOnScreen(This, [Option]) -> 'ok' when This::wxTopLevelWindow(), Option :: {'dir', integer()}. @@ -340,7 +338,6 @@ centerOnScreen(This, Options) when is_record(This, wx_ref),is_list(Options) -> centreOnScreen(This, Options). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowcentreonscreen">external documentation</a>. -doc """ Centres the window on screen. @@ -357,21 +354,17 @@ centreOnScreen(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxTopLevelWindow_CentreOnScreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowsetshape">external documentation</a>. -doc """ -If the platform supports it, sets the shape of the window to that depicted by -`region`. +If the platform supports it, sets the shape of the window to that depicted by `region`. -The system will not display or respond to any mouse event for the pixels that -lie outside of the region. To reset the window to the normal rectangular shape -simply call `setShape/2` again with an empty `m:wxRegion`. Returns true if the -operation is successful. +The system will not display or respond to any mouse event for the pixels that lie outside +of the region. To reset the window to the normal rectangular shape simply call `setShape/2` again with +an empty `m:wxRegion`. Returns true if the operation is successful. -This method is available in this class only since wxWidgets 2.9.3, previous -versions only provided it in `m:wxTopLevelWindow`. +This method is available in this class only since wxWidgets 2.9.3, previous versions only +provided it in `m:wxTopLevelWindow`. -Note that windows with non default shape have a fixed size and can't be resized -using `wxWindow:setSize/6`. +Note that windows with non default shape have a fixed size and can't be resized using `wxWindow:setSize/6`. """. -spec setShape(This, Region) -> boolean() when This::wxTopLevelWindow(), Region::wxRegion:wxRegion() | wxGraphicsPath:wxGraphicsPath(). @@ -387,7 +380,6 @@ setShape(#wx_ref{type=ThisT}=This,#wx_ref{type=RegionT}=Region) -> wxe_util:queue_cmd(This,wx:typeCast(Region, RegionType),?get_env(),?wxTopLevelWindow_SetShape), wxe_util:rec(?wxTopLevelWindow_SetShape). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowsettitle">external documentation</a>. -doc """ Sets the window title. @@ -401,7 +393,7 @@ setTitle(#wx_ref{type=ThisT}=This,Title) Title_UC = unicode:characters_to_binary(Title), wxe_util:queue_cmd(This,Title_UC,?get_env(),?wxTopLevelWindow_SetTitle). -%% @equiv showFullScreen(This,Show, []) +-doc(#{equiv => showFullScreen(This,Show, [])}). -spec showFullScreen(This, Show) -> boolean() when This::wxTopLevelWindow(), Show::boolean(). @@ -409,20 +401,30 @@ showFullScreen(This,Show) when is_record(This, wx_ref),is_boolean(Show) -> showFullScreen(This,Show, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtoplevelwindow.html#wxtoplevelwindowshowfullscreen">external documentation</a>. -doc """ -Depending on the value of `show` parameter the window is either shown full -screen or restored to its normal state. +Depending on the value of `show` parameter the window is either shown full screen or +restored to its normal state. + +`style` is a bit list containing some or all of the following values, which indicate what +elements of the window to hide in full-screen mode: + +* `?wxFULLSCREEN\_NOMENUBAR` + +* `?wxFULLSCREEN\_NOTOOLBAR` + +* `?wxFULLSCREEN\_NOSTATUSBAR` + +* `?wxFULLSCREEN\_NOBORDER` + +* `?wxFULLSCREEN\_NOCAPTION` -`style` is a bit list containing some or all of the following values, which -indicate what elements of the window to hide in full-screen mode: +* `?wxFULLSCREEN\_ALL` (all of the above) This function has not been tested with MDI frames. -Note: Showing a window full screen also actually `wxWindow:show/2`s the window -if it isn't shown. +Note: Showing a window full screen also actually `wxWindow:show/2`s the window if it isn't shown. -See: `EnableFullScreenView()` (not implemented in wx), `isFullScreen/1` +See: `isFullScreen/1` """. -spec showFullScreen(This, Show, [Option]) -> boolean() when This::wxTopLevelWindow(), Show::boolean(), @@ -437,553 +439,370 @@ showFullScreen(#wx_ref{type=ThisT}=This,Show, Options) wxe_util:rec(?wxTopLevelWindow_ShowFullScreen). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setLabel(This,Label) -> wxWindow:setLabel(This,Label). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getLabel(This) -> wxWindow:getLabel(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxTreeCtrl.erl b/lib/wx/src/gen/wxTreeCtrl.erl index 10ab8dd55846..039664e15b67 100644 --- a/lib/wx/src/gen/wxTreeCtrl.erl +++ b/lib/wx/src/gen/wxTreeCtrl.erl @@ -24,71 +24,141 @@ %% -module(wxTreeCtrl). -moduledoc """ -Functions for wxTreeCtrl class +A tree control presents information as a hierarchy, with items that may be expanded to +show further items. -A tree control presents information as a hierarchy, with items that may be -expanded to show further items. Items in a tree control are referenced by -`wxTreeItemId` (not implemented in wx) handles, which may be tested for validity -by calling `wxTreeItemId::IsOk()` (not implemented in wx). +Items in a tree control are referenced by `wxTreeItemId` (not implemented in wx) handles, +which may be tested for validity by calling `wxTreeItemId::IsOk()` (not implemented in wx). -A similar control with a fully native implementation for GTK+ and macOS as well -is `wxDataViewTreeCtrl` (not implemented in wx). +A similar control with a fully native implementation for GTK+ and macOS as well is `wxDataViewTreeCtrl` +(not implemented in wx). -To intercept events from a tree control, use the event table macros described in -`m:wxTreeEvent`. +To intercept events from a tree control, use the event table macros described in `m:wxTreeEvent`. -Styles +## Styles This class supports the following styles: +* wxTR_EDIT_LABELS: Use this style if you wish the user to be able to edit labels in the +tree control. + +* wxTR_NO_BUTTONS: For convenience to document that no buttons are to be drawn. + +* wxTR_HAS_BUTTONS: Use this style to show + and - buttons to the left of parent items. + +* wxTR_TWIST_BUTTONS: Selects alternative style of +/`-` buttons and shows rotating +("twisting") arrows instead. Currently this style is only implemented under Microsoft +Windows Vista and later Windows versions and is ignored under the other platforms as +enabling it is equivalent to using `wxSystemThemedControl::EnableSystemTheme()` (not +implemented in wx). + +* wxTR_NO_LINES: Use this style to hide vertical level connectors. + +* wxTR_FULL_ROW_HIGHLIGHT: Use this style to have the background colour and the selection +highlight extend over the entire horizontal row of the tree control window. (This flag is +ignored under Windows unless you specify `wxTR_NO_LINES` as well.) + +* wxTR_LINES_AT_ROOT: Use this style to show lines leading to the root nodes (unless no `wxTR_NO_LINES` +is also used, in which case no lines are shown). Note that in the MSW version, if this +style is omitted, not only the lines, but also the button used for expanding the root item +is not shown, which can be unexpected, so it is recommended to always use it. + +* wxTR_HIDE_ROOT: Use this style to suppress the display of the root node, effectively +causing the first-level nodes to appear as a series of root nodes. + +* wxTR_ROW_LINES: Use this style to draw a contrasting border between displayed rows. + +* wxTR_HAS_VARIABLE_ROW_HEIGHT: Use this style to cause row heights to be just big enough +to fit the content. If not set, all rows use the largest row height. The default is that +this flag is unset. Generic only. + +* wxTR_SINGLE: For convenience to document that only one item may be selected at a time. +Selecting another item causes the current selection, if any, to be deselected. This is the +default. + +* wxTR_MULTIPLE: Use this style to allow a range of items to be selected. If a second range +is selected, the current range, if any, is deselected. + +* wxTR_DEFAULT_STYLE: The set of flags that are closest to the defaults for the native +control for a particular toolkit. + See also overview_windowstyles. `Win32` `notes:` -`m:wxTreeCtrl` class uses the standard common treeview control under Win32 -implemented in the system library comctl32.dll. Some versions of this library -are known to have bugs with handling the tree control colours: the usual symptom -is that the expanded items leave black (or otherwise incorrectly coloured) -background behind them, especially for the controls using non-default background -colour. The recommended solution is to upgrade the comctl32.dll to a newer -version: see -[http://www.microsoft.com/downloads/details.aspx?familyid=cb2cf3a2-8025-4e8f-8511-9b476a8d35d2](http://www.microsoft.com/downloads/details.aspx?familyid=cb2cf3a2-8025-4e8f-8511-9b476a8d35d2) +`m:wxTreeCtrl` class uses the standard common treeview control under Win32 implemented in +the system library comctl32.dll. Some versions of this library are known to have bugs with +handling the tree control colours: the usual symptom is that the expanded items leave +black (or otherwise incorrectly coloured) background behind them, especially for the +controls using non-default background colour. The recommended solution is to upgrade the +comctl32.dll to a newer version: see [http://www.microsoft.com/downloads/details.aspx?familyid=cb2cf3a2-8025-4e8f-8511-9b476a8d35d2](http://www.microsoft.com/downloads/details.aspx?familyid=cb2cf3a2-8025-4e8f-8511-9b476a8d35d2) + +See: +* `m:wxTreeEvent` + +* [Overview treectrl](https://docs.wxwidgets.org/3.2/overview_treectrl.html#overview_treectrl) + +* `m:wxListBox` + +* `m:wxListCtrl` -See: `wxDataViewTreeCtrl` (not implemented in wx), `m:wxTreeEvent`, -`wxTreeItemData` (not implemented in wx), -[Overview treectrl](https://docs.wxwidgets.org/3.1/overview_treectrl.html#overview_treectrl), -`m:wxListBox`, `m:wxListCtrl`, `m:wxImageList` +* `m:wxImageList` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxTreeCtrl](https://docs.wxwidgets.org/3.1/classwx_tree_ctrl.html) +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxTreeCtrl](https://docs.wxwidgets.org/3.2/classwx_tree_ctrl.html) ## Events Event types emitted from this class: -[`command_tree_begin_drag`](`m:wxTreeEvent`), -[`command_tree_begin_rdrag`](`m:wxTreeEvent`), -[`command_tree_end_drag`](`m:wxTreeEvent`), -[`command_tree_begin_label_edit`](`m:wxTreeEvent`), -[`command_tree_end_label_edit`](`m:wxTreeEvent`), -[`command_tree_delete_item`](`m:wxTreeEvent`), -[`command_tree_get_info`](`m:wxTreeEvent`), -[`command_tree_set_info`](`m:wxTreeEvent`), -[`command_tree_item_activated`](`m:wxTreeEvent`), -[`command_tree_item_collapsed`](`m:wxTreeEvent`), -[`command_tree_item_collapsing`](`m:wxTreeEvent`), -[`command_tree_item_expanded`](`m:wxTreeEvent`), -[`command_tree_item_expanding`](`m:wxTreeEvent`), -[`command_tree_item_right_click`](`m:wxTreeEvent`), -[`command_tree_item_middle_click`](`m:wxTreeEvent`), -[`command_tree_sel_changed`](`m:wxTreeEvent`), -[`command_tree_sel_changing`](`m:wxTreeEvent`), -[`command_tree_key_down`](`m:wxTreeEvent`), -[`command_tree_item_gettooltip`](`m:wxTreeEvent`), -[`command_tree_item_menu`](`m:wxTreeEvent`), -[`command_tree_state_image_click`](`m:wxTreeEvent`) + +* [`command_tree_begin_drag`](`m:wxTreeEvent`) + +* [`command_tree_begin_rdrag`](`m:wxTreeEvent`) + +* [`command_tree_end_drag`](`m:wxTreeEvent`) + +* [`command_tree_begin_label_edit`](`m:wxTreeEvent`) + +* [`command_tree_end_label_edit`](`m:wxTreeEvent`) + +* [`command_tree_delete_item`](`m:wxTreeEvent`) + +* [`command_tree_get_info`](`m:wxTreeEvent`) + +* [`command_tree_set_info`](`m:wxTreeEvent`) + +* [`command_tree_item_activated`](`m:wxTreeEvent`) + +* [`command_tree_item_collapsed`](`m:wxTreeEvent`) + +* [`command_tree_item_collapsing`](`m:wxTreeEvent`) + +* [`command_tree_item_expanded`](`m:wxTreeEvent`) + +* [`command_tree_item_expanding`](`m:wxTreeEvent`) + +* [`command_tree_item_right_click`](`m:wxTreeEvent`) + +* [`command_tree_item_middle_click`](`m:wxTreeEvent`) + +* [`command_tree_sel_changed`](`m:wxTreeEvent`) + +* [`command_tree_sel_changing`](`m:wxTreeEvent`) + +* [`command_tree_key_down`](`m:wxTreeEvent`) + +* [`command_tree_item_gettooltip`](`m:wxTreeEvent`) + +* [`command_tree_item_menu`](`m:wxTreeEvent`) + +* [`command_tree_state_image_click`](`m:wxTreeEvent`) """. -include("wxe.hrl"). -export([addRoot/2,addRoot/3,appendItem/3,appendItem/4,assignImageList/2,assignStateImageList/2, @@ -151,21 +221,19 @@ Event types emitted from this class: -type wxTreeCtrl() :: wx:wx_object(). -export_type([wxTreeCtrl/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlwxtreectrl">external documentation</a>. -doc "Default Constructor.". -spec new() -> wxTreeCtrl(). new() -> wxe_util:queue_cmd(?get_env(), ?wxTreeCtrl_new_0), wxe_util:rec(?wxTreeCtrl_new_0). -%% @equiv new(Parent, []) +-doc(#{equiv => new(Parent, [])}). -spec new(Parent) -> wxTreeCtrl() when Parent::wxWindow:wxWindow(). @@ -173,11 +241,10 @@ new(Parent) when is_record(Parent, wx_ref) -> new(Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlwxtreectrl">external documentation</a>. -doc """ Constructor, creating and showing a tree control. -See: `create/3`, `wxValidator` (not implemented in wx) +See: `create/3` """. -spec new(Parent, [Option]) -> wxTreeCtrl() when Parent::wxWindow:wxWindow(), @@ -199,7 +266,7 @@ new(#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(Parent, Opts,?get_env(),?wxTreeCtrl_new_2), wxe_util:rec(?wxTreeCtrl_new_2). -%% @equiv addRoot(This,Text, []) +-doc(#{equiv => addRoot(This,Text, [])}). -spec addRoot(This, Text) -> integer() when This::wxTreeCtrl(), Text::unicode:chardata(). @@ -207,14 +274,12 @@ addRoot(This,Text) when is_record(This, wx_ref),?is_chardata(Text) -> addRoot(This,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrladdroot">external documentation</a>. -doc """ Adds the root node to the tree, returning the new item. The `image` and `selImage` parameters are an index within the normal image list -specifying the image to use for unselected and selected items, respectively. If -`image` > -1 and `selImage` is -1, the same image is used for both selected and -unselected items. +specifying the image to use for unselected and selected items, respectively. If `image` > +-1 and `selImage` is -1, the same image is used for both selected and unselected items. """. -spec addRoot(This, Text, [Option]) -> integer() when This::wxTreeCtrl(), Text::unicode:chardata(), @@ -233,7 +298,7 @@ addRoot(#wx_ref{type=ThisT}=This,Text, Options) wxe_util:queue_cmd(This,Text_UC, Opts,?get_env(),?wxTreeCtrl_AddRoot), wxe_util:rec(?wxTreeCtrl_AddRoot). -%% @equiv appendItem(This,Parent,Text, []) +-doc(#{equiv => appendItem(This,Parent,Text, [])}). -spec appendItem(This, Parent, Text) -> integer() when This::wxTreeCtrl(), Parent::integer(), Text::unicode:chardata(). @@ -241,15 +306,12 @@ appendItem(This,Parent,Text) when is_record(This, wx_ref),is_integer(Parent),?is_chardata(Text) -> appendItem(This,Parent,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlappenditem">external documentation</a>. -doc """ -Appends an item to the end of the branch identified by `parent`, return a new -item id. +Appends an item to the end of the branch identified by `parent`, return a new item id. The `image` and `selImage` parameters are an index within the normal image list -specifying the image to use for unselected and selected items, respectively. If -`image` > -1 and `selImage` is -1, the same image is used for both selected and -unselected items. +specifying the image to use for unselected and selected items, respectively. If `image` > +-1 and `selImage` is -1, the same image is used for both selected and unselected items. """. -spec appendItem(This, Parent, Text, [Option]) -> integer() when This::wxTreeCtrl(), Parent::integer(), Text::unicode:chardata(), @@ -268,12 +330,11 @@ appendItem(#wx_ref{type=ThisT}=This,Parent,Text, Options) wxe_util:queue_cmd(This,Parent,Text_UC, Opts,?get_env(),?wxTreeCtrl_AppendItem), wxe_util:rec(?wxTreeCtrl_AppendItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlassignimagelist">external documentation</a>. -doc """ Sets the normal image list. -The image list assigned with this method will be automatically deleted by -`m:wxTreeCtrl` as appropriate (i.e. it takes ownership of the list). +The image list assigned with this method will be automatically deleted by `m:wxTreeCtrl` +as appropriate (i.e. it takes ownership of the list). See: `setImageList/2` """. @@ -284,12 +345,11 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreeCtrl_AssignImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlassignstateimagelist">external documentation</a>. -doc """ Sets the state image list. -Image list assigned with this method will be automatically deleted by -`m:wxTreeCtrl` as appropriate (i.e. it takes ownership of the list). +Image list assigned with this method will be automatically deleted by `m:wxTreeCtrl` as +appropriate (i.e. it takes ownership of the list). See: `setStateImageList/2` """. @@ -300,7 +360,6 @@ assignStateImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreeCtrl_AssignStateImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlcollapse">external documentation</a>. -doc "Collapses the given item.". -spec collapse(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -309,7 +368,6 @@ collapse(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_Collapse). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlcollapseandreset">external documentation</a>. -doc "Collapses the given item and removes all children.". -spec collapseAndReset(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -318,7 +376,7 @@ collapseAndReset(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_CollapseAndReset). -%% @equiv create(This,Parent, []) +-doc(#{equiv => create(This,Parent, [])}). -spec create(This, Parent) -> boolean() when This::wxTreeCtrl(), Parent::wxWindow:wxWindow(). @@ -326,7 +384,6 @@ create(This,Parent) when is_record(This, wx_ref),is_record(Parent, wx_ref) -> create(This,Parent, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlcreate">external documentation</a>. -doc """ Creates the tree control. @@ -353,7 +410,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent, Options) wxe_util:queue_cmd(This,Parent, Opts,?get_env(),?wxTreeCtrl_Create), wxe_util:rec(?wxTreeCtrl_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrldelete">external documentation</a>. -doc """ Deletes the specified item. @@ -368,13 +424,11 @@ delete(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_Delete). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrldeleteallitems">external documentation</a>. -doc """ Deletes all items in the control. -This function generates `wxEVT_TREE_DELETE_ITEM` events for each item being -deleted, including the root one if it is shown, i.e. unless wxTR_HIDE_ROOT style -is used. +This function generates `wxEVT_TREE_DELETE_ITEM` events for each item being deleted, +including the root one if it is shown, i.e. unless wxTR_HIDE_ROOT style is used. """. -spec deleteAllItems(This) -> 'ok' when This::wxTreeCtrl(). @@ -382,14 +436,13 @@ deleteAllItems(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_DeleteAllItems). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrldeletechildren">external documentation</a>. -doc """ Deletes all children of the given item (but not the item itself). A `wxEVT_TREE_DELETE_ITEM` event will be generated for every item being deleted. -If you have called `setItemHasChildren/3`, you may need to call it again since -`deleteChildren/2` does not automatically clear the setting. +If you have called `setItemHasChildren/3`, you may need to call it again since `deleteChildren/2` does not automatically clear +the setting. """. -spec deleteChildren(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -398,18 +451,16 @@ deleteChildren(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_DeleteChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrleditlabel">external documentation</a>. -doc """ Starts editing the label of the given `item`. -This function generates a `EVT_TREE_BEGIN_LABEL_EDIT` event which can be vetoed -so that no text control will appear for in-place editing. +This function generates a `EVT_TREE_BEGIN_LABEL_EDIT` event which can be vetoed so that +no text control will appear for in-place editing. -If the user changed the label (i.e. s/he does not press ESC or leave the text -control without changes, a `EVT_TREE_END_LABEL_EDIT` event will be sent which -can be vetoed as well. +If the user changed the label (i.e. s/he does not press ESC or leave the text control +without changes, a `EVT_TREE_END_LABEL_EDIT` event will be sent which can be vetoed as well. -See: `EndEditLabel()` (not implemented in wx), `m:wxTreeEvent` +See: `m:wxTreeEvent` """. -spec editLabel(This, Item) -> wxTextCtrl:wxTextCtrl() when This::wxTreeCtrl(), Item::integer(). @@ -419,12 +470,10 @@ editLabel(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_EditLabel), wxe_util:rec(?wxTreeCtrl_EditLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlensurevisible">external documentation</a>. -doc """ Scrolls and/or expands items to ensure that the given item is visible. -This method can be used, and will work, even while the window is frozen (see -`wxWindow:freeze/1`). +This method can be used, and will work, even while the window is frozen (see `wxWindow:freeze/1`). """. -spec ensureVisible(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -433,7 +482,6 @@ ensureVisible(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_EnsureVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlexpand">external documentation</a>. -doc "Expands the given item.". -spec expand(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -442,7 +490,7 @@ expand(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_Expand). -%% @equiv getBoundingRect(This,Item, []) +-doc(#{equiv => getBoundingRect(This,Item, [])}). -spec getBoundingRect(This, Item) -> Result when Result ::{Res ::boolean(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}}, This::wxTreeCtrl(), Item::integer(). @@ -451,20 +499,18 @@ getBoundingRect(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getBoundingRect(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetboundingrect">external documentation</a>. -doc """ Retrieves the rectangle bounding the `item`. -If `textOnly` is true, only the rectangle around the item's label will be -returned, otherwise the item's image is also taken into account. +If `textOnly` is true, only the rectangle around the item's label will be returned, +otherwise the item's image is also taken into account. -The return value is true if the rectangle was successfully retrieved or false if -it was not (in this case `rect` is not changed) - for example, if the item is -currently invisible. +The return value is true if the rectangle was successfully retrieved or false if it was +not (in this case `rect` is not changed) - for example, if the item is currently invisible. -Notice that the rectangle coordinates are logical, not physical ones. So, for -example, the x coordinate may be negative if the tree has a horizontal scrollbar -and its position is not 0. +Notice that the rectangle coordinates are logical, not physical ones. So, for example, +the x coordinate may be negative if the tree has a horizontal scrollbar and its position +is not 0. """. -spec getBoundingRect(This, Item, [Option]) -> Result when Result :: {Res ::boolean(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}}, @@ -479,7 +525,7 @@ getBoundingRect(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_GetBoundingRect), wxe_util:rec(?wxTreeCtrl_GetBoundingRect). -%% @equiv getChildrenCount(This,Item, []) +-doc(#{equiv => getChildrenCount(This,Item, [])}). -spec getChildrenCount(This, Item) -> integer() when This::wxTreeCtrl(), Item::integer(). @@ -487,12 +533,11 @@ getChildrenCount(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getChildrenCount(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetchildrencount">external documentation</a>. -doc """ Returns the number of items in the branch. -If `recursively` is true, returns the total number of descendants, otherwise -only one level of children is counted. +If `recursively` is true, returns the total number of descendants, otherwise only one +level of children is counted. """. -spec getChildrenCount(This, Item, [Option]) -> integer() when This::wxTreeCtrl(), Item::integer(), @@ -506,7 +551,6 @@ getChildrenCount(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_GetChildrenCount), wxe_util:rec(?wxTreeCtrl_GetChildrenCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetcount">external documentation</a>. -doc "Returns the number of items in the control.". -spec getCount(This) -> integer() when This::wxTreeCtrl(). @@ -515,7 +559,6 @@ getCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetCount), wxe_util:rec(?wxTreeCtrl_GetCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgeteditcontrol">external documentation</a>. -doc """ Returns the edit control being currently used to edit a label. @@ -530,20 +573,21 @@ getEditControl(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetEditControl), wxe_util:rec(?wxTreeCtrl_GetEditControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetfirstchild">external documentation</a>. -doc """ Returns the first child; call `getNextChild/3` for the next child. -For this enumeration function you must pass in a 'cookie' parameter which is -opaque for the application but is necessary for the library to make these -functions reentrant (i.e. allow more than one enumeration on one and the same -object simultaneously). The cookie passed to `getFirstChild/2` and -`getNextChild/3` should be the same variable. +For this enumeration function you must pass in a 'cookie' parameter which is opaque for +the application but is necessary for the library to make these functions reentrant (i.e. +allow more than one enumeration on one and the same object simultaneously). The cookie +passed to `getFirstChild/2` and `getNextChild/3` should be the same variable. + +Returns an invalid tree item (i.e. `wxTreeItemId::IsOk()` (not implemented in wx) returns +false) if there are no further children. -Returns an invalid tree item (i.e. `wxTreeItemId::IsOk()` (not implemented in -wx) returns false) if there are no further children. +See: +* `getNextChild/3` -See: `getNextChild/3`, `getNextSibling/2` +* `getNextSibling/2` """. -spec getFirstChild(This, Item) -> Result when Result ::{Res ::integer(), Cookie::integer()}, @@ -554,15 +598,13 @@ getFirstChild(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetFirstChild), wxe_util:rec(?wxTreeCtrl_GetFirstChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetnextchild">external documentation</a>. -doc """ Returns the next child; call `getFirstChild/2` for the first child. -For this enumeration function you must pass in a 'cookie' parameter which is -opaque for the application but is necessary for the library to make these -functions reentrant (i.e. allow more than one enumeration on one and the same -object simultaneously). The cookie passed to `getFirstChild/2` and -`getNextChild/3` should be the same. +For this enumeration function you must pass in a 'cookie' parameter which is opaque for +the application but is necessary for the library to make these functions reentrant (i.e. +allow more than one enumeration on one and the same object simultaneously). The cookie +passed to `getFirstChild/2` and `getNextChild/3` should be the same. Returns an invalid tree item if there are no further children. @@ -577,7 +619,6 @@ getNextChild(#wx_ref{type=ThisT}=This,Item,Cookie) wxe_util:queue_cmd(This,Item,Cookie,?get_env(),?wxTreeCtrl_GetNextChild), wxe_util:rec(?wxTreeCtrl_GetNextChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetfirstvisibleitem">external documentation</a>. -doc "Returns the first visible item.". -spec getFirstVisibleItem(This) -> integer() when This::wxTreeCtrl(). @@ -586,7 +627,6 @@ getFirstVisibleItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetFirstVisibleItem), wxe_util:rec(?wxTreeCtrl_GetFirstVisibleItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetimagelist">external documentation</a>. -doc "Returns the normal image list.". -spec getImageList(This) -> wxImageList:wxImageList() when This::wxTreeCtrl(). @@ -595,7 +635,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetImageList), wxe_util:rec(?wxTreeCtrl_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetindent">external documentation</a>. -doc "Returns the current tree control indentation.". -spec getIndent(This) -> integer() when This::wxTreeCtrl(). @@ -604,7 +643,6 @@ getIndent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetIndent), wxe_util:rec(?wxTreeCtrl_GetIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitembackgroundcolour">external documentation</a>. -doc "Returns the background colour of the item.". -spec getItemBackgroundColour(This, Item) -> wx:wx_colour4() when This::wxTreeCtrl(), Item::integer(). @@ -614,12 +652,7 @@ getItemBackgroundColour(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemBackgroundColour), wxe_util:rec(?wxTreeCtrl_GetItemBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemdata">external documentation</a>. --doc """ -Returns the tree item data associated with the item. - -See: `wxTreeItemData` (not implemented in wx) -""". +-doc "Returns the tree item data associated with the item.". -spec getItemData(This, Item) -> term() when This::wxTreeCtrl(), Item::integer(). getItemData(#wx_ref{type=ThisT}=This,Item) @@ -628,14 +661,12 @@ getItemData(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemData), wxe_util:rec(?wxTreeCtrl_GetItemData). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemfont">external documentation</a>. -doc """ Returns the font of the item label. -If the font hadn't been explicitly set for the specified `item` with -`setItemFont/3`, returns an invalid ?wxNullFont font. `wxWindow:getFont/1` can -be used to retrieve the global tree control font used for the items without any -specific font. +If the font hadn't been explicitly set for the specified `item` with `setItemFont/3`, returns an invalid +?wxNullFont font. `wxWindow:getFont/1` can be used to retrieve the global tree control font used for the items +without any specific font. """. -spec getItemFont(This, Item) -> wxFont:wxFont() when This::wxTreeCtrl(), Item::integer(). @@ -645,7 +676,7 @@ getItemFont(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemFont), wxe_util:rec(?wxTreeCtrl_GetItemFont). -%% @equiv getItemImage(This,Item, []) +-doc(#{equiv => getItemImage(This,Item, [])}). -spec getItemImage(This, Item) -> integer() when This::wxTreeCtrl(), Item::integer(). @@ -653,13 +684,24 @@ getItemImage(This,Item) when is_record(This, wx_ref),is_integer(Item) -> getItemImage(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemimage">external documentation</a>. -%%<br /> Which = ?wxTreeItemIcon_Normal | ?wxTreeItemIcon_Selected | ?wxTreeItemIcon_Expanded | ?wxTreeItemIcon_SelectedExpanded | ?wxTreeItemIcon_Max -doc """ Gets the specified item image. The value of `which` may be: + +* ?wxTreeItemIcon\_Normal: to get the normal item image. + +* ?wxTreeItemIcon\_Selected: to get the selected item image (i.e. the image which is shown +when the item is currently selected). + +* ?wxTreeItemIcon\_Expanded: to get the expanded image (this only makes sense for items +which have children - then this image is shown when the item is expanded and the normal +image is shown when it is collapsed). + +* ?wxTreeItemIcon\_SelectedExpanded: to get the selected expanded image (which is shown +when an expanded item is currently selected). """. +%% Which = ?wxTreeItemIcon_Normal | ?wxTreeItemIcon_Selected | ?wxTreeItemIcon_Expanded | ?wxTreeItemIcon_SelectedExpanded | ?wxTreeItemIcon_Max -spec getItemImage(This, Item, [Option]) -> integer() when This::wxTreeCtrl(), Item::integer(), Option :: {'which', wx:wx_enum()}. @@ -672,7 +714,6 @@ getItemImage(#wx_ref{type=ThisT}=This,Item, Options) wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_GetItemImage), wxe_util:rec(?wxTreeCtrl_GetItemImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemtext">external documentation</a>. -doc "Returns the item label.". -spec getItemText(This, Item) -> unicode:charlist() when This::wxTreeCtrl(), Item::integer(). @@ -682,7 +723,6 @@ getItemText(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemText), wxe_util:rec(?wxTreeCtrl_GetItemText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemtextcolour">external documentation</a>. -doc "Returns the colour of the item label.". -spec getItemTextColour(This, Item) -> wx:wx_colour4() when This::wxTreeCtrl(), Item::integer(). @@ -692,12 +732,16 @@ getItemTextColour(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemTextColour), wxe_util:rec(?wxTreeCtrl_GetItemTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetlastchild">external documentation</a>. -doc """ Returns the last child of the item (or an invalid tree item if this item has no children). -See: `getFirstChild/2`, `getNextSibling/2`, `getLastChild/2` +See: +* `getFirstChild/2` + +* `getNextSibling/2` + +* `getLastChild/2` """. -spec getLastChild(This, Item) -> integer() when This::wxTreeCtrl(), Item::integer(). @@ -707,10 +751,9 @@ getLastChild(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetLastChild), wxe_util:rec(?wxTreeCtrl_GetLastChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetnextsibling">external documentation</a>. -doc """ -Returns the next sibling of the specified item; call `getPrevSibling/2` for the -previous sibling. +Returns the next sibling of the specified item; call `getPrevSibling/2` for the previous +sibling. Returns an invalid tree item if there are no further siblings. @@ -724,10 +767,8 @@ getNextSibling(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetNextSibling), wxe_util:rec(?wxTreeCtrl_GetNextSibling). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetnextvisible">external documentation</a>. -doc """ -Returns the next visible item or an invalid item if this item is the last -visible one. +Returns the next visible item or an invalid item if this item is the last visible one. Note: The `item` itself must be visible. """. @@ -739,7 +780,6 @@ getNextVisible(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetNextVisible), wxe_util:rec(?wxTreeCtrl_GetNextVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetitemparent">external documentation</a>. -doc "Returns the item's parent.". -spec getItemParent(This, Item) -> integer() when This::wxTreeCtrl(), Item::integer(). @@ -749,10 +789,9 @@ getItemParent(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetItemParent), wxe_util:rec(?wxTreeCtrl_GetItemParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetprevsibling">external documentation</a>. -doc """ -Returns the previous sibling of the specified item; call `getNextSibling/2` for -the next sibling. +Returns the previous sibling of the specified item; call `getNextSibling/2` for the next +sibling. Returns an invalid tree item if there are no further children. @@ -766,10 +805,9 @@ getPrevSibling(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetPrevSibling), wxe_util:rec(?wxTreeCtrl_GetPrevSibling). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetprevvisible">external documentation</a>. -doc """ -Returns the previous visible item or an invalid item if this item is the first -visible one. +Returns the previous visible item or an invalid item if this item is the first visible +one. Note: The `item` itself must be visible. """. @@ -781,7 +819,6 @@ getPrevVisible(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_GetPrevVisible), wxe_util:rec(?wxTreeCtrl_GetPrevVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetrootitem">external documentation</a>. -doc "Returns the root item for the tree control.". -spec getRootItem(This) -> integer() when This::wxTreeCtrl(). @@ -790,13 +827,12 @@ getRootItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetRootItem), wxe_util:rec(?wxTreeCtrl_GetRootItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetselection">external documentation</a>. -doc """ Returns the selection, or an invalid item if there is no selection. -This function only works with the controls without `wxTR_MULTIPLE` style, use -`getSelections/1` for the controls which do have this style or, if a single item -is wanted, use `GetFocusedItem()` (not implemented in wx). +This function only works with the controls without `wxTR_MULTIPLE` style, use `getSelections/1` for the +controls which do have this style or, if a single item is wanted, use `GetFocusedItem()` +(not implemented in wx). """. -spec getSelection(This) -> integer() when This::wxTreeCtrl(). @@ -805,7 +841,6 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetSelection), wxe_util:rec(?wxTreeCtrl_GetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetselections">external documentation</a>. -doc """ Fills the array of tree items passed in with the currently selected items. @@ -821,11 +856,7 @@ getSelections(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetSelections), wxe_util:rec(?wxTreeCtrl_GetSelections). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlgetstateimagelist">external documentation</a>. --doc """ -Returns the state image list (from which application-defined state images are -taken). -""". +-doc "Returns the state image list (from which application-defined state images are taken).". -spec getStateImageList(This) -> wxImageList:wxImageList() when This::wxTreeCtrl(). getStateImageList(#wx_ref{type=ThisT}=This) -> @@ -833,12 +864,34 @@ getStateImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_GetStateImageList), wxe_util:rec(?wxTreeCtrl_GetStateImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlhittest">external documentation</a>. -doc """ -Calculates which (if any) item is under the given `point`, returning the tree -item id at this point plus extra information `flags`. +Calculates which (if any) item is under the given `point`, returning the tree item id at +this point plus extra information `flags`. `flags` is a bitlist of the following: + +* `wxTREE_HITTEST_ABOVE:` Above the client area. + +* `wxTREE_HITTEST_BELOW:` Below the client area. + +* `wxTREE_HITTEST_NOWHERE:` In the client area but below the last item. + +* `wxTREE_HITTEST_ONITEMBUTTON:` On the button associated with an item. + +* `wxTREE_HITTEST_ONITEMICON:` On the bitmap associated with an item. + +* `wxTREE_HITTEST_ONITEMINDENT:` In the indentation associated with an item. + +* `wxTREE_HITTEST_ONITEMLABEL:` On the label (string) associated with an item. + +* `wxTREE_HITTEST_ONITEMRIGHT:` In the area to the right of an item. + +* `wxTREE_HITTEST_ONITEMSTATEICON:` On the state icon for a tree view item that is in a +user-defined state. + +* `wxTREE_HITTEST_TOLEFT:` To the right of the client area. + +* `wxTREE_HITTEST_TORIGHT:` To the left of the client area. """. -spec hitTest(This, Point) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -849,7 +902,7 @@ hitTest(#wx_ref{type=ThisT}=This,{PointX,PointY} = Point) wxe_util:queue_cmd(This,Point,?get_env(),?wxTreeCtrl_HitTest), wxe_util:rec(?wxTreeCtrl_HitTest). -%% @equiv insertItem(This,Parent,Previous,Text, []) +-doc(#{equiv => insertItem(This,Parent,Previous,Text, [])}). -spec insertItem(This, Parent, Previous, Text) -> integer() when This::wxTreeCtrl(), Parent::integer(), Previous::integer(), Text::unicode:chardata(). @@ -857,14 +910,12 @@ insertItem(This,Parent,Previous,Text) when is_record(This, wx_ref),is_integer(Parent),is_integer(Previous),?is_chardata(Text) -> insertItem(This,Parent,Previous,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlinsertitem">external documentation</a>. -doc """ Inserts an item after a given one (`previous`). The `image` and `selImage` parameters are an index within the normal image list -specifying the image to use for unselected and selected items, respectively. If -`image` > -1 and `selImage` is -1, the same image is used for both selected and -unselected items. +specifying the image to use for unselected and selected items, respectively. If `image` > +-1 and `selImage` is -1, the same image is used for both selected and unselected items. """. -spec insertItem(This, Parent, Previous, Text, [Option]) -> integer() when This::wxTreeCtrl(), Parent::integer(), Previous::integer(), Text::unicode:chardata(), @@ -883,7 +934,6 @@ insertItem(#wx_ref{type=ThisT}=This,Parent,Previous,Text, Options) wxe_util:queue_cmd(This,Parent,Previous,Text_UC, Opts,?get_env(),?wxTreeCtrl_InsertItem), wxe_util:rec(?wxTreeCtrl_InsertItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlisbold">external documentation</a>. -doc """ Returns true if the given item is in bold state. @@ -897,7 +947,6 @@ isBold(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_IsBold), wxe_util:rec(?wxTreeCtrl_IsBold). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlisexpanded">external documentation</a>. -doc "Returns true if the item is expanded (only makes sense if it has children).". -spec isExpanded(This, Item) -> boolean() when This::wxTreeCtrl(), Item::integer(). @@ -907,7 +956,6 @@ isExpanded(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_IsExpanded), wxe_util:rec(?wxTreeCtrl_IsExpanded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlisselected">external documentation</a>. -doc "Returns true if the item is selected.". -spec isSelected(This, Item) -> boolean() when This::wxTreeCtrl(), Item::integer(). @@ -917,7 +965,6 @@ isSelected(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_IsSelected), wxe_util:rec(?wxTreeCtrl_IsSelected). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlisvisible">external documentation</a>. -doc "Returns true if the item is visible on the screen.". -spec isVisible(This, Item) -> boolean() when This::wxTreeCtrl(), Item::integer(). @@ -927,7 +974,6 @@ isVisible(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_IsVisible), wxe_util:rec(?wxTreeCtrl_IsVisible). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlitemhaschildren">external documentation</a>. -doc "Returns true if the item has children.". -spec itemHasChildren(This, Item) -> boolean() when This::wxTreeCtrl(), Item::integer(). @@ -937,7 +983,6 @@ itemHasChildren(#wx_ref{type=ThisT}=This,Item) wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_ItemHasChildren), wxe_util:rec(?wxTreeCtrl_ItemHasChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlistreeitemidok">external documentation</a>. -doc "Returns true if the item is valid.". -spec isTreeItemIdOk(Item) -> boolean() when Item::integer(). @@ -946,7 +991,7 @@ isTreeItemIdOk(Item) wxe_util:queue_cmd(Item,?get_env(),?wxTreeCtrl_IsTreeItemIdOk), wxe_util:rec(?wxTreeCtrl_IsTreeItemIdOk). -%% @equiv prependItem(This,Parent,Text, []) +-doc(#{equiv => prependItem(This,Parent,Text, [])}). -spec prependItem(This, Parent, Text) -> integer() when This::wxTreeCtrl(), Parent::integer(), Text::unicode:chardata(). @@ -954,14 +999,12 @@ prependItem(This,Parent,Text) when is_record(This, wx_ref),is_integer(Parent),?is_chardata(Text) -> prependItem(This,Parent,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlprependitem">external documentation</a>. -doc """ Appends an item as the first child of `parent`, return a new item id. The `image` and `selImage` parameters are an index within the normal image list -specifying the image to use for unselected and selected items, respectively. If -`image` > -1 and `selImage` is -1, the same image is used for both selected and -unselected items. +specifying the image to use for unselected and selected items, respectively. If `image` > +-1 and `selImage` is -1, the same image is used for both selected and unselected items. """. -spec prependItem(This, Parent, Text, [Option]) -> integer() when This::wxTreeCtrl(), Parent::integer(), Text::unicode:chardata(), @@ -980,12 +1023,10 @@ prependItem(#wx_ref{type=ThisT}=This,Parent,Text, Options) wxe_util:queue_cmd(This,Parent,Text_UC, Opts,?get_env(),?wxTreeCtrl_PrependItem), wxe_util:rec(?wxTreeCtrl_PrependItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlscrollto">external documentation</a>. -doc """ Scrolls the specified item into view. -Note that this method doesn't work while the window is frozen (See -`wxWindow:freeze/1`), at least under MSW. +Note that this method doesn't work while the window is frozen (See `wxWindow:freeze/1`), at least under MSW. See: `ensureVisible/2` """. @@ -996,7 +1037,7 @@ scrollTo(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_ScrollTo). -%% @equiv selectItem(This,Item, []) +-doc(#{equiv => selectItem(This,Item, [])}). -spec selectItem(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1004,16 +1045,14 @@ selectItem(This,Item) when is_record(This, wx_ref),is_integer(Item) -> selectItem(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlselectitem">external documentation</a>. -doc """ Selects the given item. -In multiple selection controls, can be also used to deselect a currently -selected item if the value of `select` is false. +In multiple selection controls, can be also used to deselect a currently selected item if +the value of `select` is false. -Notice that calling this method will generate `wxEVT_TREE_SEL_CHANGING` and -`wxEVT_TREE_SEL_CHANGED` events and that the change could be vetoed by the -former event handler. +Notice that calling this method will generate `wxEVT_TREE_SEL_CHANGING` and `wxEVT_TREE_SEL_CHANGED` +events and that the change could be vetoed by the former event handler. """. -spec selectItem(This, Item, [Option]) -> 'ok' when This::wxTreeCtrl(), Item::integer(), @@ -1026,7 +1065,6 @@ selectItem(#wx_ref{type=ThisT}=This,Item, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_SelectItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetindent">external documentation</a>. -doc "Sets the indentation for the tree control.". -spec setIndent(This, Indent) -> 'ok' when This::wxTreeCtrl(), Indent::integer(). @@ -1035,12 +1073,11 @@ setIndent(#wx_ref{type=ThisT}=This,Indent) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Indent,?get_env(),?wxTreeCtrl_SetIndent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetimagelist">external documentation</a>. -doc """ Sets the normal image list. -The image list assigned with this method will `not` be deleted by -`m:wxTreeCtrl`'s destructor, you must delete it yourself. +The image list assigned with this method will `not` be deleted by `m:wxTreeCtrl`'s +destructor, you must delete it yourself. See: `assignImageList/2` """. @@ -1051,7 +1088,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreeCtrl_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitembackgroundcolour">external documentation</a>. -doc "Sets the colour of the item's background.". -spec setItemBackgroundColour(This, Item, Col) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Col::wx:wx_colour(). @@ -1060,7 +1096,7 @@ setItemBackgroundColour(#wx_ref{type=ThisT}=This,Item,Col) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,wxe_util:color(Col),?get_env(),?wxTreeCtrl_SetItemBackgroundColour). -%% @equiv setItemBold(This,Item, []) +-doc(#{equiv => setItemBold(This,Item, [])}). -spec setItemBold(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1068,10 +1104,9 @@ setItemBold(This,Item) when is_record(This, wx_ref),is_integer(Item) -> setItemBold(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitembold">external documentation</a>. -doc """ -Makes item appear in bold font if `bold` parameter is true or resets it to the -normal state. +Makes item appear in bold font if `bold` parameter is true or resets it to the normal +state. See: `isBold/2` """. @@ -1086,14 +1121,12 @@ setItemBold(#wx_ref{type=ThisT}=This,Item, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_SetItemBold). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemdata">external documentation</a>. -doc """ Sets the item client data. -Notice that the client data previously associated with the `item` (if any) is -`not` freed by this function and so calling this function multiple times for the -same item will result in memory leaks unless you delete the old item data -pointer yourself. +Notice that the client data previously associated with the `item` (if any) is `not` freed +by this function and so calling this function multiple times for the same item will result +in memory leaks unless you delete the old item data pointer yourself. """. -spec setItemData(This, Item, Data) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Data::term(). @@ -1102,7 +1135,7 @@ setItemData(#wx_ref{type=ThisT}=This,Item,Data) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,Data,?get_env(),?wxTreeCtrl_SetItemData). -%% @equiv setItemDropHighlight(This,Item, []) +-doc(#{equiv => setItemDropHighlight(This,Item, [])}). -spec setItemDropHighlight(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1110,11 +1143,10 @@ setItemDropHighlight(This,Item) when is_record(This, wx_ref),is_integer(Item) -> setItemDropHighlight(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemdrophighlight">external documentation</a>. -doc """ -Gives the item the visual feedback for Drag'n'Drop actions, which is useful if -something is dragged from the outside onto the tree control (as opposed to a DnD -operation within the tree control, which already is implemented internally). +Gives the item the visual feedback for Drag'n'Drop actions, which is useful if something +is dragged from the outside onto the tree control (as opposed to a DnD operation within +the tree control, which already is implemented internally). """. -spec setItemDropHighlight(This, Item, [Option]) -> 'ok' when This::wxTreeCtrl(), Item::integer(), @@ -1127,13 +1159,11 @@ setItemDropHighlight(#wx_ref{type=ThisT}=This,Item, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_SetItemDropHighlight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemfont">external documentation</a>. -doc """ Sets the item's font. -All items in the tree should have the same height to avoid text clipping, so the -fonts height should be the same for all of them, although font attributes may -vary. +All items in the tree should have the same height to avoid text clipping, so the fonts +height should be the same for all of them, although font attributes may vary. See: `setItemBold/3` """. @@ -1145,7 +1175,7 @@ setItemFont(#wx_ref{type=ThisT}=This,Item,#wx_ref{type=FontT}=Font) ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Item,Font,?get_env(),?wxTreeCtrl_SetItemFont). -%% @equiv setItemHasChildren(This,Item, []) +-doc(#{equiv => setItemHasChildren(This,Item, [])}). -spec setItemHasChildren(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1153,13 +1183,11 @@ setItemHasChildren(This,Item) when is_record(This, wx_ref),is_integer(Item) -> setItemHasChildren(This,Item, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemhaschildren">external documentation</a>. -doc """ Force appearance of the button next to the item. -This is useful to allow the user to expand the items which don't have any -children now, but instead adding them only when needed, thus minimizing memory -usage and loading time. +This is useful to allow the user to expand the items which don't have any children now, +but instead adding them only when needed, thus minimizing memory usage and loading time. """. -spec setItemHasChildren(This, Item, [Option]) -> 'ok' when This::wxTreeCtrl(), Item::integer(), @@ -1172,7 +1200,7 @@ setItemHasChildren(#wx_ref{type=ThisT}=This,Item, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item, Opts,?get_env(),?wxTreeCtrl_SetItemHasChildren). -%% @equiv setItemImage(This,Item,Image, []) +-doc(#{equiv => setItemImage(This,Item,Image, [])}). -spec setItemImage(This, Item, Image) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Image::integer(). @@ -1180,13 +1208,12 @@ setItemImage(This,Item,Image) when is_record(This, wx_ref),is_integer(Item),is_integer(Image) -> setItemImage(This,Item,Image, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemimage">external documentation</a>. -%%<br /> Which = ?wxTreeItemIcon_Normal | ?wxTreeItemIcon_Selected | ?wxTreeItemIcon_Expanded | ?wxTreeItemIcon_SelectedExpanded | ?wxTreeItemIcon_Max -doc """ Sets the specified item's image. See `getItemImage/3` for the description of the `which` parameter. """. +%% Which = ?wxTreeItemIcon_Normal | ?wxTreeItemIcon_Selected | ?wxTreeItemIcon_Expanded | ?wxTreeItemIcon_SelectedExpanded | ?wxTreeItemIcon_Max -spec setItemImage(This, Item, Image, [Option]) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Image::integer(), Option :: {'which', wx:wx_enum()}. @@ -1198,7 +1225,6 @@ setItemImage(#wx_ref{type=ThisT}=This,Item,Image, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Item,Image, Opts,?get_env(),?wxTreeCtrl_SetItemImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemtext">external documentation</a>. -doc "Sets the item label.". -spec setItemText(This, Item, Text) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Text::unicode:chardata(). @@ -1208,7 +1234,6 @@ setItemText(#wx_ref{type=ThisT}=This,Item,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Item,Text_UC,?get_env(),?wxTreeCtrl_SetItemText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetitemtextcolour">external documentation</a>. -doc "Sets the colour of the item's text.". -spec setItemTextColour(This, Item, Col) -> 'ok' when This::wxTreeCtrl(), Item::integer(), Col::wx:wx_colour(). @@ -1217,10 +1242,8 @@ setItemTextColour(#wx_ref{type=ThisT}=This,Item,Col) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,wxe_util:color(Col),?get_env(),?wxTreeCtrl_SetItemTextColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetstateimagelist">external documentation</a>. -doc """ -Sets the state image list (from which application-defined state images are -taken). +Sets the state image list (from which application-defined state images are taken). Image list assigned with this method will `not` be deleted by `m:wxTreeCtrl`'s destructor, you must delete it yourself. @@ -1234,7 +1257,6 @@ setStateImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) - ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreeCtrl_SetStateImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsetwindowstyle">external documentation</a>. -doc """ Sets the mode flags associated with the display of the tree control. @@ -1249,16 +1271,11 @@ setWindowStyle(#wx_ref{type=ThisT}=This,Styles) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Styles,?get_env(),?wxTreeCtrl_SetWindowStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlsortchildren">external documentation</a>. -doc """ -Sorts the children of the given item using `OnCompareItems()` (not implemented -in wx). - -You should override that method to change the sort order (the default is -ascending case-sensitive alphabetical order). +Sorts the children of the given item using `OnCompareItems()` (not implemented in wx). -See: `wxTreeItemData` (not implemented in wx), `OnCompareItems()` (not -implemented in wx) +You should override that method to change the sort order (the default is ascending +case-sensitive alphabetical order). """. -spec sortChildren(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1267,7 +1284,6 @@ sortChildren(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_SortChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrltoggle">external documentation</a>. -doc "Toggles the given item between collapsed and expanded states.". -spec toggle(This, Item) -> 'ok' when This::wxTreeCtrl(), Item::integer(). @@ -1276,7 +1292,6 @@ toggle(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_Toggle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrltoggleitemselection">external documentation</a>. -doc """ Toggles the given item between selected and unselected states. @@ -1289,7 +1304,6 @@ toggleItemSelection(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_ToggleItemSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlunselect">external documentation</a>. -doc "Removes the selection from the currently selected item (if any).". -spec unselect(This) -> 'ok' when This::wxTreeCtrl(). @@ -1297,11 +1311,9 @@ unselect(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_Unselect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlunselectall">external documentation</a>. -doc """ -This function either behaves the same as `unselect/1` if the control doesn't -have `wxTR_MULTIPLE` style, or removes the selection from all items if it does -have this style. +This function either behaves the same as `unselect/1` if the control doesn't have `wxTR\_MULTIPLE` +style, or removes the selection from all items if it does have this style. """. -spec unselectAll(This) -> 'ok' when This::wxTreeCtrl(). @@ -1309,7 +1321,6 @@ unselectAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,?get_env(),?wxTreeCtrl_UnselectAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreectrl.html#wxtreectrlunselectitem">external documentation</a>. -doc """ Unselects the given item. @@ -1322,559 +1333,376 @@ unselectItem(#wx_ref{type=ThisT}=This,Item) ?CLASS(ThisT,wxTreeCtrl), wxe_util:queue_cmd(This,Item,?get_env(),?wxTreeCtrl_UnselectItem). -%% @doc Destroys this object, do not use object again --doc "Destructor, destroying the tree control.". +-doc "Destroys the object". -spec destroy(This::wxTreeCtrl()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTreeCtrl), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxTreeEvent.erl b/lib/wx/src/gen/wxTreeEvent.erl index 4cbd03f1beb1..ff24d9df45f0 100644 --- a/lib/wx/src/gen/wxTreeEvent.erl +++ b/lib/wx/src/gen/wxTreeEvent.erl @@ -20,26 +20,26 @@ -module(wxTreeEvent). -moduledoc """ -Functions for wxTreeEvent class +A tree event holds information about events associated with `m:wxTreeCtrl` objects. -A tree event holds information about events associated with `m:wxTreeCtrl` -objects. - -To process input from a tree control, use these event handler macros to direct -input to member functions that take a `m:wxTreeEvent` argument. +To process input from a tree control, use these event handler macros to direct input to +member functions that take a `m:wxTreeEvent` argument. See: `m:wxTreeCtrl` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +This class is derived, and can use functions, from: + +* `m:wxNotifyEvent` + +* `m:wxCommandEvent` + +* `m:wxEvent` -wxWidgets docs: -[wxTreeEvent](https://docs.wxwidgets.org/3.1/classwx_tree_event.html) +wxWidgets docs: [wxTreeEvent](https://docs.wxwidgets.org/3.2/classwx_tree_event.html) ## Events -Use `wxEvtHandler:connect/3` with [`wxTreeEventType`](`t:wxTreeEventType/0`) to -subscribe to events of this type. +Use `wxEvtHandler:connect/3` with `wxTreeEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getItem/1,getKeyCode/1,getKeyEvent/1,getLabel/1,getOldItem/1,getPoint/1, @@ -55,19 +55,16 @@ subscribe to events of this type. -include("wx.hrl"). -type wxTreeEventType() :: 'command_tree_begin_drag' | 'command_tree_begin_rdrag' | 'command_tree_begin_label_edit' | 'command_tree_end_label_edit' | 'command_tree_delete_item' | 'command_tree_get_info' | 'command_tree_set_info' | 'command_tree_item_expanded' | 'command_tree_item_expanding' | 'command_tree_item_collapsed' | 'command_tree_item_collapsing' | 'command_tree_sel_changed' | 'command_tree_sel_changing' | 'command_tree_key_down' | 'command_tree_item_activated' | 'command_tree_item_right_click' | 'command_tree_item_middle_click' | 'command_tree_end_drag' | 'command_tree_state_image_click' | 'command_tree_item_gettooltip' | 'command_tree_item_menu' | 'dirctrl_selectionchanged' | 'dirctrl_fileactivated'. -export_type([wxTreeEvent/0, wxTree/0, wxTreeEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetkeycode">external documentation</a>. -doc """ Returns the key code if the event is a key event. -Use `getKeyEvent/1` to get the values of the modifier keys for this event (i.e. -Shift or Ctrl). +Use `getKeyEvent/1` to get the values of the modifier keys for this event (i.e. Shift or Ctrl). """. -spec getKeyCode(This) -> integer() when This::wxTreeEvent(). @@ -76,7 +73,6 @@ getKeyCode(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetKeyCode), wxe_util:rec(?wxTreeEvent_GetKeyCode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetitem">external documentation</a>. -doc "Returns the item (valid for all events).". -spec getItem(This) -> integer() when This::wxTreeEvent(). @@ -85,8 +81,7 @@ getItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetItem), wxe_util:rec(?wxTreeEvent_GetItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetkeyevent">external documentation</a>. --doc "Returns the key event for `EVT_TREE_KEY_DOWN` events.". +-doc "Returns the key event for `EVT\_TREE\_KEY\_DOWN` events.". -spec getKeyEvent(This) -> wxKeyEvent:wxKeyEvent() when This::wxTreeEvent(). getKeyEvent(#wx_ref{type=ThisT}=This) -> @@ -94,7 +89,6 @@ getKeyEvent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetKeyEvent), wxe_util:rec(?wxTreeEvent_GetKeyEvent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetlabel">external documentation</a>. -doc "Returns the label if the event is a begin or end edit label event.". -spec getLabel(This) -> unicode:charlist() when This::wxTreeEvent(). @@ -103,10 +97,9 @@ getLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetLabel), wxe_util:rec(?wxTreeEvent_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetolditem">external documentation</a>. -doc """ -Returns the old item index (valid for `EVT_TREE_SEL_CHANGING` and -`EVT_TREE_SEL_CHANGED` events). +Returns the old item index (valid for `EVT\_TREE\_SEL\_CHANGING` and `EVT\_TREE\_SEL\_CHANGED` +events). """. -spec getOldItem(This) -> integer() when This::wxTreeEvent(). @@ -115,14 +108,11 @@ getOldItem(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetOldItem), wxe_util:rec(?wxTreeEvent_GetOldItem). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventgetpoint">external documentation</a>. -doc """ -Returns the position of the mouse pointer if the event is a drag or menu-context -event. +Returns the position of the mouse pointer if the event is a drag or menu-context event. -In both cases the position is in client coordinates - i.e. relative to the -`m:wxTreeCtrl` window (so that you can pass it directly to e.g. -`wxWindow:popupMenu/4`). +In both cases the position is in client coordinates - i.e. relative to the `m:wxTreeCtrl` +window (so that you can pass it directly to e.g. `wxWindow:popupMenu/4`). """. -spec getPoint(This) -> {X::integer(), Y::integer()} when This::wxTreeEvent(). @@ -131,7 +121,6 @@ getPoint(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_GetPoint), wxe_util:rec(?wxTreeEvent_GetPoint). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventiseditcancelled">external documentation</a>. -doc """ Returns true if the label edit was cancelled. @@ -144,9 +133,8 @@ isEditCancelled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreeEvent_IsEditCancelled), wxe_util:rec(?wxTreeEvent_IsEditCancelled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreeevent.html#wxtreeeventsettooltip">external documentation</a>. -doc """ -Set the tooltip for the item (valid for `EVT_TREE_ITEM_GETTOOLTIP` events). +Set the tooltip for the item (valid for `EVT\_TREE\_ITEM\_GETTOOLTIP` events). Windows only. """. @@ -159,68 +147,47 @@ setToolTip(#wx_ref{type=ThisT}=This,Tooltip) wxe_util:queue_cmd(This,Tooltip_UC,?get_env(),?wxTreeEvent_SetToolTip). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxTreebook.erl b/lib/wx/src/gen/wxTreebook.erl index d194d4f3df24..eb040e45c0d5 100644 --- a/lib/wx/src/gen/wxTreebook.erl +++ b/lib/wx/src/gen/wxTreebook.erl @@ -20,36 +20,53 @@ -module(wxTreebook). -moduledoc """ -Functions for wxTreebook class +This class is an extension of the `m:wxNotebook` class that allows a tree structured set +of pages to be shown in a control. -This class is an extension of the `m:wxNotebook` class that allows a tree -structured set of pages to be shown in a control. A classic example is a -netscape preferences dialog that shows a tree of preference sections on the left -and select section page on the right. +A classic example is a netscape preferences dialog that shows a tree of preference +sections on the left and select section page on the right. -To use the class simply create it and populate with pages using `insertPage/5`, -`insertSubPage/5`, `addPage/4`, `AddSubPage()` (not implemented in wx). +To use the class simply create it and populate with pages using `insertPage/5`, `insertSubPage/5`, `addPage/4`, `AddSubPage()` (not +implemented in wx). -If your tree is no more than 1 level in depth then you could simply use -`addPage/4` and `AddSubPage()` (not implemented in wx) to sequentially populate -your tree by adding at every step a page or a subpage to the end of the tree. +If your tree is no more than 1 level in depth then you could simply use `addPage/4` and `AddSubPage()` +(not implemented in wx) to sequentially populate your tree by adding at every step a page +or a subpage to the end of the tree. -See: ?wxBookCtrl, `m:wxBookCtrlEvent`, `m:wxNotebook`, `m:wxTreeCtrl`, -`m:wxImageList`, -[Overview bookctrl](https://docs.wxwidgets.org/3.1/overview_bookctrl.html#overview_bookctrl), -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_notebook) +See: +* ?wxBookCtrl -This class is derived (and can use functions) from: `m:wxBookCtrlBase` -`m:wxControl` `m:wxWindow` `m:wxEvtHandler` +* `m:wxBookCtrlEvent` -wxWidgets docs: -[wxTreebook](https://docs.wxwidgets.org/3.1/classwx_treebook.html) +* `m:wxNotebook` + +* `m:wxTreeCtrl` + +* `m:wxImageList` + +* [Overview bookctrl](https://docs.wxwidgets.org/3.2/overview_bookctrl.html#overview_bookctrl) + +* [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_notebook) + +This class is derived, and can use functions, from: + +* `m:wxBookCtrlBase` + +* `m:wxControl` + +* `m:wxWindow` + +* `m:wxEvtHandler` + +wxWidgets docs: [wxTreebook](https://docs.wxwidgets.org/3.2/classwx_treebook.html) ## Events Event types emitted from this class: -[`treebook_page_changed`](`m:wxBookCtrlEvent`), -[`treebook_page_changing`](`m:wxBookCtrlEvent`) + +* [`treebook_page_changed`](`m:wxBookCtrlEvent`) + +* [`treebook_page_changing`](`m:wxBookCtrlEvent`) """. -include("wxe.hrl"). -export([addPage/3,addPage/4,advanceSelection/1,advanceSelection/2,assignImageList/2, @@ -102,7 +119,6 @@ Event types emitted from this class: -type wxTreebook() :: wx:wx_object(). -export_type([wxTreebook/0]). -%% @hidden -doc false. parent_class(wxBookCtrlBase) -> true; parent_class(wxControl) -> true; @@ -110,14 +126,13 @@ parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookwxtreebook">external documentation</a>. -doc "Default constructor.". -spec new() -> wxTreebook(). new() -> wxe_util:queue_cmd(?get_env(), ?wxTreebook_new_0), wxe_util:rec(?wxTreebook_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxTreebook() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -125,7 +140,6 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookwxtreebook">external documentation</a>. -doc "Creates an empty `m:wxTreebook`.". -spec new(Parent, Id, [Option]) -> wxTreebook() when Parent::wxWindow:wxWindow(), Id::integer(), @@ -143,7 +157,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxTreebook_new_3), wxe_util:rec(?wxTreebook_new_3). -%% @equiv addPage(This,Page,Text, []) +-doc(#{equiv => addPage(This,Page,Text, [])}). -spec addPage(This, Page, Text) -> boolean() when This::wxTreebook(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -151,12 +165,11 @@ addPage(This,Page,Text) when is_record(This, wx_ref),is_record(Page, wx_ref),?is_chardata(Text) -> addPage(This,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookaddpage">external documentation</a>. -doc """ Adds a new page. -The page is placed at the topmost level after all other pages. NULL could be -specified for page to create an empty page. +The page is placed at the topmost level after all other pages. NULL could be specified +for page to create an empty page. """. -spec addPage(This, Page, Text, [Option]) -> boolean() when This::wxTreebook(), Page::wxWindow:wxWindow(), Text::unicode:chardata(), @@ -174,7 +187,7 @@ addPage(#wx_ref{type=ThisT}=This,#wx_ref{type=PageT}=Page,Text, Options) wxe_util:queue_cmd(This,Page,Text_UC, Opts,?get_env(),?wxTreebook_AddPage), wxe_util:rec(?wxTreebook_AddPage). -%% @equiv advanceSelection(This, []) +-doc(#{equiv => advanceSelection(This, [])}). -spec advanceSelection(This) -> 'ok' when This::wxTreebook(). @@ -182,7 +195,6 @@ advanceSelection(This) when is_record(This, wx_ref) -> advanceSelection(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookadvanceselection">external documentation</a>. -doc """ Cycles through the tabs. @@ -199,11 +211,13 @@ advanceSelection(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxTreebook_AdvanceSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookassignimagelist">external documentation</a>. -doc """ Sets the image list for the page control and takes ownership of the list. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec assignImageList(This, ImageList) -> 'ok' when This::wxTreebook(), ImageList::wxImageList:wxImageList(). @@ -212,7 +226,7 @@ assignImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreebook_AssignImageList). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxTreebook(), Parent::wxWindow:wxWindow(), Id::integer(). @@ -220,7 +234,6 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookcreate">external documentation</a>. -doc """ Creates a treebook control. @@ -243,7 +256,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxTreebook_Create), wxe_util:rec(?wxTreebook_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookdeleteallpages">external documentation</a>. -doc "Deletes all pages.". -spec deleteAllPages(This) -> boolean() when This::wxTreebook(). @@ -252,7 +264,6 @@ deleteAllPages(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreebook_DeleteAllPages), wxe_util:rec(?wxTreebook_DeleteAllPages). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetcurrentpage">external documentation</a>. -doc "Returns the currently selected page or NULL.". -spec getCurrentPage(This) -> wxWindow:wxWindow() when This::wxTreebook(). @@ -261,11 +272,13 @@ getCurrentPage(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreebook_GetCurrentPage), wxe_util:rec(?wxTreebook_GetCurrentPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetimagelist">external documentation</a>. -doc """ Returns the associated image list, may be NULL. -See: `m:wxImageList`, `setImageList/2` +See: +* `m:wxImageList` + +* `setImageList/2` """. -spec getImageList(This) -> wxImageList:wxImageList() when This::wxTreebook(). @@ -274,7 +287,6 @@ getImageList(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreebook_GetImageList), wxe_util:rec(?wxTreebook_GetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetpage">external documentation</a>. -doc "Returns the window at the given page position.". -spec getPage(This, Page) -> wxWindow:wxWindow() when This::wxTreebook(), Page::integer(). @@ -284,7 +296,6 @@ getPage(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxTreebook_GetPage), wxe_util:rec(?wxTreebook_GetPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetpagecount">external documentation</a>. -doc "Returns the number of pages in the control.". -spec getPageCount(This) -> integer() when This::wxTreebook(). @@ -293,7 +304,6 @@ getPageCount(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreebook_GetPageCount), wxe_util:rec(?wxTreebook_GetPageCount). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetpageimage">external documentation</a>. -doc "Returns the image index for the given page.". -spec getPageImage(This, NPage) -> integer() when This::wxTreebook(), NPage::integer(). @@ -303,7 +313,6 @@ getPageImage(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxTreebook_GetPageImage), wxe_util:rec(?wxTreebook_GetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetpagetext">external documentation</a>. -doc "Returns the string for the given page.". -spec getPageText(This, NPage) -> unicode:charlist() when This::wxTreebook(), NPage::integer(). @@ -313,13 +322,12 @@ getPageText(#wx_ref{type=ThisT}=This,NPage) wxe_util:queue_cmd(This,NPage,?get_env(),?wxTreebook_GetPageText), wxe_util:rec(?wxTreebook_GetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookgetselection">external documentation</a>. -doc """ -Returns the currently selected page, or `wxNOT_FOUND` if none was selected. +Returns the currently selected page, or `wxNOT\_FOUND` if none was selected. -Note: This method may return either the previously or newly selected page when -called from the EVT_TREEBOOK_PAGE_CHANGED() handler depending on the platform -and so `wxBookCtrlEvent:getSelection/1` should be used instead in this case. +Note: This method may return either the previously or newly selected page when called +from the EVT_TREEBOOK_PAGE_CHANGED() handler depending on the platform and so `wxBookCtrlEvent:getSelection/1` should be +used instead in this case. """. -spec getSelection(This) -> integer() when This::wxTreebook(). @@ -328,7 +336,7 @@ getSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxTreebook_GetSelection), wxe_util:rec(?wxTreebook_GetSelection). -%% @equiv expandNode(This,PageId, []) +-doc(#{equiv => expandNode(This,PageId, [])}). -spec expandNode(This, PageId) -> boolean() when This::wxTreebook(), PageId::integer(). @@ -336,12 +344,11 @@ expandNode(This,PageId) when is_record(This, wx_ref),is_integer(PageId) -> expandNode(This,PageId, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookexpandnode">external documentation</a>. -doc """ Expands (collapses) the `pageId` node. -Returns the previous state. May generate page changing events (if selected page -is under the collapsed branch, then its parent is autoselected). +Returns the previous state. May generate page changing events (if selected page is under +the collapsed branch, then its parent is autoselected). """. -spec expandNode(This, PageId, [Option]) -> boolean() when This::wxTreebook(), PageId::integer(), @@ -355,7 +362,6 @@ expandNode(#wx_ref{type=ThisT}=This,PageId, Options) wxe_util:queue_cmd(This,PageId, Opts,?get_env(),?wxTreebook_ExpandNode), wxe_util:rec(?wxTreebook_ExpandNode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookisnodeexpanded">external documentation</a>. -doc "Returns true if the page represented by `pageId` is expanded.". -spec isNodeExpanded(This, PageId) -> boolean() when This::wxTreebook(), PageId::integer(). @@ -365,15 +371,13 @@ isNodeExpanded(#wx_ref{type=ThisT}=This,PageId) wxe_util:queue_cmd(This,PageId,?get_env(),?wxTreebook_IsNodeExpanded), wxe_util:rec(?wxTreebook_IsNodeExpanded). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookhittest">external documentation</a>. -doc """ -Returns the index of the tab at the specified position or `wxNOT_FOUND` if none. +Returns the index of the tab at the specified position or `wxNOT\_FOUND` if none. -If `flags` parameter is non-NULL, the position of the point inside the tab is -returned as well. +If `flags` parameter is non-NULL, the position of the point inside the tab is returned as well. -Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at -the specified position. +Return: Returns the zero-based tab index or `wxNOT_FOUND` if there is no tab at the +specified position. """. -spec hitTest(This, Pt) -> Result when Result ::{Res ::integer(), Flags::integer()}, @@ -384,7 +388,7 @@ hitTest(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxTreebook_HitTest), wxe_util:rec(?wxTreebook_HitTest). -%% @equiv insertPage(This,PagePos,Page,Text, []) +-doc(#{equiv => insertPage(This,PagePos,Page,Text, [])}). -spec insertPage(This, PagePos, Page, Text) -> boolean() when This::wxTreebook(), PagePos::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -392,12 +396,11 @@ insertPage(This,PagePos,Page,Text) when is_record(This, wx_ref),is_integer(PagePos),is_record(Page, wx_ref),?is_chardata(Text) -> insertPage(This,PagePos,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookinsertpage">external documentation</a>. -doc """ Inserts a new page just before the page indicated by `pagePos`. -The new page is placed before `pagePos` page and on the same level. NULL could -be specified for page to create an empty page. +The new page is placed before `pagePos` page and on the same level. NULL could be +specified for page to create an empty page. """. -spec insertPage(This, PagePos, Page, Text, [Option]) -> boolean() when This::wxTreebook(), PagePos::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(), @@ -415,7 +418,7 @@ insertPage(#wx_ref{type=ThisT}=This,PagePos,#wx_ref{type=PageT}=Page,Text, Optio wxe_util:queue_cmd(This,PagePos,Page,Text_UC, Opts,?get_env(),?wxTreebook_InsertPage), wxe_util:rec(?wxTreebook_InsertPage). -%% @equiv insertSubPage(This,PagePos,Page,Text, []) +-doc(#{equiv => insertSubPage(This,PagePos,Page,Text, [])}). -spec insertSubPage(This, PagePos, Page, Text) -> boolean() when This::wxTreebook(), PagePos::integer(), Page::wxWindow:wxWindow(), Text::unicode:chardata(). @@ -423,7 +426,6 @@ insertSubPage(This,PagePos,Page,Text) when is_record(This, wx_ref),is_integer(PagePos),is_record(Page, wx_ref),?is_chardata(Text) -> insertSubPage(This,PagePos,Page,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookinsertsubpage">external documentation</a>. -doc """ Inserts a sub page under the specified page. @@ -445,13 +447,15 @@ insertSubPage(#wx_ref{type=ThisT}=This,PagePos,#wx_ref{type=PageT}=Page,Text, Op wxe_util:queue_cmd(This,PagePos,Page,Text_UC, Opts,?get_env(),?wxTreebook_InsertSubPage), wxe_util:rec(?wxTreebook_InsertSubPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebooksetimagelist">external documentation</a>. -doc """ Sets the image list to use. It does not take ownership of the image list, you must delete it yourself. -See: `m:wxImageList`, `assignImageList/2` +See: +* `m:wxImageList` + +* `assignImageList/2` """. -spec setImageList(This, ImageList) -> 'ok' when This::wxTreebook(), ImageList::wxImageList:wxImageList(). @@ -460,7 +464,6 @@ setImageList(#wx_ref{type=ThisT}=This,#wx_ref{type=ImageListT}=ImageList) -> ?CLASS(ImageListT,wxImageList), wxe_util:queue_cmd(This,ImageList,?get_env(),?wxTreebook_SetImageList). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebooksetpagesize">external documentation</a>. -doc """ Sets the width and height of the pages. @@ -473,7 +476,6 @@ setPageSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxTreebook), wxe_util:queue_cmd(This,Size,?get_env(),?wxTreebook_SetPageSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebooksetpageimage">external documentation</a>. -doc """ Sets the image index for the given page. @@ -487,7 +489,6 @@ setPageImage(#wx_ref{type=ThisT}=This,Page,Image) wxe_util:queue_cmd(This,Page,Image,?get_env(),?wxTreebook_SetPageImage), wxe_util:rec(?wxTreebook_SetPageImage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebooksetpagetext">external documentation</a>. -doc "Sets the text for the given page.". -spec setPageText(This, Page, Text) -> boolean() when This::wxTreebook(), Page::integer(), Text::unicode:chardata(). @@ -498,12 +499,11 @@ setPageText(#wx_ref{type=ThisT}=This,Page,Text) wxe_util:queue_cmd(This,Page,Text_UC,?get_env(),?wxTreebook_SetPageText), wxe_util:rec(?wxTreebook_SetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebooksetselection">external documentation</a>. -doc """ Sets the selection to the given page, returning the previous selection. -Notice that the call to this function generates the page changing events, use -the `changeSelection/2` function if you don't want these events to be generated. +Notice that the call to this function generates the page changing events, use the `changeSelection/2` +function if you don't want these events to be generated. See: `wxBookCtrlBase:getSelection/1` """. @@ -515,12 +515,10 @@ setSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxTreebook_SetSelection), wxe_util:rec(?wxTreebook_SetSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxtreebook.html#wxtreebookchangeselection">external documentation</a>. -doc """ Changes the selection to the given page, returning the previous selection. -This function behaves as `setSelection/2` but does `not` generate the page -changing events. +This function behaves as `setSelection/2` but does `not` generate the page changing events. See overview_events_prog for more information. """. @@ -532,573 +530,383 @@ changeSelection(#wx_ref{type=ThisT}=This,Page) wxe_util:queue_cmd(This,Page,?get_env(),?wxTreebook_ChangeSelection), wxe_util:rec(?wxTreebook_ChangeSelection). -%% @doc Destroys this object, do not use object again --doc """ -Destroys the `m:wxTreebook` object. - -Also deletes all the pages owned by the control (inserted previously into it). -""". +-doc "Destroys the object". -spec destroy(This::wxTreebook()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxTreebook), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxBookCtrlBase -%% @hidden -doc false. removePage(This,Page) -> wxBookCtrlBase:removePage(This,Page). -%% @hidden -doc false. deletePage(This,Page) -> wxBookCtrlBase:deletePage(This,Page). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxUpdateUIEvent.erl b/lib/wx/src/gen/wxUpdateUIEvent.erl index 0f1af9248227..201afe6c6bdf 100644 --- a/lib/wx/src/gen/wxUpdateUIEvent.erl +++ b/lib/wx/src/gen/wxUpdateUIEvent.erl @@ -20,57 +20,59 @@ -module(wxUpdateUIEvent). -moduledoc """ -Functions for wxUpdateUIEvent class - -This class is used for pseudo-events which are called by wxWidgets to give an -application the chance to update various user interface elements. +This class is used for pseudo-events which are called by wxWidgets to give an application +the chance to update various user interface elements. Without update UI events, an application has to work hard to check/uncheck, -enable/disable, show/hide, and set the text for elements such as menu items and -toolbar buttons. The code for doing this has to be mixed up with the code that -is invoked when an action is invoked for a menu item or button. +enable/disable, show/hide, and set the text for elements such as menu items and toolbar +buttons. The code for doing this has to be mixed up with the code that is invoked when an +action is invoked for a menu item or button. With update UI events, you define an event handler to look at the state of the -application and change UI elements accordingly. wxWidgets will call your member -functions in idle time, so you don't have to worry where to call this code. +application and change UI elements accordingly. wxWidgets will call your member functions +in idle time, so you don't have to worry where to call this code. -In addition to being a clearer and more declarative method, it also means you -don't have to worry whether you're updating a toolbar or menubar identifier. The -same handler can update a menu item and toolbar button, if the identifier is the -same. Instead of directly manipulating the menu or button, you call functions in -the event object, such as `check/2`. wxWidgets will determine whether such a -call has been made, and which UI element to update. +In addition to being a clearer and more declarative method, it also means you don't have +to worry whether you're updating a toolbar or menubar identifier. The same handler can +update a menu item and toolbar button, if the identifier is the same. Instead of directly +manipulating the menu or button, you call functions in the event object, such as `check/2`. +wxWidgets will determine whether such a call has been made, and which UI element to update. -These events will work for popup menus as well as menubars. Just before a menu -is popped up, `wxMenu::UpdateUI` (not implemented in wx) is called to process -any UI events for the window that owns the menu. +These events will work for popup menus as well as menubars. Just before a menu is popped +up, `wxMenu::UpdateUI` (not implemented in wx) is called to process any UI events for the +window that owns the menu. -If you find that the overhead of UI update processing is affecting your -application, you can do one or both of the following: +If you find that the overhead of UI update processing is affecting your application, you +can do one or both of the following: -Note that although events are sent in idle time, defining a `m:wxIdleEvent` -handler for a window does not affect this because the events are sent from -`wxWindow::OnInternalIdle` (not implemented in wx) which is always called in -idle time. +* Call `setMode/1` with a value of wxUPDATE_UI_PROCESS_SPECIFIED, and set the extra style +wxWS_EX_PROCESS_UI_UPDATES for every window that should receive update events. No other +windows will receive update events. -wxWidgets tries to optimize update events on some platforms. On Windows and -GTK+, events for menubar items are only sent when the menu is about to be shown, -and not in idle time. +* Call `setUpdateInterval/1` with a millisecond value to set the delay between updates. You may need to call `wxWindow:updateWindowUI/2` at +critical points, for example when a dialog is about to be shown, in case the user sees a +slight delay before windows are updated. -See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events) +Note that although events are sent in idle time, defining a `m:wxIdleEvent` handler for +a window does not affect this because the events are sent from `wxWindow::OnInternalIdle` +(not implemented in wx) which is always called in idle time. + +wxWidgets tries to optimize update events on some platforms. On Windows and GTK+, events +for menubar items are only sent when the menu is about to be shown, and not in idle time. + +See: [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +This class is derived, and can use functions, from: -wxWidgets docs: -[wxUpdateUIEvent](https://docs.wxwidgets.org/3.1/classwx_update_u_i_event.html) +* `m:wxCommandEvent` + +* `m:wxEvent` + +wxWidgets docs: [wxUpdateUIEvent](https://docs.wxwidgets.org/3.2/classwx_update_u_i_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxUpdateUIEventType`](`t:wxUpdateUIEventType/0`) to subscribe to events of -this type. +Use `wxEvtHandler:connect/3` with `wxUpdateUIEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([canUpdate/1,check/2,enable/2,getChecked/1,getEnabled/1,getMode/0,getSetChecked/1, @@ -87,26 +89,27 @@ this type. -include("wx.hrl"). -type wxUpdateUIEventType() :: 'update_ui'. -export_type([wxUpdateUIEvent/0, wxUpdateUI/0, wxUpdateUIEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventcanupdate">external documentation</a>. -doc """ -Returns true if it is appropriate to update (send UI update events to) this -window. - -This function looks at the mode used (see `setMode/1`), the -wxWS_EX_PROCESS_UI_UPDATES flag in `window`, the time update events were last -sent in idle time, and the update interval, to determine whether events should -be sent to this window now. By default this will always return true because the -update mode is initially wxUPDATE_UI_PROCESS_ALL and the interval is set to 0; -so update events will be sent as often as possible. You can reduce the frequency -that events are sent by changing the mode and/or setting an update interval. - -See: `resetUpdateTime/0`, `setUpdateInterval/1`, `setMode/1` +Returns true if it is appropriate to update (send UI update events to) this window. + +This function looks at the mode used (see `setMode/1`), the wxWS_EX_PROCESS_UI_UPDATES flag in `window`, +the time update events were last sent in idle time, and the update interval, to determine +whether events should be sent to this window now. By default this will always return true +because the update mode is initially wxUPDATE_UI_PROCESS_ALL and the interval is set to 0; +so update events will be sent as often as possible. You can reduce the frequency that +events are sent by changing the mode and/or setting an update interval. + +See: +* `resetUpdateTime/0` + +* `setUpdateInterval/1` + +* `setMode/1` """. -spec canUpdate(Window) -> boolean() when Window::wxWindow:wxWindow(). @@ -115,7 +118,6 @@ canUpdate(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxUpdateUIEvent_CanUpdate), wxe_util:rec(?wxUpdateUIEvent_CanUpdate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventcheck">external documentation</a>. -doc "Check or uncheck the UI element.". -spec check(This, Check) -> 'ok' when This::wxUpdateUIEvent(), Check::boolean(). @@ -124,7 +126,6 @@ check(#wx_ref{type=ThisT}=This,Check) ?CLASS(ThisT,wxUpdateUIEvent), wxe_util:queue_cmd(This,Check,?get_env(),?wxUpdateUIEvent_Check). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventenable">external documentation</a>. -doc "Enable or disable the UI element.". -spec enable(This, Enable) -> 'ok' when This::wxUpdateUIEvent(), Enable::boolean(). @@ -133,7 +134,6 @@ enable(#wx_ref{type=ThisT}=This,Enable) ?CLASS(ThisT,wxUpdateUIEvent), wxe_util:queue_cmd(This,Enable,?get_env(),?wxUpdateUIEvent_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventshow">external documentation</a>. -doc "Show or hide the UI element.". -spec show(This, Show) -> 'ok' when This::wxUpdateUIEvent(), Show::boolean(). @@ -142,7 +142,6 @@ show(#wx_ref{type=ThisT}=This,Show) ?CLASS(ThisT,wxUpdateUIEvent), wxe_util:queue_cmd(This,Show,?get_env(),?wxUpdateUIEvent_Show). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetchecked">external documentation</a>. -doc "Returns true if the UI element should be checked.". -spec getChecked(This) -> boolean() when This::wxUpdateUIEvent(). @@ -151,7 +150,6 @@ getChecked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetChecked), wxe_util:rec(?wxUpdateUIEvent_GetChecked). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetenabled">external documentation</a>. -doc "Returns true if the UI element should be enabled.". -spec getEnabled(This) -> boolean() when This::wxUpdateUIEvent(). @@ -160,7 +158,6 @@ getEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetEnabled), wxe_util:rec(?wxUpdateUIEvent_GetEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetshown">external documentation</a>. -doc "Returns true if the UI element should be shown.". -spec getShown(This) -> boolean() when This::wxUpdateUIEvent(). @@ -169,7 +166,6 @@ getShown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetShown), wxe_util:rec(?wxUpdateUIEvent_GetShown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetsetchecked">external documentation</a>. -doc """ Returns true if the application has called `check/2`. @@ -182,7 +178,6 @@ getSetChecked(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetSetChecked), wxe_util:rec(?wxUpdateUIEvent_GetSetChecked). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetsetenabled">external documentation</a>. -doc """ Returns true if the application has called `enable/2`. @@ -195,7 +190,6 @@ getSetEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetSetEnabled), wxe_util:rec(?wxUpdateUIEvent_GetSetEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetsetshown">external documentation</a>. -doc """ Returns true if the application has called `show/2`. @@ -208,7 +202,6 @@ getSetShown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetSetShown), wxe_util:rec(?wxUpdateUIEvent_GetSetShown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetsettext">external documentation</a>. -doc """ Returns true if the application has called `setText/2`. @@ -221,7 +214,6 @@ getSetText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetSetText), wxe_util:rec(?wxUpdateUIEvent_GetSetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgettext">external documentation</a>. -doc "Returns the text that should be set for the UI element.". -spec getText(This) -> unicode:charlist() when This::wxUpdateUIEvent(). @@ -230,21 +222,18 @@ getText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxUpdateUIEvent_GetText), wxe_util:rec(?wxUpdateUIEvent_GetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetmode">external documentation</a>. -%%<br /> Res = ?wxUPDATE_UI_PROCESS_ALL | ?wxUPDATE_UI_PROCESS_SPECIFIED -doc """ -Static function returning a value specifying how wxWidgets will send update -events: to all windows, or only to those which specify that they will process -the events. +Static function returning a value specifying how wxWidgets will send update events: to +all windows, or only to those which specify that they will process the events. See: `setMode/1` """. +%% Res = ?wxUPDATE_UI_PROCESS_ALL | ?wxUPDATE_UI_PROCESS_SPECIFIED -spec getMode() -> wx:wx_enum(). getMode() -> wxe_util:queue_cmd(?get_env(), ?wxUpdateUIEvent_GetMode), wxe_util:rec(?wxUpdateUIEvent_GetMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventgetupdateinterval">external documentation</a>. -doc """ Returns the current interval between updates in milliseconds. @@ -257,32 +246,34 @@ getUpdateInterval() -> wxe_util:queue_cmd(?get_env(), ?wxUpdateUIEvent_GetUpdateInterval), wxe_util:rec(?wxUpdateUIEvent_GetUpdateInterval). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventresetupdatetime">external documentation</a>. -doc """ Used internally to reset the last-updated time to the current time. -It is assumed that update events are normally sent in idle time, so this is -called at the end of idle processing. +It is assumed that update events are normally sent in idle time, so this is called at the +end of idle processing. + +See: +* `canUpdate/1` + +* `setUpdateInterval/1` -See: `canUpdate/1`, `setUpdateInterval/1`, `setMode/1` +* `setMode/1` """. -spec resetUpdateTime() -> 'ok'. resetUpdateTime() -> wxe_util:queue_cmd(?get_env(), ?wxUpdateUIEvent_ResetUpdateTime). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventsetmode">external documentation</a>. -%%<br /> Mode = ?wxUPDATE_UI_PROCESS_ALL | ?wxUPDATE_UI_PROCESS_SPECIFIED -doc """ -Specify how wxWidgets will send update events: to all windows, or only to those -which specify that they will process the events. +Specify how wxWidgets will send update events: to all windows, or only to those which +specify that they will process the events. """. +%% Mode = ?wxUPDATE_UI_PROCESS_ALL | ?wxUPDATE_UI_PROCESS_SPECIFIED -spec setMode(Mode) -> 'ok' when Mode::wx:wx_enum(). setMode(Mode) when is_integer(Mode) -> wxe_util:queue_cmd(Mode,?get_env(),?wxUpdateUIEvent_SetMode). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventsettext">external documentation</a>. -doc "Sets the text for this UI element.". -spec setText(This, Text) -> 'ok' when This::wxUpdateUIEvent(), Text::unicode:chardata(). @@ -292,17 +283,14 @@ setText(#wx_ref{type=ThisT}=This,Text) Text_UC = unicode:characters_to_binary(Text), wxe_util:queue_cmd(This,Text_UC,?get_env(),?wxUpdateUIEvent_SetText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxupdateuievent.html#wxupdateuieventsetupdateinterval">external documentation</a>. -doc """ Sets the interval between updates in milliseconds. -Set to -1 to disable updates, or to 0 to update as frequently as possible. The -default is 0. +Set to -1 to disable updates, or to 0 to update as frequently as possible. The default is 0. -Use this to reduce the overhead of UI update events if your application has a -lot of windows. If you set the value to -1 or greater than 0, you may also need -to call `wxWindow:updateWindowUI/2` at appropriate points in your application, -such as when a dialog is about to be shown. +Use this to reduce the overhead of UI update events if your application has a lot of +windows. If you set the value to -1 or greater than 0, you may also need to call `wxWindow:updateWindowUI/2` at +appropriate points in your application, such as when a dialog is about to be shown. """. -spec setUpdateInterval(UpdateInterval) -> 'ok' when UpdateInterval::integer(). @@ -311,58 +299,40 @@ setUpdateInterval(UpdateInterval) wxe_util:queue_cmd(UpdateInterval,?get_env(),?wxUpdateUIEvent_SetUpdateInterval). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxWebView.erl b/lib/wx/src/gen/wxWebView.erl index e26f10e522fa..47d9db52555b 100644 --- a/lib/wx/src/gen/wxWebView.erl +++ b/lib/wx/src/gen/wxWebView.erl @@ -20,95 +20,122 @@ -module(wxWebView). -moduledoc """ -Functions for wxWebView class +This control may be used to render web (HTML / CSS / javascript) documents. -This control may be used to render web (HTML / CSS / javascript) documents. It -is designed to allow the creation of multiple backends for each port, although -currently just one is available. It differs from `m:wxHtmlWindow` in that each -backend is actually a full rendering engine, Trident on MSW and Webkit on macOS -and GTK. This allows the correct viewing of complex pages with javascript and -css. +It is designed to allow the creation of multiple backends for each port, although +currently just one is available. It differs from `m:wxHtmlWindow` in that each backend is +actually a full rendering engine, Trident on MSW and Webkit on macOS and GTK. This allows +the correct viewing of complex pages with javascript and css. Backend Descriptions -Par: The IE backend uses Microsoft's Trident rendering engine, specifically the -version used by the locally installed copy of Internet Explorer. As such it is -only available for the MSW port. By default recent versions of the -[WebBrowser](http://msdn.microsoft.com/en-us/library/aa752085%28v=VS.85%29.aspx) -control, which this backend uses, emulate Internet Explorer 7. This can be -changed with a registry setting by wxWebView::MSWSetEmulationLevel() see -[this](http://msdn.microsoft.com/en-us/library/ee330730%28v=vs.85%29.aspx#browser_emulation) -article for more information. This backend has full support for custom schemes -and virtual file systems. - -Par: The Edge (Chromium) backend uses Microsoft's -[Edge WebView2](https://docs.microsoft.com/en-us/microsoft-edge/hosting/webview2). -It is available for Windows 7 and newer. The following features are currently -unsupported with this backend: virtual filesystems, custom urls, find. +Par: + +The IE backend uses Microsoft's Trident rendering engine, specifically the version used +by the locally installed copy of Internet Explorer. As such it is only available for the +MSW port. By default recent versions of the [WebBrowser](http://msdn.microsoft.com/en-us/library/aa752085%28v=VS.85%29.aspx) +control, which this backend uses, emulate Internet Explorer 7. This can be changed with a +registry setting by wxWebView::MSWSetEmulationLevel() see [this](http://msdn.microsoft.com/en-us/library/ee330730%28v=vs.85%29.aspx#browser_emulation) +article for more information. This backend has full support for custom schemes and +virtual file systems. + +Par: + +The Edge (Chromium) backend uses Microsoft's [Edge WebView2](https://docs.microsoft.com/en-us/microsoft-edge/hosting/webview2). +It is available for Windows 7 and newer. The following features are currently unsupported +with this backend: virtual filesystems, custom urls, find. This backend is not enabled by default, to build it follow these steps: -Par: Under GTK the WebKit backend uses [WebKitGTK+](http://webkitgtk.org/). The -current minimum version required is 1.3.1 which ships by default with Ubuntu -Natty and Debian Wheezy and has the package name libwebkitgtk-dev. Custom -schemes and virtual files systems are supported under this backend, however -embedded resources such as images and stylesheets are currently loaded using the -data:// scheme. +* Visual Studio 2015, or newer, is required + +* Download the [WebView2 SDK](https://aka.ms/webviewnuget) nuget package (Version 0.9.488 +or newer) + +* Extract the package (it's a zip archive) to `wxWidgets/3rdparty/webview2` (you should +have `3rdparty/webview2/build/native/include/WebView2.h` file after unpacking it) + +* Enable `wxUSE_WEBVIEW_EDGE` in CMake or `setup.h` + +* Build wxWidgets webview library + +* Copy `WebView2Loader.dll` from the subdirectory corresponding to the architecture used +(x86 or x64) of `wxWidgets/3rdparty/webview2/build/` to your applications executable -Par: Under GTK3 the WebKit2 version of [WebKitGTK+](http://webkitgtk.org/) is -used. In Ubuntu the required package name is libwebkit2gtk-4.0-dev and under -Fedora it is webkitgtk4-devel. All wxWEBVIEW_WEBKIT features are supported -except for clearing and enabling / disabling the history. +* At runtime you can use `isBackendAvailable/1` to check if the backend can be used (it will be available if `WebView2Loader.dll` +can be loaded and Edge (Chromium) is installed) -Par: The macOS WebKit backend uses Apple's -[WebView](http://developer.apple.com/library/mac/#documentation/Cocoa/Reference/WebKit/Classes/WebView_Class/Reference/Reference.html#//apple_ref/doc/uid/20001903) -class. This backend has full support for custom schemes and virtual file -systems. +* Make sure to add a note about using the WebView2 SDK to your application documentation, +as required by its licence + +Par: + +Under GTK the WebKit backend uses [WebKitGTK+](http://webkitgtk.org/). The current +minimum version required is 1.3.1 which ships by default with Ubuntu Natty and Debian +Wheezy and has the package name libwebkitgtk-dev. Custom schemes and virtual files systems +are supported under this backend, however embedded resources such as images and +stylesheets are currently loaded using the data:// scheme. + +Par: + +Under GTK3 the WebKit2 version of [WebKitGTK+](http://webkitgtk.org/) is used. In Ubuntu +the required package name is libwebkit2gtk-4.0-dev and under Fedora it is +webkitgtk4-devel. All wxWEBVIEW_WEBKIT features are supported except for clearing and +enabling / disabling the history. + +Par: + +The macOS WebKit backend uses Apple's [WebView](http://developer.apple.com/library/mac/#documentation/Cocoa/Reference/WebKit/Classes/WebView_Class/Reference/Reference.html#//apple_ref/doc/uid/20001903) +class. This backend has full support for custom schemes and virtual file systems. Asynchronous Notifications -Many of the methods in `m:wxWebView` are asynchronous, i.e. they return -immediately and perform their work in the background. This includes functions -such as `loadURL/2` and `reload/2`. To receive notification of the progress and -completion of these functions you need to handle the events that are provided. -Specifically `wxEVT_WEBVIEW_LOADED` notifies when the page or a sub-frame has -finished loading and `wxEVT_WEBVIEW_ERROR` notifies that an error has occurred. +Many of the methods in `m:wxWebView` are asynchronous, i.e. they return immediately and +perform their work in the background. This includes functions such as `loadURL/2` and `reload/2`. To receive +notification of the progress and completion of these functions you need to handle the +events that are provided. Specifically `wxEVT_WEBVIEW_LOADED` notifies when the page or a +sub-frame has finished loading and `wxEVT_WEBVIEW_ERROR` notifies that an error has occurred. Virtual File Systems and Custom Schemes -`m:wxWebView` supports the registering of custom scheme handlers, for example -`file` or `http`. To do this create a new class which inherits from -`wxWebViewHandler` (not implemented in wx), where wxWebHandler::GetFile() -returns a pointer to a `wxFSFile` (not implemented in wx) which represents the -given url. You can then register your handler with `RegisterHandler()` (not -implemented in wx) it will be called for all pages and resources. +`m:wxWebView` supports the registering of custom scheme handlers, for example `file` or `http`. +To do this create a new class which inherits from `wxWebViewHandler` (not implemented in +wx), where wxWebHandler::GetFile() returns a pointer to a `wxFSFile` (not implemented in +wx) which represents the given url. You can then register your handler with `RegisterHandler()` +(not implemented in wx) it will be called for all pages and resources. + +`wxWebViewFSHandler` (not implemented in wx) is provided to access the virtual file +system encapsulated by `wxFileSystem` (not implemented in wx). The `wxMemoryFSHandler` +(not implemented in wx) documentation gives an example of how this may be used. -`wxWebViewFSHandler` (not implemented in wx) is provided to access the virtual -file system encapsulated by `wxFileSystem` (not implemented in wx). The -`wxMemoryFSHandler` (not implemented in wx) documentation gives an example of -how this may be used. +`wxWebViewArchiveHandler` (not implemented in wx) is provided to allow the navigation of +pages inside a zip archive. It supports paths of the form: `scheme:///C`:/example/docs.zip;protocol=zip/main.htm -`wxWebViewArchiveHandler` (not implemented in wx) is provided to allow the -navigation of pages inside a zip archive. It supports paths of the form: -`scheme:///C`:/example/docs.zip;protocol=zip/main.htm +This class is derived, and can use functions, from: -Since: 2.9.3 +* `m:wxControl` -See: `wxWebViewHandler` (not implemented in wx), `m:wxWebViewEvent` +* `m:wxWindow` -This class is derived (and can use functions) from: `m:wxControl` `m:wxWindow` -`m:wxEvtHandler` +* `m:wxEvtHandler` -wxWidgets docs: -[wxWebView](https://docs.wxwidgets.org/3.1/classwx_web_view.html) +wxWidgets docs: [wxWebView](https://docs.wxwidgets.org/3.2/classwx_web_view.html) ## Events -Event types emitted from this class: [`webview_navigating`](`m:wxWebViewEvent`), -[`webview_navigated`](`m:wxWebViewEvent`), -[`webview_loaded`](`m:wxWebViewEvent`), [`webview_error`](`m:wxWebViewEvent`), -[`webview_newwindow`](`m:wxWebViewEvent`), -[`webview_title_changed`](`m:wxWebViewEvent`) +Event types emitted from this class: + +* [`webview_navigating`](`m:wxWebViewEvent`) + +* [`webview_navigated`](`m:wxWebViewEvent`) + +* [`webview_loaded`](`m:wxWebViewEvent`) + +* [`webview_error`](`m:wxWebViewEvent`) + +* [`webview_newwindow`](`m:wxWebViewEvent`) + +* [`webview_title_changed`](`m:wxWebViewEvent`) """. -include("wxe.hrl"). -export([canCopy/1,canCut/1,canGoBack/1,canGoForward/1,canPaste/1,canRedo/1, @@ -164,14 +191,13 @@ Event types emitted from this class: [`webview_navigating`](`m:wxWebViewEvent`), -type wxWebView() :: wx:wx_object(). -export_type([wxWebView/0]). -%% @hidden -doc false. parent_class(wxControl) -> true; parent_class(wxWindow) -> true; parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxWebView() when Parent::wxWindow:wxWindow(), Id::integer(). @@ -179,13 +205,11 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewnew">external documentation</a>. -doc """ Factory function to create a new `m:wxWebView` using a `wxWebViewFactory` (not implemented in wx). -Return: The created `m:wxWebView`, or `NULL` if the requested backend is not -available +Return: The created `m:wxWebView`, or `NULL` if the requested backend is not available Since: 2.9.5 """. @@ -209,11 +233,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxWebView_New), wxe_util:rec(?wxWebView_New). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetcurrenttitle">external documentation</a>. --doc """ -Get the title of the current web page, or its URL/path if title is not -available. -""". +-doc "Get the title of the current web page, or its URL/path if title is not available.". -spec getCurrentTitle(This) -> unicode:charlist() when This::wxWebView(). getCurrentTitle(#wx_ref{type=ThisT}=This) -> @@ -221,7 +241,6 @@ getCurrentTitle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetCurrentTitle), wxe_util:rec(?wxWebView_GetCurrentTitle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetcurrenturl">external documentation</a>. -doc "Get the URL of the currently displayed document.". -spec getCurrentURL(This) -> unicode:charlist() when This::wxWebView(). @@ -230,7 +249,6 @@ getCurrentURL(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetCurrentURL), wxe_util:rec(?wxWebView_GetCurrentURL). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetpagesource">external documentation</a>. -doc """ Get the HTML source code of the currently displayed document. @@ -243,7 +261,6 @@ getPageSource(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetPageSource), wxe_util:rec(?wxWebView_GetPageSource). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetpagetext">external documentation</a>. -doc "Get the text of the current page.". -spec getPageText(This) -> unicode:charlist() when This::wxWebView(). @@ -252,7 +269,6 @@ getPageText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetPageText), wxe_util:rec(?wxWebView_GetPageText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewisbusy">external documentation</a>. -doc "Returns whether the web control is currently busy (e.g. loading a page).". -spec isBusy(This) -> boolean() when This::wxWebView(). @@ -261,7 +277,6 @@ isBusy(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_IsBusy), wxe_util:rec(?wxWebView_IsBusy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewiseditable">external documentation</a>. -doc "Returns whether the web control is currently editable.". -spec isEditable(This) -> boolean() when This::wxWebView(). @@ -270,13 +285,11 @@ isEditable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_IsEditable), wxe_util:rec(?wxWebView_IsEditable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewloadurl">external documentation</a>. -doc """ Load a web page from a URL. -Note: Web engines generally report errors asynchronously, so if you wish to know -whether loading the URL was successful, register to receive navigation error -events. +Note: Web engines generally report errors asynchronously, so if you wish to know whether +loading the URL was successful, register to receive navigation error events. """. -spec loadURL(This, Url) -> 'ok' when This::wxWebView(), Url::unicode:chardata(). @@ -286,7 +299,6 @@ loadURL(#wx_ref{type=ThisT}=This,Url) Url_UC = unicode:characters_to_binary(Url), wxe_util:queue_cmd(This,Url_UC,?get_env(),?wxWebView_LoadURL). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewprint">external documentation</a>. -doc "Opens a print dialog so that the user may print the currently displayed page.". -spec print(This) -> 'ok' when This::wxWebView(). @@ -294,7 +306,7 @@ print(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Print). -%% @equiv reload(This, []) +-doc(#{equiv => reload(This, [])}). -spec reload(This) -> 'ok' when This::wxWebView(). @@ -302,13 +314,12 @@ reload(This) when is_record(This, wx_ref) -> reload(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewreload">external documentation</a>. -%%<br /> Flags = ?wxWEBVIEW_RELOAD_DEFAULT | ?wxWEBVIEW_RELOAD_NO_CACHE -doc """ Reload the currently displayed URL. Note: The flags are ignored by the edge backend. """. +%% Flags = ?wxWEBVIEW_RELOAD_DEFAULT | ?wxWEBVIEW_RELOAD_NO_CACHE -spec reload(This, [Option]) -> 'ok' when This::wxWebView(), Option :: {'flags', wx:wx_enum()}. @@ -320,28 +331,36 @@ reload(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWebView_Reload). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewrunscript">external documentation</a>. -doc """ Runs the given JavaScript code. -JavaScript code is executed inside the browser control and has full access to -DOM and other browser-provided functionality. For example, this code will -replace the current page contents with the provided string. +JavaScript code is executed inside the browser control and has full access to DOM and +other browser-provided functionality. For example, this code will replace the current +page contents with the provided string. -If `output` is non-null, it is filled with the result of executing this code on -success, e.g. a JavaScript value such as a string, a number (integer or floating -point), a boolean or JSON representation for non-primitive types such as arrays -and objects. For example: +If `output` is non-null, it is filled with the result of executing this code on success, +e.g. a JavaScript value such as a string, a number (integer or floating point), a boolean +or JSON representation for non-primitive types such as arrays and objects. For example: This function has a few platform-specific limitations: -Also notice that under MSW converting JavaScript objects to JSON is not -supported in the default emulation mode. `m:wxWebView` implements its own -object-to-JSON conversion as a fallback for this case, however it is not as -full-featured, well-tested or performing as the implementation of this -functionality in the browser control itself, so it is recommended to use -MSWSetEmulationLevel() to change emulation level to a more modern one in which -JSON conversion is done by the control itself. +* When using WebKit v1 in wxGTK2, retrieving the result of JavaScript execution is +unsupported and this function will always return false if `output` is non-null to indicate +this. This functionality is fully supported when using WebKit v2 or later in wxGTK3. + +* When using WebKit under macOS, code execution is limited to at most 10MiB of memory and +10 seconds of execution time. + +* When using IE backend under MSW, scripts can only be executed when the current page is +fully loaded (i.e. `wxEVT_WEBVIEW_LOADED` event was received). A script tag inside the +page HTML is required in order to run JavaScript. + +Also notice that under MSW converting JavaScript objects to JSON is not supported in the +default emulation mode. `m:wxWebView` implements its own object-to-JSON conversion as a +fallback for this case, however it is not as full-featured, well-tested or performing as +the implementation of this functionality in the browser control itself, so it is +recommended to use MSWSetEmulationLevel() to change emulation level to a more modern one +in which JSON conversion is done by the control itself. Return: true if there is a result, false if there is an error. """. @@ -355,7 +374,7 @@ runScript(#wx_ref{type=ThisT}=This,Javascript) wxe_util:queue_cmd(This,Javascript_UC,?get_env(),?wxWebView_RunScript), wxe_util:rec(?wxWebView_RunScript). -%% @equiv setEditable(This, []) +-doc(#{equiv => setEditable(This, [])}). -spec setEditable(This) -> 'ok' when This::wxWebView(). @@ -363,12 +382,11 @@ setEditable(This) when is_record(This, wx_ref) -> setEditable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewseteditable">external documentation</a>. -doc """ Set the editable property of the web control. -Enabling allows the user to edit the page even if the `contenteditable` -attribute is not set. The exact capabilities vary with the backend being used. +Enabling allows the user to edit the page even if the `contenteditable` attribute is not +set. The exact capabilities vary with the backend being used. """. -spec setEditable(This, [Option]) -> 'ok' when This::wxWebView(), @@ -381,13 +399,12 @@ setEditable(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWebView_SetEditable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewsetpage">external documentation</a>. -doc """ Set the displayed page source to the contents of the given string. -Note: When using `wxWEBVIEW_BACKEND_IE` you must wait for the current page to -finish loading before calling `setPage/3`. The baseURL parameter is not used in -this backend and the edge backend. +Note: When using `wxWEBVIEW_BACKEND_IE` you must wait for the current page to finish +loading before calling `setPage/3`. The baseURL parameter is not used in this backend and the edge +backend. """. -spec setPage(This, Html, BaseUrl) -> 'ok' when This::wxWebView(), Html::unicode:chardata(), BaseUrl::unicode:chardata(). @@ -398,12 +415,11 @@ setPage(#wx_ref{type=ThisT}=This,Html,BaseUrl) BaseUrl_UC = unicode:characters_to_binary(BaseUrl), wxe_util:queue_cmd(This,Html_UC,BaseUrl_UC,?get_env(),?wxWebView_SetPage). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewstop">external documentation</a>. -doc """ Stop the current page loading process, if any. -May trigger an error event of type `wxWEBVIEW_NAV_ERR_USER_CANCELLED`. TODO: -make `wxWEBVIEW_NAV_ERR_USER_CANCELLED` errors uniform across ports. +May trigger an error event of type `wxWEBVIEW_NAV_ERR_USER_CANCELLED`. TODO: make `wxWEBVIEW_NAV_ERR_USER_CANCELLED` +errors uniform across ports. """. -spec stop(This) -> 'ok' when This::wxWebView(). @@ -411,7 +427,6 @@ stop(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Stop). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcancopy">external documentation</a>. -doc """ Returns true if the current selection can be copied. @@ -424,7 +439,6 @@ canCopy(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanCopy), wxe_util:rec(?wxWebView_CanCopy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcancut">external documentation</a>. -doc """ Returns true if the current selection can be cut. @@ -437,7 +451,6 @@ canCut(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanCut), wxe_util:rec(?wxWebView_CanCut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcanpaste">external documentation</a>. -doc """ Returns true if data can be pasted. @@ -450,7 +463,6 @@ canPaste(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanPaste), wxe_util:rec(?wxWebView_CanPaste). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcopy">external documentation</a>. -doc "Copies the current selection.". -spec copy(This) -> 'ok' when This::wxWebView(). @@ -458,7 +470,6 @@ copy(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Copy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcut">external documentation</a>. -doc "Cuts the current selection.". -spec cut(This) -> 'ok' when This::wxWebView(). @@ -466,7 +477,6 @@ cut(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Cut). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewpaste">external documentation</a>. -doc "Pastes the current data.". -spec paste(This) -> 'ok' when This::wxWebView(). @@ -474,7 +484,7 @@ paste(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Paste). -%% @equiv enableContextMenu(This, []) +-doc(#{equiv => enableContextMenu(This, [])}). -spec enableContextMenu(This) -> 'ok' when This::wxWebView(). @@ -482,12 +492,11 @@ enableContextMenu(This) when is_record(This, wx_ref) -> enableContextMenu(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewenablecontextmenu">external documentation</a>. -doc """ Enable or disable the right click context menu. -By default the standard context menu is enabled, this method can be used to -disable it or re-enable it later. +By default the standard context menu is enabled, this method can be used to disable it or +re-enable it later. Since: 2.9.5 """. @@ -502,7 +511,6 @@ enableContextMenu(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWebView_EnableContextMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewiscontextmenuenabled">external documentation</a>. -doc """ Returns true if a context menu will be shown on right click. @@ -515,11 +523,7 @@ isContextMenuEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_IsContextMenuEnabled), wxe_util:rec(?wxWebView_IsContextMenuEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcangoback">external documentation</a>. --doc """ -Returns true if it is possible to navigate backward in the history of visited -pages. -""". +-doc "Returns true if it is possible to navigate backward in the history of visited pages.". -spec canGoBack(This) -> boolean() when This::wxWebView(). canGoBack(#wx_ref{type=ThisT}=This) -> @@ -527,11 +531,7 @@ canGoBack(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanGoBack), wxe_util:rec(?wxWebView_CanGoBack). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcangoforward">external documentation</a>. --doc """ -Returns true if it is possible to navigate forward in the history of visited -pages. -""". +-doc "Returns true if it is possible to navigate forward in the history of visited pages.". -spec canGoForward(This) -> boolean() when This::wxWebView(). canGoForward(#wx_ref{type=ThisT}=This) -> @@ -539,7 +539,6 @@ canGoForward(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanGoForward), wxe_util:rec(?wxWebView_CanGoForward). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewclearhistory">external documentation</a>. -doc """ Clear the history, this will also remove the visible page. @@ -551,7 +550,7 @@ clearHistory(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_ClearHistory). -%% @equiv enableHistory(This, []) +-doc(#{equiv => enableHistory(This, [])}). -spec enableHistory(This) -> 'ok' when This::wxWebView(). @@ -559,7 +558,6 @@ enableHistory(This) when is_record(This, wx_ref) -> enableHistory(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewenablehistory">external documentation</a>. -doc """ Enable or disable the history. @@ -578,7 +576,6 @@ enableHistory(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWebView_EnableHistory). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgoback">external documentation</a>. -doc """ Navigate back in the history of visited pages. @@ -590,7 +587,6 @@ goBack(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_GoBack). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgoforward">external documentation</a>. -doc """ Navigate forward in the history of visited pages. @@ -602,7 +598,6 @@ goForward(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_GoForward). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewclearselection">external documentation</a>. -doc "Clears the current selection.". -spec clearSelection(This) -> 'ok' when This::wxWebView(). @@ -610,12 +605,11 @@ clearSelection(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_ClearSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewdeleteselection">external documentation</a>. -doc """ Deletes the current selection. -Note that for `wxWEBVIEW_BACKEND_WEBKIT` the selection must be editable, either -through SetEditable or the correct HTML attribute. +Note that for `wxWEBVIEW_BACKEND_WEBKIT` the selection must be editable, either through +SetEditable or the correct HTML attribute. """. -spec deleteSelection(This) -> 'ok' when This::wxWebView(). @@ -623,7 +617,6 @@ deleteSelection(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_DeleteSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetselectedsource">external documentation</a>. -doc "Returns the currently selected source, if any.". -spec getSelectedSource(This) -> unicode:charlist() when This::wxWebView(). @@ -632,7 +625,6 @@ getSelectedSource(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetSelectedSource), wxe_util:rec(?wxWebView_GetSelectedSource). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetselectedtext">external documentation</a>. -doc "Returns the currently selected text, if any.". -spec getSelectedText(This) -> unicode:charlist() when This::wxWebView(). @@ -641,7 +633,6 @@ getSelectedText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetSelectedText), wxe_util:rec(?wxWebView_GetSelectedText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewhasselection">external documentation</a>. -doc "Returns true if there is a current selection.". -spec hasSelection(This) -> boolean() when This::wxWebView(). @@ -650,7 +641,6 @@ hasSelection(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_HasSelection), wxe_util:rec(?wxWebView_HasSelection). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewselectall">external documentation</a>. -doc "Selects the entire page.". -spec selectAll(This) -> 'ok' when This::wxWebView(). @@ -658,7 +648,6 @@ selectAll(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_SelectAll). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcanredo">external documentation</a>. -doc "Returns true if there is an action to redo.". -spec canRedo(This) -> boolean() when This::wxWebView(). @@ -667,7 +656,6 @@ canRedo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanRedo), wxe_util:rec(?wxWebView_CanRedo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcanundo">external documentation</a>. -doc "Returns true if there is an action to undo.". -spec canUndo(This) -> boolean() when This::wxWebView(). @@ -676,7 +664,6 @@ canUndo(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_CanUndo), wxe_util:rec(?wxWebView_CanUndo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewredo">external documentation</a>. -doc "Redos the last action.". -spec redo(This) -> 'ok' when This::wxWebView(). @@ -684,7 +671,6 @@ redo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Redo). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewundo">external documentation</a>. -doc "Undos the last action.". -spec undo(This) -> 'ok' when This::wxWebView(). @@ -692,7 +678,7 @@ undo(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,?get_env(),?wxWebView_Undo). -%% @equiv find(This,Text, []) +-doc(#{equiv => find(This,Text, [])}). -spec find(This, Text) -> integer() when This::wxWebView(), Text::unicode:chardata(). @@ -700,25 +686,23 @@ find(This,Text) when is_record(This, wx_ref),?is_chardata(Text) -> find(This,Text, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewfind">external documentation</a>. -%%<br /> Flags = ?wxWEBVIEW_FIND_WRAP | ?wxWEBVIEW_FIND_ENTIRE_WORD | ?wxWEBVIEW_FIND_MATCH_CASE | ?wxWEBVIEW_FIND_HIGHLIGHT_RESULT | ?wxWEBVIEW_FIND_BACKWARDS | ?wxWEBVIEW_FIND_DEFAULT -doc """ -Finds a phrase on the current page and if found, the control will scroll the -phrase into view and select it. +Finds a phrase on the current page and if found, the control will scroll the phrase into +view and select it. -Return: If search phrase was not found in combination with the flags then -`wxNOT_FOUND` is returned. If called for the first time with search phrase then -the total number of results will be returned. Then for every time its called -with the same search phrase it will return the number of the current match. +Return: If search phrase was not found in combination with the flags then `wxNOT_FOUND` +is returned. If called for the first time with search phrase then the total number of +results will be returned. Then for every time its called with the same search phrase it +will return the number of the current match. -Note: This function will restart the search if the flags -`wxWEBVIEW_FIND_ENTIRE_WORD` or `wxWEBVIEW_FIND_MATCH_CASE` are changed, since -this will require a new search. To reset the search, for example resetting the -highlights call the function with an empty search phrase. This always returns -`wxNOT_FOUND` on the macOS WebKit backend. +Note: This function will restart the search if the flags `wxWEBVIEW_FIND_ENTIRE_WORD` or `wxWEBVIEW_FIND_MATCH_CASE` +are changed, since this will require a new search. To reset the search, for example +resetting the highlights call the function with an empty search phrase. This always +returns `wxNOT_FOUND` on the macOS WebKit backend. Since: 2.9.5 """. +%% Flags = ?wxWEBVIEW_FIND_WRAP | ?wxWEBVIEW_FIND_ENTIRE_WORD | ?wxWEBVIEW_FIND_MATCH_CASE | ?wxWEBVIEW_FIND_HIGHLIGHT_RESULT | ?wxWEBVIEW_FIND_BACKWARDS | ?wxWEBVIEW_FIND_DEFAULT -spec find(This, Text, [Option]) -> integer() when This::wxWebView(), Text::unicode:chardata(), Option :: {'flags', wx:wx_enum()}. @@ -732,14 +716,13 @@ find(#wx_ref{type=ThisT}=This,Text, Options) wxe_util:queue_cmd(This,Text_UC, Opts,?get_env(),?wxWebView_Find), wxe_util:rec(?wxWebView_Find). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewcansetzoomtype">external documentation</a>. -%%<br /> Type = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -doc """ Retrieve whether the current HTML engine supports a zoom type. -Return: Whether this type of zoom is supported by this HTML engine (and thus can -be set through `setZoomType/2`). +Return: Whether this type of zoom is supported by this HTML engine (and thus can be set +through `setZoomType/2`). """. +%% Type = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -spec canSetZoomType(This, Type) -> boolean() when This::wxWebView(), Type::wx:wx_enum(). canSetZoomType(#wx_ref{type=ThisT}=This,Type) @@ -748,16 +731,14 @@ canSetZoomType(#wx_ref{type=ThisT}=This,Type) wxe_util:queue_cmd(This,Type,?get_env(),?wxWebView_CanSetZoomType), wxe_util:rec(?wxWebView_CanSetZoomType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetzoom">external documentation</a>. -%%<br /> Res = ?wxWEBVIEW_ZOOM_TINY | ?wxWEBVIEW_ZOOM_SMALL | ?wxWEBVIEW_ZOOM_MEDIUM | ?wxWEBVIEW_ZOOM_LARGE | ?wxWEBVIEW_ZOOM_LARGEST -doc """ Get the zoom level of the page. -See `getZoomFactor/1` to get more precise zoom scale value other than as -provided by `wxWebViewZoom`. +See `getZoomFactor/1` to get more precise zoom scale value other than as provided by `wxWebViewZoom`. Return: The current level of zoom. """. +%% Res = ?wxWEBVIEW_ZOOM_TINY | ?wxWEBVIEW_ZOOM_SMALL | ?wxWEBVIEW_ZOOM_MEDIUM | ?wxWEBVIEW_ZOOM_LARGE | ?wxWEBVIEW_ZOOM_LARGEST -spec getZoom(This) -> wx:wx_enum() when This::wxWebView(). getZoom(#wx_ref{type=ThisT}=This) -> @@ -765,13 +746,12 @@ getZoom(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetZoom), wxe_util:rec(?wxWebView_GetZoom). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetzoomtype">external documentation</a>. -%%<br /> Res = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -doc """ Get how the zoom factor is currently interpreted. Return: How the zoom factor is currently interpreted by the HTML engine. """. +%% Res = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -spec getZoomType(This) -> wx:wx_enum() when This::wxWebView(). getZoomType(#wx_ref{type=ThisT}=This) -> @@ -779,14 +759,12 @@ getZoomType(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetZoomType), wxe_util:rec(?wxWebView_GetZoomType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewsetzoom">external documentation</a>. -%%<br /> Zoom = ?wxWEBVIEW_ZOOM_TINY | ?wxWEBVIEW_ZOOM_SMALL | ?wxWEBVIEW_ZOOM_MEDIUM | ?wxWEBVIEW_ZOOM_LARGE | ?wxWEBVIEW_ZOOM_LARGEST -doc """ Set the zoom level of the page. -See `setZoomFactor/2` for more precise scaling other than the measured steps -provided by `wxWebViewZoom`. +See `setZoomFactor/2` for more precise scaling other than the measured steps provided by `wxWebViewZoom`. """. +%% Zoom = ?wxWEBVIEW_ZOOM_TINY | ?wxWEBVIEW_ZOOM_SMALL | ?wxWEBVIEW_ZOOM_MEDIUM | ?wxWEBVIEW_ZOOM_LARGE | ?wxWEBVIEW_ZOOM_LARGEST -spec setZoom(This, Zoom) -> 'ok' when This::wxWebView(), Zoom::wx:wx_enum(). setZoom(#wx_ref{type=ThisT}=This,Zoom) @@ -794,14 +772,12 @@ setZoom(#wx_ref{type=ThisT}=This,Zoom) ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,Zoom,?get_env(),?wxWebView_SetZoom). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewsetzoomtype">external documentation</a>. -%%<br /> ZoomType = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -doc """ Set how to interpret the zoom factor. -Note: invoke `canSetZoomType/2` first, some HTML renderers may not support all -zoom types. +Note: invoke `canSetZoomType/2` first, some HTML renderers may not support all zoom types. """. +%% ZoomType = ?wxWEBVIEW_ZOOM_TYPE_LAYOUT | ?wxWEBVIEW_ZOOM_TYPE_TEXT -spec setZoomType(This, ZoomType) -> 'ok' when This::wxWebView(), ZoomType::wx:wx_enum(). setZoomType(#wx_ref{type=ThisT}=This,ZoomType) @@ -809,7 +785,6 @@ setZoomType(#wx_ref{type=ThisT}=This,ZoomType) ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,ZoomType,?get_env(),?wxWebView_SetZoomType). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewgetzoomfactor">external documentation</a>. -doc """ Get the zoom factor of the page. @@ -824,12 +799,11 @@ getZoomFactor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebView_GetZoomFactor), wxe_util:rec(?wxWebView_GetZoomFactor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewsetzoomfactor">external documentation</a>. -doc """ Set the zoom factor of the page. -Note: zoom scale in IE will be converted into `wxWebViewZoom` levels for -`wxWebViewZoomType` of `wxWEBVIEW_ZOOM_TYPE_TEXT`. +Note: zoom scale in IE will be converted into `wxWebViewZoom` levels for `wxWebViewZoomType` +of `wxWEBVIEW_ZOOM_TYPE_TEXT`. Since: 3.1.4 """. @@ -840,7 +814,6 @@ setZoomFactor(#wx_ref{type=ThisT}=This,Zoom) ?CLASS(ThisT,wxWebView), wxe_util:queue_cmd(This,Zoom,?get_env(),?wxWebView_SetZoomFactor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebview.html#wxwebviewisbackendavailable">external documentation</a>. -doc """ Allows to check if a specific backend is currently available. @@ -855,554 +828,371 @@ isBackendAvailable(Backend) wxe_util:rec(?wxWebView_IsBackendAvailable). %% From wxControl -%% @hidden -doc false. setLabel(This,Label) -> wxControl:setLabel(This,Label). -%% @hidden -doc false. getLabel(This) -> wxControl:getLabel(This). %% From wxWindow -%% @hidden -doc false. getDPI(This) -> wxWindow:getDPI(This). -%% @hidden -doc false. getContentScaleFactor(This) -> wxWindow:getContentScaleFactor(This). -%% @hidden -doc false. setDoubleBuffered(This,On) -> wxWindow:setDoubleBuffered(This,On). -%% @hidden -doc false. isDoubleBuffered(This) -> wxWindow:isDoubleBuffered(This). -%% @hidden -doc false. canSetTransparent(This) -> wxWindow:canSetTransparent(This). -%% @hidden -doc false. setTransparent(This,Alpha) -> wxWindow:setTransparent(This,Alpha). -%% @hidden -doc false. warpPointer(This,X,Y) -> wxWindow:warpPointer(This,X,Y). -%% @hidden -doc false. validate(This) -> wxWindow:validate(This). -%% @hidden -doc false. updateWindowUI(This, Options) -> wxWindow:updateWindowUI(This, Options). -%% @hidden -doc false. updateWindowUI(This) -> wxWindow:updateWindowUI(This). -%% @hidden -doc false. update(This) -> wxWindow:update(This). -%% @hidden -doc false. transferDataToWindow(This) -> wxWindow:transferDataToWindow(This). -%% @hidden -doc false. transferDataFromWindow(This) -> wxWindow:transferDataFromWindow(This). -%% @hidden -doc false. thaw(This) -> wxWindow:thaw(This). -%% @hidden -doc false. show(This, Options) -> wxWindow:show(This, Options). -%% @hidden -doc false. show(This) -> wxWindow:show(This). -%% @hidden -doc false. shouldInheritColours(This) -> wxWindow:shouldInheritColours(This). -%% @hidden -doc false. setWindowVariant(This,Variant) -> wxWindow:setWindowVariant(This,Variant). -%% @hidden -doc false. setWindowStyleFlag(This,Style) -> wxWindow:setWindowStyleFlag(This,Style). -%% @hidden -doc false. setWindowStyle(This,Style) -> wxWindow:setWindowStyle(This,Style). -%% @hidden -doc false. setVirtualSize(This,Width,Height) -> wxWindow:setVirtualSize(This,Width,Height). -%% @hidden -doc false. setVirtualSize(This,Size) -> wxWindow:setVirtualSize(This,Size). -%% @hidden -doc false. setToolTip(This,TipString) -> wxWindow:setToolTip(This,TipString). -%% @hidden -doc false. setThemeEnabled(This,Enable) -> wxWindow:setThemeEnabled(This,Enable). -%% @hidden -doc false. setSizerAndFit(This,Sizer, Options) -> wxWindow:setSizerAndFit(This,Sizer, Options). -%% @hidden -doc false. setSizerAndFit(This,Sizer) -> wxWindow:setSizerAndFit(This,Sizer). -%% @hidden -doc false. setSizer(This,Sizer, Options) -> wxWindow:setSizer(This,Sizer, Options). -%% @hidden -doc false. setSizer(This,Sizer) -> wxWindow:setSizer(This,Sizer). -%% @hidden -doc false. setSizeHints(This,MinW,MinH, Options) -> wxWindow:setSizeHints(This,MinW,MinH, Options). -%% @hidden -doc false. setSizeHints(This,MinW,MinH) -> wxWindow:setSizeHints(This,MinW,MinH). -%% @hidden -doc false. setSizeHints(This,MinSize) -> wxWindow:setSizeHints(This,MinSize). -%% @hidden -doc false. setSize(This,X,Y,Width,Height, Options) -> wxWindow:setSize(This,X,Y,Width,Height, Options). -%% @hidden -doc false. setSize(This,X,Y,Width,Height) -> wxWindow:setSize(This,X,Y,Width,Height). -%% @hidden -doc false. setSize(This,Width,Height) -> wxWindow:setSize(This,Width,Height). -%% @hidden -doc false. setSize(This,Rect) -> wxWindow:setSize(This,Rect). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos, Options) -> wxWindow:setScrollPos(This,Orientation,Pos, Options). -%% @hidden -doc false. setScrollPos(This,Orientation,Pos) -> wxWindow:setScrollPos(This,Orientation,Pos). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range, Options) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range, Options). -%% @hidden -doc false. setScrollbar(This,Orientation,Position,ThumbSize,Range) -> wxWindow:setScrollbar(This,Orientation,Position,ThumbSize,Range). -%% @hidden -doc false. setPalette(This,Pal) -> wxWindow:setPalette(This,Pal). -%% @hidden -doc false. setName(This,Name) -> wxWindow:setName(This,Name). -%% @hidden -doc false. setId(This,Winid) -> wxWindow:setId(This,Winid). -%% @hidden -doc false. setHelpText(This,HelpText) -> wxWindow:setHelpText(This,HelpText). -%% @hidden -doc false. setForegroundColour(This,Colour) -> wxWindow:setForegroundColour(This,Colour). -%% @hidden -doc false. setFont(This,Font) -> wxWindow:setFont(This,Font). -%% @hidden -doc false. setFocusFromKbd(This) -> wxWindow:setFocusFromKbd(This). -%% @hidden -doc false. setFocus(This) -> wxWindow:setFocus(This). -%% @hidden -doc false. setExtraStyle(This,ExStyle) -> wxWindow:setExtraStyle(This,ExStyle). -%% @hidden -doc false. setDropTarget(This,Target) -> wxWindow:setDropTarget(This,Target). -%% @hidden -doc false. setOwnForegroundColour(This,Colour) -> wxWindow:setOwnForegroundColour(This,Colour). -%% @hidden -doc false. setOwnFont(This,Font) -> wxWindow:setOwnFont(This,Font). -%% @hidden -doc false. setOwnBackgroundColour(This,Colour) -> wxWindow:setOwnBackgroundColour(This,Colour). -%% @hidden -doc false. setMinSize(This,Size) -> wxWindow:setMinSize(This,Size). -%% @hidden -doc false. setMaxSize(This,Size) -> wxWindow:setMaxSize(This,Size). -%% @hidden -doc false. setCursor(This,Cursor) -> wxWindow:setCursor(This,Cursor). -%% @hidden -doc false. setContainingSizer(This,Sizer) -> wxWindow:setContainingSizer(This,Sizer). -%% @hidden -doc false. setClientSize(This,Width,Height) -> wxWindow:setClientSize(This,Width,Height). -%% @hidden -doc false. setClientSize(This,Size) -> wxWindow:setClientSize(This,Size). -%% @hidden -doc false. setCaret(This,Caret) -> wxWindow:setCaret(This,Caret). -%% @hidden -doc false. setBackgroundStyle(This,Style) -> wxWindow:setBackgroundStyle(This,Style). -%% @hidden -doc false. setBackgroundColour(This,Colour) -> wxWindow:setBackgroundColour(This,Colour). -%% @hidden -doc false. setAutoLayout(This,AutoLayout) -> wxWindow:setAutoLayout(This,AutoLayout). -%% @hidden -doc false. setAcceleratorTable(This,Accel) -> wxWindow:setAcceleratorTable(This,Accel). -%% @hidden -doc false. scrollWindow(This,Dx,Dy, Options) -> wxWindow:scrollWindow(This,Dx,Dy, Options). -%% @hidden -doc false. scrollWindow(This,Dx,Dy) -> wxWindow:scrollWindow(This,Dx,Dy). -%% @hidden -doc false. scrollPages(This,Pages) -> wxWindow:scrollPages(This,Pages). -%% @hidden -doc false. scrollLines(This,Lines) -> wxWindow:scrollLines(This,Lines). -%% @hidden -doc false. screenToClient(This,Pt) -> wxWindow:screenToClient(This,Pt). -%% @hidden -doc false. screenToClient(This) -> wxWindow:screenToClient(This). -%% @hidden -doc false. reparent(This,NewParent) -> wxWindow:reparent(This,NewParent). -%% @hidden -doc false. removeChild(This,Child) -> wxWindow:removeChild(This,Child). -%% @hidden -doc false. releaseMouse(This) -> wxWindow:releaseMouse(This). -%% @hidden -doc false. refreshRect(This,Rect, Options) -> wxWindow:refreshRect(This,Rect, Options). -%% @hidden -doc false. refreshRect(This,Rect) -> wxWindow:refreshRect(This,Rect). -%% @hidden -doc false. refresh(This, Options) -> wxWindow:refresh(This, Options). -%% @hidden -doc false. refresh(This) -> wxWindow:refresh(This). -%% @hidden -doc false. raise(This) -> wxWindow:raise(This). -%% @hidden -doc false. popupMenu(This,Menu,X,Y) -> wxWindow:popupMenu(This,Menu,X,Y). -%% @hidden -doc false. popupMenu(This,Menu, Options) -> wxWindow:popupMenu(This,Menu, Options). -%% @hidden -doc false. popupMenu(This,Menu) -> wxWindow:popupMenu(This,Menu). -%% @hidden -doc false. pageUp(This) -> wxWindow:pageUp(This). -%% @hidden -doc false. pageDown(This) -> wxWindow:pageDown(This). -%% @hidden -doc false. navigate(This, Options) -> wxWindow:navigate(This, Options). -%% @hidden -doc false. navigate(This) -> wxWindow:navigate(This). -%% @hidden -doc false. moveBeforeInTabOrder(This,Win) -> wxWindow:moveBeforeInTabOrder(This,Win). -%% @hidden -doc false. moveAfterInTabOrder(This,Win) -> wxWindow:moveAfterInTabOrder(This,Win). -%% @hidden -doc false. move(This,X,Y, Options) -> wxWindow:move(This,X,Y, Options). -%% @hidden -doc false. move(This,X,Y) -> wxWindow:move(This,X,Y). -%% @hidden -doc false. move(This,Pt) -> wxWindow:move(This,Pt). -%% @hidden -doc false. lower(This) -> wxWindow:lower(This). -%% @hidden -doc false. lineUp(This) -> wxWindow:lineUp(This). -%% @hidden -doc false. lineDown(This) -> wxWindow:lineDown(This). -%% @hidden -doc false. layout(This) -> wxWindow:layout(This). -%% @hidden -doc false. isShownOnScreen(This) -> wxWindow:isShownOnScreen(This). -%% @hidden -doc false. isTopLevel(This) -> wxWindow:isTopLevel(This). -%% @hidden -doc false. isShown(This) -> wxWindow:isShown(This). -%% @hidden -doc false. isRetained(This) -> wxWindow:isRetained(This). -%% @hidden -doc false. isExposed(This,X,Y,W,H) -> wxWindow:isExposed(This,X,Y,W,H). -%% @hidden -doc false. isExposed(This,X,Y) -> wxWindow:isExposed(This,X,Y). -%% @hidden -doc false. isExposed(This,Pt) -> wxWindow:isExposed(This,Pt). -%% @hidden -doc false. isEnabled(This) -> wxWindow:isEnabled(This). -%% @hidden -doc false. isFrozen(This) -> wxWindow:isFrozen(This). -%% @hidden -doc false. invalidateBestSize(This) -> wxWindow:invalidateBestSize(This). -%% @hidden -doc false. initDialog(This) -> wxWindow:initDialog(This). -%% @hidden -doc false. inheritAttributes(This) -> wxWindow:inheritAttributes(This). -%% @hidden -doc false. hide(This) -> wxWindow:hide(This). -%% @hidden -doc false. hasTransparentBackground(This) -> wxWindow:hasTransparentBackground(This). -%% @hidden -doc false. hasScrollbar(This,Orient) -> wxWindow:hasScrollbar(This,Orient). -%% @hidden -doc false. hasCapture(This) -> wxWindow:hasCapture(This). -%% @hidden -doc false. getWindowVariant(This) -> wxWindow:getWindowVariant(This). -%% @hidden -doc false. getWindowStyleFlag(This) -> wxWindow:getWindowStyleFlag(This). -%% @hidden -doc false. getVirtualSize(This) -> wxWindow:getVirtualSize(This). -%% @hidden -doc false. getUpdateRegion(This) -> wxWindow:getUpdateRegion(This). -%% @hidden -doc false. getToolTip(This) -> wxWindow:getToolTip(This). -%% @hidden -doc false. getThemeEnabled(This) -> wxWindow:getThemeEnabled(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxWindow:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxWindow:getTextExtent(This,String). -%% @hidden -doc false. getSizer(This) -> wxWindow:getSizer(This). -%% @hidden -doc false. getSize(This) -> wxWindow:getSize(This). -%% @hidden -doc false. getScrollThumb(This,Orientation) -> wxWindow:getScrollThumb(This,Orientation). -%% @hidden -doc false. getScrollRange(This,Orientation) -> wxWindow:getScrollRange(This,Orientation). -%% @hidden -doc false. getScrollPos(This,Orientation) -> wxWindow:getScrollPos(This,Orientation). -%% @hidden -doc false. getScreenRect(This) -> wxWindow:getScreenRect(This). -%% @hidden -doc false. getScreenPosition(This) -> wxWindow:getScreenPosition(This). -%% @hidden -doc false. getRect(This) -> wxWindow:getRect(This). -%% @hidden -doc false. getPosition(This) -> wxWindow:getPosition(This). -%% @hidden -doc false. getParent(This) -> wxWindow:getParent(This). -%% @hidden -doc false. getName(This) -> wxWindow:getName(This). -%% @hidden -doc false. getMinSize(This) -> wxWindow:getMinSize(This). -%% @hidden -doc false. getMaxSize(This) -> wxWindow:getMaxSize(This). -%% @hidden -doc false. getId(This) -> wxWindow:getId(This). -%% @hidden -doc false. getHelpText(This) -> wxWindow:getHelpText(This). -%% @hidden -doc false. getHandle(This) -> wxWindow:getHandle(This). -%% @hidden -doc false. getGrandParent(This) -> wxWindow:getGrandParent(This). -%% @hidden -doc false. getForegroundColour(This) -> wxWindow:getForegroundColour(This). -%% @hidden -doc false. getFont(This) -> wxWindow:getFont(This). -%% @hidden -doc false. getExtraStyle(This) -> wxWindow:getExtraStyle(This). -%% @hidden -doc false. getDPIScaleFactor(This) -> wxWindow:getDPIScaleFactor(This). -%% @hidden -doc false. getDropTarget(This) -> wxWindow:getDropTarget(This). -%% @hidden -doc false. getCursor(This) -> wxWindow:getCursor(This). -%% @hidden -doc false. getContainingSizer(This) -> wxWindow:getContainingSizer(This). -%% @hidden -doc false. getClientSize(This) -> wxWindow:getClientSize(This). -%% @hidden -doc false. getChildren(This) -> wxWindow:getChildren(This). -%% @hidden -doc false. getCharWidth(This) -> wxWindow:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxWindow:getCharHeight(This). -%% @hidden -doc false. getCaret(This) -> wxWindow:getCaret(This). -%% @hidden -doc false. getBestSize(This) -> wxWindow:getBestSize(This). -%% @hidden -doc false. getBackgroundStyle(This) -> wxWindow:getBackgroundStyle(This). -%% @hidden -doc false. getBackgroundColour(This) -> wxWindow:getBackgroundColour(This). -%% @hidden -doc false. getAcceleratorTable(This) -> wxWindow:getAcceleratorTable(This). -%% @hidden -doc false. freeze(This) -> wxWindow:freeze(This). -%% @hidden -doc false. fitInside(This) -> wxWindow:fitInside(This). -%% @hidden -doc false. fit(This) -> wxWindow:fit(This). -%% @hidden -doc false. findWindow(This,Id) -> wxWindow:findWindow(This,Id). -%% @hidden -doc false. enable(This, Options) -> wxWindow:enable(This, Options). -%% @hidden -doc false. enable(This) -> wxWindow:enable(This). -%% @hidden -doc false. dragAcceptFiles(This,Accept) -> wxWindow:dragAcceptFiles(This,Accept). -%% @hidden -doc false. disable(This) -> wxWindow:disable(This). -%% @hidden -doc false. destroyChildren(This) -> wxWindow:destroyChildren(This). -%% @hidden -doc false. convertPixelsToDialog(This,Sz) -> wxWindow:convertPixelsToDialog(This,Sz). -%% @hidden -doc false. convertDialogToPixels(This,Sz) -> wxWindow:convertDialogToPixels(This,Sz). -%% @hidden -doc false. close(This, Options) -> wxWindow:close(This, Options). -%% @hidden -doc false. close(This) -> wxWindow:close(This). -%% @hidden -doc false. clientToScreen(This,X,Y) -> wxWindow:clientToScreen(This,X,Y). -%% @hidden -doc false. clientToScreen(This,Pt) -> wxWindow:clientToScreen(This,Pt). -%% @hidden -doc false. clearBackground(This) -> wxWindow:clearBackground(This). -%% @hidden -doc false. centreOnParent(This, Options) -> wxWindow:centreOnParent(This, Options). -%% @hidden -doc false. centerOnParent(This, Options) -> wxWindow:centerOnParent(This, Options). -%% @hidden -doc false. centreOnParent(This) -> wxWindow:centreOnParent(This). -%% @hidden -doc false. centerOnParent(This) -> wxWindow:centerOnParent(This). -%% @hidden -doc false. centre(This, Options) -> wxWindow:centre(This, Options). -%% @hidden -doc false. center(This, Options) -> wxWindow:center(This, Options). -%% @hidden -doc false. centre(This) -> wxWindow:centre(This). -%% @hidden -doc false. center(This) -> wxWindow:center(This). -%% @hidden -doc false. captureMouse(This) -> wxWindow:captureMouse(This). -%% @hidden -doc false. cacheBestSize(This,Size) -> wxWindow:cacheBestSize(This,Size). %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxWebViewEvent.erl b/lib/wx/src/gen/wxWebViewEvent.erl index 565415be78d3..98c2dd6082cb 100644 --- a/lib/wx/src/gen/wxWebViewEvent.erl +++ b/lib/wx/src/gen/wxWebViewEvent.erl @@ -20,26 +20,21 @@ -module(wxWebViewEvent). -moduledoc """ -Functions for wxWebViewEvent class +A navigation event holds information about events associated with `m:wxWebView` objects. -A navigation event holds information about events associated with `m:wxWebView` -objects. +This class is derived, and can use functions, from: -Since: 2.9.3 +* `m:wxNotifyEvent` -See: `m:wxWebView` +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxNotifyEvent` -`m:wxCommandEvent` `m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxWebViewEvent](https://docs.wxwidgets.org/3.1/classwx_web_view_event.html) +wxWidgets docs: [wxWebViewEvent](https://docs.wxwidgets.org/3.2/classwx_web_view_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxWebViewEventType`](`t:wxWebViewEventType/0`) to subscribe to events of this -type. +Use `wxEvtHandler:connect/3` with `wxWebViewEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([getInt/1,getString/1,getTarget/1,getURL/1]). @@ -54,20 +49,18 @@ type. -include("wx.hrl"). -type wxWebViewEventType() :: 'webview_navigating' | 'webview_navigated' | 'webview_loaded' | 'webview_error' | 'webview_newwindow' | 'webview_title_changed'. -export_type([wxWebViewEvent/0, wxWebView/0, wxWebViewEventType/0]). -%% @hidden -doc false. parent_class(wxNotifyEvent) -> true; parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebviewevent.html#wxwebvieweventgetstring">external documentation</a>. -doc """ Returns item string for a listbox or choice selection event. -If one or several items have been deselected, returns the index of the first -deselected item. If some items have been selected and others deselected at the -same time, it will return the index of the first selected item. +If one or several items have been deselected, returns the index of the first deselected +item. If some items have been selected and others deselected at the same time, it will +return the index of the first selected item. """. -spec getString(This) -> unicode:charlist() when This::wxWebViewEvent(). @@ -76,15 +69,13 @@ getString(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebViewEvent_GetString), wxe_util:rec(?wxWebViewEvent_GetString). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebviewevent.html#wxwebvieweventgetint">external documentation</a>. -doc """ -Returns the integer identifier corresponding to a listbox, choice or radiobox -selection (only if the event was a selection, not a deselection), or a boolean -value representing the value of a checkbox. +Returns the integer identifier corresponding to a listbox, choice or radiobox selection +(only if the event was a selection, not a deselection), or a boolean value representing +the value of a checkbox. -For a menu item, this method returns -1 if the item is not checkable or a -boolean value (true or false) for checkable items indicating the new state of -the item. +For a menu item, this method returns -1 if the item is not checkable or a boolean value +(true or false) for checkable items indicating the new state of the item. """. -spec getInt(This) -> integer() when This::wxWebViewEvent(). @@ -93,10 +84,9 @@ getInt(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebViewEvent_GetInt), wxe_util:rec(?wxWebViewEvent_GetInt). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebviewevent.html#wxwebvieweventgettarget">external documentation</a>. -doc """ -Get the name of the target frame which the url of this event has been or will be -loaded into. +Get the name of the target frame which the url of this event has been or will be loaded +into. This may return an empty string if the frame is not available. """. @@ -107,7 +97,6 @@ getTarget(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWebViewEvent_GetTarget), wxe_util:rec(?wxWebViewEvent_GetTarget). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwebviewevent.html#wxwebvieweventgeturl">external documentation</a>. -doc "Get the URL being visited.". -spec getURL(This) -> unicode:charlist() when This::wxWebViewEvent(). @@ -117,62 +106,43 @@ getURL(#wx_ref{type=ThisT}=This) -> wxe_util:rec(?wxWebViewEvent_GetURL). %% From wxNotifyEvent -%% @hidden -doc false. veto(This) -> wxNotifyEvent:veto(This). -%% @hidden -doc false. isAllowed(This) -> wxNotifyEvent:isAllowed(This). -%% @hidden -doc false. allow(This) -> wxNotifyEvent:allow(This). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxWindow.erl b/lib/wx/src/gen/wxWindow.erl index 42351bf0cd39..f6b0d317f2b6 100644 --- a/lib/wx/src/gen/wxWindow.erl +++ b/lib/wx/src/gen/wxWindow.erl @@ -20,77 +20,232 @@ -module(wxWindow). -moduledoc """ -Functions for wxWindow class +`m:wxWindow` is the base class for all windows and represents any visible object on +screen. -`m:wxWindow` is the base class for all windows and represents any visible object -on screen. All controls, top level windows and so on are windows. Sizers and -device contexts are not, however, as they don't appear on screen themselves. +All controls, top level windows and so on are windows. Sizers and device contexts are +not, however, as they don't appear on screen themselves. Please note that all children of the window will be deleted automatically by the -destructor before the window itself is deleted which means that you don't have -to worry about deleting them manually. Please see the window deletion overview -for more information. - -Also note that in this, and many others, wxWidgets classes some `GetXXX()` -methods may be overloaded (as, for example, `getSize/1` or `getClientSize/1`). -In this case, the overloads are non-virtual because having multiple virtual -functions with the same name results in a virtual function name hiding at the -derived class level (in English, this means that the derived class has to -override all overloaded variants if it overrides any of them). To allow -overriding them in the derived class, wxWidgets uses a unique protected virtual -`DoGetXXX()` method and all `GetXXX()` ones are forwarded to it, so overriding -the former changes the behaviour of the latter. - -Styles +destructor before the window itself is deleted which means that you don't have to worry +about deleting them manually. Please see the window deletion overview for more information. + +Also note that in this, and many others, wxWidgets classes some `GetXXX()` methods may be +overloaded (as, for example, `getSize/1` or `getClientSize/1`). In this case, the overloads are non-virtual because +having multiple virtual functions with the same name results in a virtual function name +hiding at the derived class level (in English, this means that the derived class has to +override all overloaded variants if it overrides any of them). To allow overriding them in +the derived class, wxWidgets uses a unique protected virtual `DoGetXXX()` method and all `GetXXX()` +ones are forwarded to it, so overriding the former changes the behaviour of the latter. + +## Styles This class supports the following styles: -Extra Styles +* wxBORDER_DEFAULT: The window class will decide the kind of border to show, if any. + +* wxBORDER_SIMPLE: Displays a thin border around the window. wxSIMPLE_BORDER is the old +name for this style. + +* wxBORDER_SUNKEN: Displays a sunken border. wxSUNKEN_BORDER is the old name for this +style. + +* wxBORDER_RAISED: Displays a raised border. wxRAISED_BORDER is the old name for this +style. + +* wxBORDER_STATIC: Displays a border suitable for a static control. wxSTATIC_BORDER is the +old name for this style. Windows only. + +* wxBORDER_THEME: Displays a native border suitable for a control, on the current platform. +On Windows, this will be a themed border; on most other platforms a sunken border will be +used. For more information for themed borders on Windows, please see Themed borders on +Windows. + +* wxBORDER_NONE: Displays no border, overriding the default border style for the window. +wxNO_BORDER is the old name for this style. + +* wxBORDER_DOUBLE: This style is obsolete and should not be used. + +* wxTRANSPARENT_WINDOW: The window is transparent, that is, it will not receive paint +events. Windows only. + +* wxTAB_TRAVERSAL: This style is used by wxWidgets for the windows supporting TAB +navigation among their children, such as `m:wxDialog` and `m:wxPanel`. It should almost +never be used in the application code. + +* wxWANTS_CHARS: Use this to indicate that the window wants to get all char/key events for +all keys - even for keys like TAB or ENTER which are usually used for dialog navigation +and which wouldn't be generated without this style. If you need to use this style in order +to get the arrows or etc., but would still like to have normal keyboard navigation take +place, you should call Navigate in response to the key events for Tab and Shift-Tab. + +* wxNO_FULL_REPAINT_ON_RESIZE: On Windows, this style used to disable repainting the window +completely when its size is changed. Since this behaviour is now the default, the style is +now obsolete and no longer has an effect. + +* wxVSCROLL: Use this style to enable a vertical scrollbar. Notice that this style cannot +be used with native controls which don't support scrollbars nor with top-level windows in +most ports. + +* wxHSCROLL: Use this style to enable a horizontal scrollbar. The same limitations as for +wxVSCROLL apply to this style. + +* wxALWAYS_SHOW_SB: If a window has scrollbars, disable them instead of hiding them when +they are not needed (i.e. when the size of the window is big enough to not require the +scrollbars to navigate it). This style is currently implemented for wxMSW, wxGTK and +wxUniversal and does nothing on the other platforms. + +* wxCLIP_CHILDREN: Use this style to eliminate flicker caused by the background being +repainted, then children being painted over them. Windows only. + +* wxFULL_REPAINT_ON_RESIZE: Use this style to force a complete redraw of the window +whenever it is resized instead of redrawing just the part of the window affected by +resizing. Note that this was the behaviour by default before 2.5.1 release and that if you +experience redraw problems with code which previously used to work you may want to try +this. Currently this style applies on GTK+ 2 and Windows only, and full repainting is +always done on other platforms. + +## Extra Styles This class supports the following extra styles: +* wxWS_EX_BLOCK_EVENTS: wxCommandEvents and the objects of the derived classes are +forwarded to the parent window and so on recursively by default. Using this flag for the +given window allows blocking this propagation at this window, i.e. prevent the events from +being propagated further upwards. Dialogs have this flag on by default for the reasons +explained in the overview_events. + +* wxWS_EX_TRANSIENT: Don't use this window as an implicit parent for the other windows: +this must be used with transient windows as otherwise there is the risk of creating a +dialog/frame with this window as a parent, which would lead to a crash if the parent were +destroyed before the child. + +* wxWS_EX_CONTEXTHELP: Under Windows, puts a query button on the caption. When pressed, +Windows will go into a context-sensitive help mode and wxWidgets will send a `wxEVT_HELP` +event if the user clicked on an application window. This style cannot be used (because of +the underlying native behaviour) together with `wxMAXIMIZE_BOX` or `wxMINIMIZE_BOX`, so +these two styles are automatically turned off if this one is used. + +* wxWS_EX_PROCESS_IDLE: This window should always process idle events, even if the mode set +by `wxIdleEvent:setMode/1` is `wxIDLE_PROCESS_SPECIFIED`. + +* wxWS_EX_PROCESS_UI_UPDATES: This window should always process UI update events, even if +the mode set by `wxUpdateUIEvent:setMode/1` is `wxUPDATE_UI_PROCESS_SPECIFIED`. + See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) -This class is derived (and can use functions) from: `m:wxEvtHandler` +* [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) -wxWidgets docs: [wxWindow](https://docs.wxwidgets.org/3.1/classwx_window.html) +This class is derived, and can use functions, from: + +* `m:wxEvtHandler` + +wxWidgets docs: [wxWindow](https://docs.wxwidgets.org/3.2/classwx_window.html) ## Events -Event types emitted from this class: [`activate`](`m:wxActivateEvent`), -[`child_focus`](`m:wxChildFocusEvent`), -[`context_menu`](`m:wxContextMenuEvent`), [`help`](`m:wxHelpEvent`), -[`drop_files`](`m:wxDropFilesEvent`), [`erase_background`](`m:wxEraseEvent`), -[`set_focus`](`m:wxFocusEvent`), [`kill_focus`](`m:wxFocusEvent`), -[`idle`](`m:wxIdleEvent`), [`joy_button_down`](`m:wxJoystickEvent`), -[`joy_button_up`](`m:wxJoystickEvent`), [`joy_move`](`m:wxJoystickEvent`), -[`joy_zmove`](`m:wxJoystickEvent`), [`key_down`](`m:wxKeyEvent`), -[`key_up`](`m:wxKeyEvent`), [`char`](`m:wxKeyEvent`), -[`char_hook`](`m:wxKeyEvent`), -[`mouse_capture_lost`](`m:wxMouseCaptureLostEvent`), -[`mouse_capture_changed`](`m:wxMouseCaptureChangedEvent`), -[`left_down`](`m:wxMouseEvent`), [`left_up`](`m:wxMouseEvent`), -[`middle_down`](`m:wxMouseEvent`), [`middle_up`](`m:wxMouseEvent`), -[`right_down`](`m:wxMouseEvent`), [`right_up`](`m:wxMouseEvent`), -[`motion`](`m:wxMouseEvent`), [`enter_window`](`m:wxMouseEvent`), -[`leave_window`](`m:wxMouseEvent`), [`left_dclick`](`m:wxMouseEvent`), -[`middle_dclick`](`m:wxMouseEvent`), [`right_dclick`](`m:wxMouseEvent`), -[`mousewheel`](`m:wxMouseEvent`), [`aux1_down`](`m:wxMouseEvent`), -[`aux1_up`](`m:wxMouseEvent`), [`aux1_dclick`](`m:wxMouseEvent`), -[`aux2_down`](`m:wxMouseEvent`), [`aux2_up`](`m:wxMouseEvent`), -[`aux2_dclick`](`m:wxMouseEvent`), [`paint`](`m:wxPaintEvent`), -[`scrollwin_top`](`m:wxScrollWinEvent`), -[`scrollwin_bottom`](`m:wxScrollWinEvent`), -[`scrollwin_lineup`](`m:wxScrollWinEvent`), -[`scrollwin_linedown`](`m:wxScrollWinEvent`), -[`scrollwin_pageup`](`m:wxScrollWinEvent`), -[`scrollwin_pagedown`](`m:wxScrollWinEvent`), -[`scrollwin_thumbtrack`](`m:wxScrollWinEvent`), -[`scrollwin_thumbrelease`](`m:wxScrollWinEvent`), -[`set_cursor`](`m:wxSetCursorEvent`), [`size`](`m:wxSizeEvent`), -[`sys_colour_changed`](`m:wxSysColourChangedEvent`) +Event types emitted from this class: + +* [`activate`](`m:wxActivateEvent`) + +* [`child_focus`](`m:wxChildFocusEvent`) + +* [`context_menu`](`m:wxContextMenuEvent`) + +* [`help`](`m:wxHelpEvent`) + +* [`drop_files`](`m:wxDropFilesEvent`) + +* [`erase_background`](`m:wxEraseEvent`) + +* [`set_focus`](`m:wxFocusEvent`) + +* [`kill_focus`](`m:wxFocusEvent`) + +* [`idle`](`m:wxIdleEvent`) + +* [`joy_button_down`](`m:wxJoystickEvent`) + +* [`joy_button_up`](`m:wxJoystickEvent`) + +* [`joy_move`](`m:wxJoystickEvent`) + +* [`joy_zmove`](`m:wxJoystickEvent`) + +* [`key_down`](`m:wxKeyEvent`) + +* [`key_up`](`m:wxKeyEvent`) + +* [`char`](`m:wxKeyEvent`) + +* [`char_hook`](`m:wxKeyEvent`) + +* [`mouse_capture_lost`](`m:wxMouseCaptureLostEvent`) + +* [`mouse_capture_changed`](`m:wxMouseCaptureChangedEvent`) + +* [`left_down`](`m:wxMouseEvent`) + +* [`left_up`](`m:wxMouseEvent`) + +* [`middle_down`](`m:wxMouseEvent`) + +* [`middle_up`](`m:wxMouseEvent`) + +* [`right_down`](`m:wxMouseEvent`) + +* [`right_up`](`m:wxMouseEvent`) + +* [`motion`](`m:wxMouseEvent`) + +* [`enter_window`](`m:wxMouseEvent`) + +* [`leave_window`](`m:wxMouseEvent`) + +* [`left_dclick`](`m:wxMouseEvent`) + +* [`middle_dclick`](`m:wxMouseEvent`) + +* [`right_dclick`](`m:wxMouseEvent`) + +* [`mousewheel`](`m:wxMouseEvent`) + +* [`aux1_down`](`m:wxMouseEvent`) + +* [`aux1_up`](`m:wxMouseEvent`) + +* [`aux1_dclick`](`m:wxMouseEvent`) + +* [`aux2_down`](`m:wxMouseEvent`) + +* [`aux2_up`](`m:wxMouseEvent`) + +* [`aux2_dclick`](`m:wxMouseEvent`) + +* [`paint`](`m:wxPaintEvent`) + +* [`scrollwin_top`](`m:wxScrollWinEvent`) + +* [`scrollwin_bottom`](`m:wxScrollWinEvent`) + +* [`scrollwin_lineup`](`m:wxScrollWinEvent`) + +* [`scrollwin_linedown`](`m:wxScrollWinEvent`) + +* [`scrollwin_pageup`](`m:wxScrollWinEvent`) + +* [`scrollwin_pagedown`](`m:wxScrollWinEvent`) + +* [`scrollwin_thumbtrack`](`m:wxScrollWinEvent`) + +* [`scrollwin_thumbrelease`](`m:wxScrollWinEvent`) + +* [`set_cursor`](`m:wxSetCursorEvent`) + +* [`size`](`m:wxSizeEvent`) + +* [`sys_colour_changed`](`m:wxSysColourChangedEvent`) """. -include("wxe.hrl"). -export(['Destroy'/1,cacheBestSize/2,canSetTransparent/1,captureMouse/1,center/1, @@ -138,19 +293,17 @@ Event types emitted from this class: [`activate`](`m:wxActivateEvent`), -type wxWindow() :: wx:wx_object(). -export_type([wxWindow/0]). -%% @hidden -doc false. parent_class(wxEvtHandler) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowwxwindow">external documentation</a>. -doc "Default constructor.". -spec new() -> wxWindow(). new() -> wxe_util:queue_cmd(?get_env(), ?wxWindow_new_0), wxe_util:rec(?wxWindow_new_0). -%% @equiv new(Parent,Id, []) +-doc(#{equiv => new(Parent,Id, [])}). -spec new(Parent, Id) -> wxWindow() when Parent::wxWindow(), Id::integer(). @@ -158,10 +311,9 @@ new(Parent,Id) when is_record(Parent, wx_ref),is_integer(Id) -> new(Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowwxwindow">external documentation</a>. -doc """ -Constructs a window, which can be a child of a frame, dialog or any other -non-control window. +Constructs a window, which can be a child of a frame, dialog or any other non-control +window. """. -spec new(Parent, Id, [Option]) -> wxWindow() when Parent::wxWindow(), Id::integer(), @@ -179,7 +331,7 @@ new(#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(Parent,Id, Opts,?get_env(),?wxWindow_new_3), wxe_util:rec(?wxWindow_new_3). -%% @equiv create(This,Parent,Id, []) +-doc(#{equiv => create(This,Parent,Id, [])}). -spec create(This, Parent, Id) -> boolean() when This::wxWindow(), Parent::wxWindow(), Id::integer(). @@ -187,28 +339,25 @@ create(This,Parent,Id) when is_record(This, wx_ref),is_record(Parent, wx_ref),is_integer(Id) -> create(This,Parent,Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcreate">external documentation</a>. -doc """ Construct the actual window object after creating the C++ object. -The non-default constructor of `m:wxWindow` class does two things: it -initializes the C++ object and it also creates the window object in the -underlying graphical toolkit. The `create/4` method can be used to perform the -second part later, while the default constructor can be used to perform the -first part only. +The non-default constructor of `m:wxWindow` class does two things: it initializes the C++ +object and it also creates the window object in the underlying graphical toolkit. The `create/4` +method can be used to perform the second part later, while the default constructor can be +used to perform the first part only. -Please note that the underlying window must be created exactly once, i.e. if you -use the default constructor, which doesn't do this, you `must` call `create/4` -before using the window and if you use the non-default constructor, you can -`not` call `create/4`, as the underlying window is already created. +Please note that the underlying window must be created exactly once, i.e. if you use the +default constructor, which doesn't do this, you `must` call `create/4` before using the window and +if you use the non-default constructor, you can `not` call `create/4`, as the underlying window is +already created. -Note that it is possible and, in fact, useful, to call some methods on the -object between creating the C++ object itself and calling `create/4` on it, e.g. -a common pattern to avoid showing the contents of a window before it is fully -initialized is: +Note that it is possible and, in fact, useful, to call some methods on the object between +creating the C++ object itself and calling `create/4` on it, e.g. a common pattern to avoid showing +the contents of a window before it is fully initialized is: -Also note that it is possible to create an object of a derived type and then -call `create/4` on it: This is notably used by overview_xrc. +Also note that it is possible to create an object of a derived type and then call `create/4` on it: +This is notably used by overview_xrc. The parameters of this method have exactly the same meaning as the non-default constructor parameters, please refer to them for their description. @@ -232,7 +381,6 @@ create(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Id, Options) wxe_util:queue_cmd(This,Parent,Id, Opts,?get_env(),?wxWindow_Create), wxe_util:rec(?wxWindow_Create). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcachebestsize">external documentation</a>. -doc """ Sets the cached best size value. @@ -245,24 +393,25 @@ cacheBestSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxWindow_CacheBestSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcapturemouse">external documentation</a>. -doc """ Directs all mouse input to this window. Call `releaseMouse/1` to release the capture. -Note that wxWidgets maintains the stack of windows having captured the mouse and -when the mouse is released the capture returns to the window which had had -captured it previously and it is only really released if there were no previous -window. In particular, this means that you must release the mouse as many times -as you capture it, unless the window receives the `m:wxMouseCaptureLostEvent` -event. +Note that wxWidgets maintains the stack of windows having captured the mouse and when the +mouse is released the capture returns to the window which had had captured it previously +and it is only really released if there were no previous window. In particular, this means +that you must release the mouse as many times as you capture it, unless the window +receives the `m:wxMouseCaptureLostEvent` event. + +Any application which captures the mouse in the beginning of some operation must handle `m:wxMouseCaptureLostEvent` +and cancel this operation when it receives the event. The event handler must not +recapture mouse. -Any application which captures the mouse in the beginning of some operation must -handle `m:wxMouseCaptureLostEvent` and cancel this operation when it receives -the event. The event handler must not recapture mouse. +See: +* `releaseMouse/1` -See: `releaseMouse/1`, `m:wxMouseCaptureLostEvent` +* `m:wxMouseCaptureLostEvent` """. -spec captureMouse(This) -> 'ok' when This::wxWindow(). @@ -270,7 +419,7 @@ captureMouse(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_CaptureMouse). -%% @equiv center(This, []) +-doc(#{equiv => center(This, [])}). -spec center(This) -> 'ok' when This::wxWindow(). @@ -278,7 +427,7 @@ center(This) when is_record(This, wx_ref) -> center(This, []). -%% @equiv centre(This, []) +-doc(#{equiv => centre(This, [])}). -spec centre(This) -> 'ok' when This::wxWindow(). @@ -286,8 +435,7 @@ centre(This) when is_record(This, wx_ref) -> centre(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcentre">external documentation</a>. --doc "See: `centre/2`.". +-doc "Equivalent to: `centre/2`". -spec center(This, [Option]) -> 'ok' when This::wxWindow(), Option :: {'dir', integer()}. @@ -296,12 +444,11 @@ center(This, Options) when is_record(This, wx_ref),is_list(Options) -> centre(This, Options). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcentre">external documentation</a>. -doc """ Centres the window. -Remark: If the window is a top level one (i.e. doesn't have a parent), it will -be centred relative to the screen anyhow. +Remark: If the window is a top level one (i.e. doesn't have a parent), it will be centred +relative to the screen anyhow. See: `center/2` """. @@ -316,7 +463,7 @@ centre(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Centre). -%% @equiv centerOnParent(This, []) +-doc(#{equiv => centerOnParent(This, [])}). -spec centerOnParent(This) -> 'ok' when This::wxWindow(). @@ -324,7 +471,7 @@ centerOnParent(This) when is_record(This, wx_ref) -> centerOnParent(This, []). -%% @equiv centreOnParent(This, []) +-doc(#{equiv => centreOnParent(This, [])}). -spec centreOnParent(This) -> 'ok' when This::wxWindow(). @@ -332,8 +479,7 @@ centreOnParent(This) when is_record(This, wx_ref) -> centreOnParent(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcentreonparent">external documentation</a>. --doc "See: `centreOnParent/2`.". +-doc "Equivalent to: `centreOnParent/2`". -spec centerOnParent(This, [Option]) -> 'ok' when This::wxWindow(), Option :: {'dir', integer()}. @@ -342,15 +488,14 @@ centerOnParent(This, Options) when is_record(This, wx_ref),is_list(Options) -> centreOnParent(This, Options). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcentreonparent">external documentation</a>. -doc """ Centres the window on its parent. This is a more readable synonym for `centre/2`. -Remark: This methods provides for a way to centre top level windows over their -parents instead of the entire screen. If there is no parent or if the window is -not a top level window, then behaviour is the same as `centre/2`. +Remark: This methods provides for a way to centre top level windows over their parents +instead of the entire screen. If there is no parent or if the window is not a top level +window, then behaviour is the same as `centre/2`. See: `wxTopLevelWindow:centreOnScreen/2` """. @@ -365,16 +510,15 @@ centreOnParent(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_CentreOnParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowclearbackground">external documentation</a>. -doc """ Clears the window by filling it with the current background colour. Does not cause an erase background event to be generated. -Notice that this uses `m:wxClientDC` to draw on the window and the results of -doing it while also drawing on `m:wxPaintDC` for this window are undefined. -Hence this method shouldn't be used from EVT_PAINT handlers, just use -`wxDC:clear/1` on the `m:wxPaintDC` you already use there instead. +Notice that this uses `m:wxClientDC` to draw on the window and the results of doing it +while also drawing on `m:wxPaintDC` for this window are undefined. Hence this method +shouldn't be used from EVT_PAINT handlers, just use `wxDC:clear/1` on the `m:wxPaintDC` you already use +there instead. """. -spec clearBackground(This) -> 'ok' when This::wxWindow(). @@ -382,7 +526,6 @@ clearBackground(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_ClearBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowclienttoscreen">external documentation</a>. -doc "Converts to screen coordinates from coordinates relative to this window.". -spec clientToScreen(This, Pt) -> {X::integer(), Y::integer()} when This::wxWindow(), Pt::{X::integer(), Y::integer()}. @@ -392,7 +535,6 @@ clientToScreen(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxWindow_ClientToScreen_1), wxe_util:rec(?wxWindow_ClientToScreen_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowclienttoscreen">external documentation</a>. -doc "Converts to screen coordinates from coordinates relative to this window.". -spec clientToScreen(This, X, Y) -> {X::integer(), Y::integer()} when This::wxWindow(), X::integer(), Y::integer(). @@ -402,7 +544,7 @@ clientToScreen(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxWindow_ClientToScreen_2), wxe_util:rec(?wxWindow_ClientToScreen_2). -%% @equiv close(This, []) +-doc(#{equiv => close(This, [])}). -spec close(This) -> boolean() when This::wxWindow(). @@ -410,30 +552,30 @@ close(This) when is_record(This, wx_ref) -> close(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowclose">external documentation</a>. -doc """ -This function simply generates a `m:wxCloseEvent` whose handler usually tries to -close the window. +This function simply generates a `m:wxCloseEvent` whose handler usually tries to close +the window. It doesn't close the window itself, however. Return: true if the event was handled and not vetoed, false otherwise. -Remark: Close calls the close handler for the window, providing an opportunity -for the window to choose whether to destroy the window. Usually it is only used -with the top level windows (`m:wxFrame` and `m:wxDialog` classes) as the others -are not supposed to have any special OnClose() logic. The close handler should -check whether the window is being deleted forcibly, using -`wxCloseEvent:canVeto/1`, in which case it should destroy the window using -`'Destroy'/1`. Note that calling Close does not guarantee that the window will -be destroyed; but it provides a way to simulate a manual close of a window, -which may or may not be implemented by destroying the window. The default -implementation of wxDialog::OnCloseWindow does not necessarily delete the -dialog, since it will simply simulate an wxID_CANCEL event which is handled by -the appropriate button event handler and may do anything at all. To guarantee -that the window will be destroyed, call `'Destroy'/1` instead - -See: Window Deletion Overview, `'Destroy'/1`, `m:wxCloseEvent` +Remark: Close calls the close handler for the window, providing an opportunity for the +window to choose whether to destroy the window. Usually it is only used with the top level +windows (`m:wxFrame` and `m:wxDialog` classes) as the others are not supposed to have any +special OnClose() logic. The close handler should check whether the window is being +deleted forcibly, using `wxCloseEvent:canVeto/1`, in which case it should destroy the window using `'Destroy'/1`. Note that +calling Close does not guarantee that the window will be destroyed; but it provides a way +to simulate a manual close of a window, which may or may not be implemented by destroying +the window. The default implementation of wxDialog::OnCloseWindow does not necessarily +delete the dialog, since it will simply simulate an wxID_CANCEL event which is handled by +the appropriate button event handler and may do anything at all. To guarantee that the +window will be destroyed, call `'Destroy'/1` instead + +See: +* `'Destroy'/1` + +* `m:wxCloseEvent` """. -spec close(This, [Option]) -> boolean() when This::wxWindow(), @@ -447,10 +589,9 @@ close(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Close), wxe_util:rec(?wxWindow_Close). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowconvertdialogtopixels">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec convertDialogToPixels(This, Sz) -> {W::integer(), H::integer()} when This::wxWindow(), Sz::{W::integer(), H::integer()}. @@ -460,10 +601,9 @@ convertDialogToPixels(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz) wxe_util:queue_cmd(This,Sz,?get_env(),?wxWindow_ConvertDialogToPixels), wxe_util:rec(?wxWindow_ConvertDialogToPixels). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowconvertpixelstodialog">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec convertPixelsToDialog(This, Sz) -> {W::integer(), H::integer()} when This::wxWindow(), Sz::{W::integer(), H::integer()}. @@ -473,18 +613,17 @@ convertPixelsToDialog(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz) wxe_util:queue_cmd(This,Sz,?get_env(),?wxWindow_ConvertPixelsToDialog), wxe_util:rec(?wxWindow_ConvertPixelsToDialog). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowdestroy">external documentation</a>. -doc """ Destroys the window safely. -Use this function instead of the delete operator, since different window classes -can be destroyed differently. Frames and dialogs are not destroyed immediately -when this function is called - they are added to a list of windows to be deleted -on idle time, when all the window's events have been processed. This prevents -problems with events being sent to non-existent windows. +Use this function instead of the delete operator, since different window classes can be +destroyed differently. Frames and dialogs are not destroyed immediately when this function +is called - they are added to a list of windows to be deleted on idle time, when all the +window's events have been processed. This prevents problems with events being sent to +non-existent windows. -Return: true if the window has either been successfully deleted, or it has been -added to the list of windows pending real deletion. +Return: true if the window has either been successfully deleted, or it has been added to +the list of windows pending real deletion. """. -spec 'Destroy'(This) -> boolean() when This::wxWindow(). @@ -493,7 +632,6 @@ added to the list of windows pending real deletion. wxe_util:queue_cmd(This,?get_env(),?wxWindow_Destroy), wxe_util:rec(?wxWindow_Destroy). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowdestroychildren">external documentation</a>. -doc """ Destroys all children of a window. @@ -506,14 +644,13 @@ destroyChildren(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_DestroyChildren), wxe_util:rec(?wxWindow_DestroyChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowdisable">external documentation</a>. -doc """ Disables the window. Same as `enable/2` Enable(false). -Return: Returns true if the window has been disabled, false if it had been -already disabled before the call to this function. +Return: Returns true if the window has been disabled, false if it had been already +disabled before the call to this function. """. -spec disable(This) -> boolean() when This::wxWindow(). @@ -522,12 +659,11 @@ disable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_Disable), wxe_util:rec(?wxWindow_Disable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowdragacceptfiles">external documentation</a>. -doc """ Enables or disables eligibility for drop file events (OnDropFiles). -Remark: Windows only until version 2.8.9, available on all platforms since -2.8.10. Cannot be used together with `setDropTarget/2` on non-Windows platforms. +Remark: Windows only until version 2.8.9, available on all platforms since 2.8.10. Cannot +be used together with `setDropTarget/2` on non-Windows platforms. See: `setDropTarget/2` """. @@ -538,7 +674,7 @@ dragAcceptFiles(#wx_ref{type=ThisT}=This,Accept) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Accept,?get_env(),?wxWindow_DragAcceptFiles). -%% @equiv enable(This, []) +-doc(#{equiv => enable(This, [])}). -spec enable(This) -> boolean() when This::wxWindow(). @@ -546,20 +682,24 @@ enable(This) when is_record(This, wx_ref) -> enable(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowenable">external documentation</a>. -doc """ Enable or disable the window for user input. -Note that when a parent window is disabled, all of its children are disabled as -well and they are re-enabled again when the parent is. +Note that when a parent window is disabled, all of its children are disabled as well and +they are re-enabled again when the parent is. + +A window can be created initially disabled by calling this method on it `before` calling `create/4` +to create the actual underlying window, e.g. + +Return: Returns true if the window has been enabled or disabled, false if nothing was +done, i.e. if the window had already been in the specified state. -A window can be created initially disabled by calling this method on it `before` -calling `create/4` to create the actual underlying window, e.g. +See: +* `isEnabled/1` -Return: Returns true if the window has been enabled or disabled, false if -nothing was done, i.e. if the window had already been in the specified state. +* `disable/1` -See: `isEnabled/1`, `disable/1`, `wxRadioBox:enable/3` +* `wxRadioBox:enable/3` """. -spec enable(This, [Option]) -> boolean() when This::wxWindow(), @@ -573,32 +713,26 @@ enable(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Enable), wxe_util:rec(?wxWindow_Enable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfindfocus">external documentation</a>. -doc """ Finds the window or control which currently has the keyboard focus. -Remark: Note that this is a static function, so it can be called without needing -a `m:wxWindow` pointer. +Remark: Note that this is a static function, so it can be called without needing a `m:wxWindow` +pointer. -See: `setFocus/1`, `HasFocus()` (not implemented in wx) +See: `setFocus/1` """. -spec findFocus() -> wxWindow(). findFocus() -> wxe_util:queue_cmd(?get_env(), ?wxWindow_FindFocus), wxe_util:rec(?wxWindow_FindFocus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfindwindow">external documentation</a>. -%% <br /> Also:<br /> -%% findWindow(This, Name) -> wxWindow() when<br /> -%% This::wxWindow(), Name::unicode:chardata().<br /> -%% -doc """ Find a child of this window, by name. May return `this` if it matches itself. -Notice that only real children, not top level windows using this window as -parent, are searched by this function. +Notice that only real children, not top level windows using this window as parent, are +searched by this function. """. -spec findWindow(This, Id) -> wxWindow() when This::wxWindow(), Id::integer(); @@ -616,7 +750,7 @@ findWindow(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxWindow_FindWindow_1_1), wxe_util:rec(?wxWindow_FindWindow_1_1). -%% @equiv findWindowById(Id, []) +-doc(#{equiv => findWindowById(Id, [])}). -spec findWindowById(Id) -> wxWindow() when Id::integer(). @@ -624,13 +758,12 @@ findWindowById(Id) when is_integer(Id) -> findWindowById(Id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfindwindowbyid">external documentation</a>. -doc """ Find the first window with the given `id`. -If `parent` is NULL, the search will start from all top-level frames and dialog -boxes; if non-NULL, the search will be limited to the given window hierarchy. -The search is recursive in both cases. +If `parent` is NULL, the search will start from all top-level frames and dialog boxes; if +non-NULL, the search will be limited to the given window hierarchy. The search is +recursive in both cases. See: `findWindow/2` @@ -647,7 +780,7 @@ findWindowById(Id, Options) wxe_util:queue_cmd(Id, Opts,?get_env(),?wxWindow_FindWindowById), wxe_util:rec(?wxWindow_FindWindowById). -%% @equiv findWindowByName(Name, []) +-doc(#{equiv => findWindowByName(Name, [])}). -spec findWindowByName(Name) -> wxWindow() when Name::unicode:chardata(). @@ -655,22 +788,18 @@ findWindowByName(Name) when ?is_chardata(Name) -> findWindowByName(Name, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfindwindowbyname">external documentation</a>. -doc """ -Find a window by its name (as given in a window constructor or `create/4` -function call). +Find a window by its name (as given in a window constructor or `create/4` function call). -If `parent` is NULL, the search will start from all top-level frames and dialog -boxes; if non-NULL, the search will be limited to the given window hierarchy. +If `parent` is NULL, the search will start from all top-level frames and dialog boxes; if +non-NULL, the search will be limited to the given window hierarchy. -The search is recursive in both cases and, unlike `findWindow/2`, recurses into -top level child windows too. +The search is recursive in both cases and, unlike `findWindow/2`, recurses into top level child windows too. -If no window with such name is found, `findWindowByLabel/2` is called, i.e. the -name is interpreted as (internal) name first but if this fails, it's internal as -(user-visible) label. As this behaviour may be confusing, it is usually better -to use either the `findWindow/2` overload taking the name or -`findWindowByLabel/2` directly. +If no window with such name is found, `findWindowByLabel/2` is called, i.e. the name is interpreted as +(internal) name first but if this fails, it's internal as (user-visible) label. As this +behaviour may be confusing, it is usually better to use either the `findWindow/2` overload taking the +name or `findWindowByLabel/2` directly. Return: Window with the given `name` or NULL if not found. """. @@ -686,7 +815,7 @@ findWindowByName(Name, Options) wxe_util:queue_cmd(Name_UC, Opts,?get_env(),?wxWindow_FindWindowByName), wxe_util:rec(?wxWindow_FindWindowByName). -%% @equiv findWindowByLabel(Label, []) +-doc(#{equiv => findWindowByLabel(Label, [])}). -spec findWindowByLabel(Label) -> wxWindow() when Label::unicode:chardata(). @@ -694,17 +823,15 @@ findWindowByLabel(Label) when ?is_chardata(Label) -> findWindowByLabel(Label, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfindwindowbylabel">external documentation</a>. -doc """ Find a window by its label. -Depending on the type of window, the label may be a window title or panel item -label. If `parent` is NULL, the search will start from all top-level frames and -dialog boxes; if non-NULL, the search will be limited to the given window -hierarchy. +Depending on the type of window, the label may be a window title or panel item label. If `parent` +is NULL, the search will start from all top-level frames and dialog boxes; if non-NULL, +the search will be limited to the given window hierarchy. -The search is recursive in both cases and, unlike with `findWindow/2`, recurses -into top level child windows too. +The search is recursive in both cases and, unlike with `findWindow/2`, recurses into top level child +windows too. See: `findWindow/2` @@ -722,18 +849,15 @@ findWindowByLabel(Label, Options) wxe_util:queue_cmd(Label_UC, Opts,?get_env(),?wxWindow_FindWindowByLabel), wxe_util:rec(?wxWindow_FindWindowByLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfit">external documentation</a>. -doc """ Sizes the window to fit its best size. -Using this function is equivalent to setting window size to the return value of -`getBestSize/1`. +Using this function is equivalent to setting window size to the return value of `getBestSize/1`. -Note that, unlike `setSizerAndFit/3`, this function only changes the current -window size and doesn't change its minimal size. +Note that, unlike `setSizerAndFit/3`, this function only changes the current window size and doesn't change +its minimal size. -See: -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec fit(This) -> 'ok' when This::wxWindow(). @@ -741,13 +865,12 @@ fit(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Fit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfitinside">external documentation</a>. -doc """ Similar to `fit/1`, but sizes the interior (virtual) size of a window. -Mainly useful with scrolled windows to reset scrollbars after sizing changes -that do not trigger a size event, and/or scrolled windows without an interior -sizer. This function similarly won't do anything if there are no subwindows. +Mainly useful with scrolled windows to reset scrollbars after sizing changes that do not +trigger a size event, and/or scrolled windows without an interior sizer. This function +similarly won't do anything if there are no subwindows. """. -spec fitInside(This) -> 'ok' when This::wxWindow(). @@ -755,23 +878,25 @@ fitInside(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_FitInside). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfreeze">external documentation</a>. -doc """ -Freezes the window or, in other words, prevents any updates from taking place on -screen, the window is not redrawn at all. +Freezes the window or, in other words, prevents any updates from taking place on screen, +the window is not redrawn at all. -`thaw/1` must be called to re-enable window redrawing. Calls to these two -functions may be nested but to ensure that the window is properly repainted -again, you must thaw it exactly as many times as you froze it. +`thaw/1` must be called to re-enable window redrawing. Calls to these two functions may be nested +but to ensure that the window is properly repainted again, you must thaw it exactly as +many times as you froze it. If the window has any children, they are recursively frozen too. -This method is useful for visual appearance optimization (for example, it is a -good idea to use it before doing many large text insertions in a row into a -`m:wxTextCtrl` under wxGTK) but is not implemented on all platforms nor for all -controls so it is mostly just a hint to wxWidgets and not a mandatory directive. +This method is useful for visual appearance optimization (for example, it is a good idea +to use it before doing many large text insertions in a row into a `m:wxTextCtrl` under +wxGTK) but is not implemented on all platforms nor for all controls so it is mostly just a +hint to wxWidgets and not a mandatory directive. + +See: +* `thaw/1` -See: `wxWindowUpdateLocker` (not implemented in wx), `thaw/1`, `isFrozen/1` +* `isFrozen/1` """. -spec freeze(This) -> 'ok' when This::wxWindow(). @@ -779,7 +904,6 @@ freeze(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Freeze). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetacceleratortable">external documentation</a>. -doc """ Gets the accelerator table for this window. @@ -792,11 +916,15 @@ getAcceleratorTable(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetAcceleratorTable), wxe_util:rec(?wxWindow_GetAcceleratorTable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetbackgroundcolour">external documentation</a>. -doc """ Returns the background colour of the window. -See: `setBackgroundColour/2`, `setForegroundColour/2`, `getForegroundColour/1` +See: +* `setBackgroundColour/2` + +* `setForegroundColour/2` + +* `getForegroundColour/1` """. -spec getBackgroundColour(This) -> wx:wx_colour4() when This::wxWindow(). @@ -805,14 +933,19 @@ getBackgroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetBackgroundColour), wxe_util:rec(?wxWindow_GetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetbackgroundstyle">external documentation</a>. -%%<br /> Res = ?wxBG_STYLE_ERASE | ?wxBG_STYLE_SYSTEM | ?wxBG_STYLE_PAINT | ?wxBG_STYLE_COLOUR | ?wxBG_STYLE_TRANSPARENT -doc """ Returns the background style of the window. -See: `setBackgroundColour/2`, `getForegroundColour/1`, `setBackgroundStyle/2`, -`setTransparent/2` +See: +* `setBackgroundColour/2` + +* `getForegroundColour/1` + +* `setBackgroundStyle/2` + +* `setTransparent/2` """. +%% Res = ?wxBG_STYLE_ERASE | ?wxBG_STYLE_SYSTEM | ?wxBG_STYLE_PAINT | ?wxBG_STYLE_COLOUR | ?wxBG_STYLE_TRANSPARENT -spec getBackgroundStyle(This) -> wx:wx_enum() when This::wxWindow(). getBackgroundStyle(#wx_ref{type=ThisT}=This) -> @@ -820,27 +953,26 @@ getBackgroundStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetBackgroundStyle), wxe_util:rec(?wxWindow_GetBackgroundStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetbestsize">external documentation</a>. -doc """ This functions returns the best acceptable minimal size for the window. -For example, for a static control, it will be the minimal size such that the -control label is not truncated. For windows containing subwindows (typically -`m:wxPanel`), the size returned by this function will be the same as the size -the window would have had after calling `fit/1`. +For example, for a static control, it will be the minimal size such that the control +label is not truncated. For windows containing subwindows (typically `m:wxPanel`), the size +returned by this function will be the same as the size the window would have had after +calling `fit/1`. + +Override virtual `DoGetBestSize()` (not implemented in wx) or, better, because it's +usually more convenient, `DoGetBestClientSize()` (not implemented in wx) when writing your +own custom window class to change the value returned by this public non-virtual method. -Override virtual `DoGetBestSize()` (not implemented in wx) or, better, because -it's usually more convenient, `DoGetBestClientSize()` (not implemented in wx) -when writing your own custom window class to change the value returned by this -public non-virtual method. +Notice that the best size respects the minimal and maximal size explicitly set for the +window, if any. So even if some window believes that it needs 200 pixels horizontally, +calling `setMaxSize/2` with a width of 100 would ensure that `getBestSize/1` returns the width of at most 100 pixels. -Notice that the best size respects the minimal and maximal size explicitly set -for the window, if any. So even if some window believes that it needs 200 pixels -horizontally, calling `setMaxSize/2` with a width of 100 would ensure that -`getBestSize/1` returns the width of at most 100 pixels. +See: +* `cacheBestSize/2` -See: `cacheBestSize/2`, -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +* [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec getBestSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). @@ -849,7 +981,6 @@ getBestSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetBestSize), wxe_util:rec(?wxWindow_GetBestSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcaret">external documentation</a>. -doc "Returns the caret() associated with the window.". -spec getCaret(This) -> wxCaret:wxCaret() when This::wxWindow(). @@ -858,19 +989,25 @@ getCaret(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetCaret), wxe_util:rec(?wxWindow_GetCaret). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcapture">external documentation</a>. -doc """ Returns the currently captured window. -See: `hasCapture/1`, `captureMouse/1`, `releaseMouse/1`, -`m:wxMouseCaptureLostEvent`, `m:wxMouseCaptureChangedEvent` +See: +* `hasCapture/1` + +* `captureMouse/1` + +* `releaseMouse/1` + +* `m:wxMouseCaptureLostEvent` + +* `m:wxMouseCaptureChangedEvent` """. -spec getCapture() -> wxWindow(). getCapture() -> wxe_util:queue_cmd(?get_env(), ?wxWindow_GetCapture), wxe_util:rec(?wxWindow_GetCapture). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcharheight">external documentation</a>. -doc "Returns the character height for this window.". -spec getCharHeight(This) -> integer() when This::wxWindow(). @@ -879,7 +1016,6 @@ getCharHeight(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetCharHeight), wxe_util:rec(?wxWindow_GetCharHeight). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcharwidth">external documentation</a>. -doc "Returns the average character width for this window.". -spec getCharWidth(This) -> integer() when This::wxWindow(). @@ -888,12 +1024,10 @@ getCharWidth(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetCharWidth), wxe_util:rec(?wxWindow_GetCharWidth). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetchildren">external documentation</a>. -doc """ Returns a const reference to the list of the window's children. -`wxWindowList` is a type-safe wxList-like class whose elements are of type -`wxWindow*`. +`wxWindowList` is a type-safe wxList-like class whose elements are of type `wxWindow*`. """. -spec getChildren(This) -> [wxWindow()] when This::wxWindow(). @@ -902,10 +1036,9 @@ getChildren(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetChildren), wxe_util:rec(?wxWindow_GetChildren). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetclientsize">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec getClientSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). @@ -914,7 +1047,6 @@ getClientSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetClientSize), wxe_util:rec(?wxWindow_GetClientSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcontainingsizer">external documentation</a>. -doc "Returns the sizer of which this window is a member, if any, otherwise NULL.". -spec getContainingSizer(This) -> wxSizer:wxSizer() when This::wxWindow(). @@ -923,7 +1055,6 @@ getContainingSizer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetContainingSizer), wxe_util:rec(?wxWindow_GetContainingSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcursor">external documentation</a>. -doc """ Return the cursor associated with this window. @@ -936,12 +1067,13 @@ getCursor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetCursor), wxe_util:rec(?wxWindow_GetCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetdroptarget">external documentation</a>. -doc """ Returns the associated drop target, which may be NULL. -See: `setDropTarget/2`, -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd) +See: +* `setDropTarget/2` + +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) """. -spec getDropTarget(This) -> wx:wx_object() when This::wxWindow(). @@ -950,22 +1082,21 @@ getDropTarget(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetDropTarget), wxe_util:rec(?wxWindow_GetDropTarget). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetdpiscalefactor">external documentation</a>. -doc """ Returns the ratio of the DPI used by this window to the standard DPI. -The returned value is 1 for standard DPI screens or 2 for "200% scaling" and, -unlike for `getContentScaleFactor/1`, is the same under all platforms. +The returned value is 1 for standard DPI screens or 2 for "200% scaling" and, unlike for `getContentScaleFactor/1`, +is the same under all platforms. -This factor should be used to increase the size of icons and similar windows -whose best size is not based on text metrics when using DPI scaling. +This factor should be used to increase the size of icons and similar windows whose best +size is not based on text metrics when using DPI scaling. -E.g. the program may load a 32px bitmap if the content scale factor is 1.0 or -64px version of the same bitmap if it is 2.0 or bigger. +E.g. the program may load a 32px bitmap if the content scale factor is 1.0 or 64px +version of the same bitmap if it is 2.0 or bigger. -Notice that this method should `not` be used for window sizes expressed in -pixels, as they are already scaled by this factor by the underlying toolkit -under some platforms. Use `fromDIP/2` for anything window-related instead. +Notice that this method should `not` be used for window sizes expressed in pixels, as +they are already scaled by this factor by the underlying toolkit under some platforms. Use `fromDIP/2` +for anything window-related instead. Since: 3.1.4 """. @@ -976,7 +1107,6 @@ getDPIScaleFactor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetDPIScaleFactor), wxe_util:rec(?wxWindow_GetDPIScaleFactor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetextrastyle">external documentation</a>. -doc "Returns the extra style bits for the window.". -spec getExtraStyle(This) -> integer() when This::wxWindow(). @@ -985,7 +1115,6 @@ getExtraStyle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetExtraStyle), wxe_util:rec(?wxWindow_GetExtraStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetfont">external documentation</a>. -doc """ Returns the font for this window. @@ -998,14 +1127,18 @@ getFont(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetFont), wxe_util:rec(?wxWindow_GetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetforegroundcolour">external documentation</a>. -doc """ Returns the foreground colour of the window. -Remark: The meaning of foreground colour varies according to the window class; -it may be the text colour or other colour, or it may not be used at all. +Remark: The meaning of foreground colour varies according to the window class; it may be +the text colour or other colour, or it may not be used at all. + +See: +* `setForegroundColour/2` -See: `setForegroundColour/2`, `setBackgroundColour/2`, `getBackgroundColour/1` +* `setBackgroundColour/2` + +* `getBackgroundColour/1` """. -spec getForegroundColour(This) -> wx:wx_colour4() when This::wxWindow(). @@ -1014,7 +1147,6 @@ getForegroundColour(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetForegroundColour), wxe_util:rec(?wxWindow_GetForegroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetgrandparent">external documentation</a>. -doc "Returns the grandparent of a window, or NULL if there isn't one.". -spec getGrandParent(This) -> wxWindow() when This::wxWindow(). @@ -1023,12 +1155,11 @@ getGrandParent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetGrandParent), wxe_util:rec(?wxWindow_GetGrandParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgethandle">external documentation</a>. -doc """ Returns the platform-specific handle of the physical window. -Cast it to an appropriate handle, such as `HWND` for Windows, `Widget` for Motif -or `GtkWidget` for GTK. +Cast it to an appropriate handle, such as `HWND` for Windows, `Widget` for Motif or `GtkWidget` +for GTK. """. -spec getHandle(This) -> integer() when This::wxWindow(). @@ -1037,15 +1168,13 @@ getHandle(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetHandle), wxe_util:rec(?wxWindow_GetHandle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgethelptext">external documentation</a>. -doc """ Gets the help text to be used as context-sensitive help for this window. -Note that the text is actually stored by the current `wxHelpProvider` (not -implemented in wx) implementation, and not in the window object itself. +Note that the text is actually stored by the current `wxHelpProvider` (not implemented in +wx) implementation, and not in the window object itself. -See: `setHelpText/2`, `GetHelpTextAtPoint()` (not implemented in wx), -`wxHelpProvider` (not implemented in wx) +See: `setHelpText/2` """. -spec getHelpText(This) -> unicode:charlist() when This::wxWindow(). @@ -1054,16 +1183,16 @@ getHelpText(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetHelpText), wxe_util:rec(?wxWindow_GetHelpText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetid">external documentation</a>. -doc """ Returns the identifier of the window. -Remark: Each window has an integer identifier. If the application has not -provided one (or the default wxID_ANY) a unique identifier with a negative value -will be generated. +Remark: Each window has an integer identifier. If the application has not provided one +(or the default wxID_ANY) a unique identifier with a negative value will be generated. + +See: +* `setId/2` -See: `setId/2`, -[Overview windowids](https://docs.wxwidgets.org/3.1/overview_windowids.html#overview_windowids) +* [Overview windowids](https://docs.wxwidgets.org/3.2/overview_windowids.html#overview_windowids) """. -spec getId(This) -> integer() when This::wxWindow(). @@ -1072,15 +1201,13 @@ getId(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetId), wxe_util:rec(?wxWindow_GetId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetlabel">external documentation</a>. -doc """ Generic way of getting a label from any window, for identification purposes. -Remark: The interpretation of this function differs from class to class. For -frames and dialogs, the value returned is the title. For buttons or static text -controls, it is the button text. This function can be useful for meta-programs -(such as testing tools or special-needs access programs) which need to identify -windows by name. +Remark: The interpretation of this function differs from class to class. For frames and +dialogs, the value returned is the title. For buttons or static text controls, it is the +button text. This function can be useful for meta-programs (such as testing tools or +special-needs access programs) which need to identify windows by name. """. -spec getLabel(This) -> unicode:charlist() when This::wxWindow(). @@ -1089,16 +1216,13 @@ getLabel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetLabel), wxe_util:rec(?wxWindow_GetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetmaxsize">external documentation</a>. -doc """ Returns the maximum size of the window. -This is an indication to the sizer layout mechanism that this is the maximum -possible size as well as the upper bound on window's size settable using -`setSize/6`. +This is an indication to the sizer layout mechanism that this is the maximum possible +size as well as the upper bound on window's size settable using `setSize/6`. -See: `GetMaxClientSize()` (not implemented in wx), -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec getMaxSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). @@ -1107,16 +1231,14 @@ getMaxSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetMaxSize), wxe_util:rec(?wxWindow_GetMaxSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetminsize">external documentation</a>. -doc """ -Returns the minimum size of the window, an indication to the sizer layout -mechanism that this is the minimum required size. +Returns the minimum size of the window, an indication to the sizer layout mechanism that +this is the minimum required size. -This method normally just returns the value set by `setMinSize/2`, but it can be -overridden to do the calculation on demand. +This method normally just returns the value set by `setMinSize/2`, but it can be overridden to do the +calculation on demand. -See: `GetMinClientSize()` (not implemented in wx), -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec getMinSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). @@ -1125,12 +1247,11 @@ getMinSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetMinSize), wxe_util:rec(?wxWindow_GetMinSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetname">external documentation</a>. -doc """ Returns the window's name. -Remark: This name is not guaranteed to be unique; it is up to the programmer to -supply an appropriate name in the window constructor or via `setName/2`. +Remark: This name is not guaranteed to be unique; it is up to the programmer to supply an +appropriate name in the window constructor or via `setName/2`. See: `setName/2` """. @@ -1141,7 +1262,6 @@ getName(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetName), wxe_util:rec(?wxWindow_GetName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetparent">external documentation</a>. -doc "Returns the parent of the window, or NULL if there is no parent.". -spec getParent(This) -> wxWindow() when This::wxWindow(). @@ -1150,11 +1270,9 @@ getParent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetParent), wxe_util:rec(?wxWindow_GetParent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetposition">external documentation</a>. -doc """ -This gets the position of the window in pixels, relative to the parent window -for the child windows or relative to the display origin for the top level -windows. +This gets the position of the window in pixels, relative to the parent window for the +child windows or relative to the display origin for the top level windows. See: `getScreenPosition/1` """. @@ -1165,9 +1283,8 @@ getPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetPosition), wxe_util:rec(?wxWindow_GetPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetrect">external documentation</a>. -doc """ -Returns the position and size of the window as a \{X,Y,W,H\} object. +Returns the position and size of the window as a {X,Y,W,H} object. See: `getScreenRect/1` """. @@ -1178,10 +1295,9 @@ getRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetRect), wxe_util:rec(?wxWindow_GetRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetscreenposition">external documentation</a>. -doc """ -Returns the window position in screen coordinates, whether the window is a child -window or a top level one. +Returns the window position in screen coordinates, whether the window is a child window +or a top level one. See: `getPosition/1` """. @@ -1192,10 +1308,8 @@ getScreenPosition(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetScreenPosition), wxe_util:rec(?wxWindow_GetScreenPosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetscreenrect">external documentation</a>. -doc """ -Returns the position and size of the window on the screen as a \{X,Y,W,H\} -object. +Returns the position and size of the window on the screen as a {X,Y,W,H} object. See: `getRect/1` """. @@ -1206,7 +1320,6 @@ getScreenRect(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetScreenRect), wxe_util:rec(?wxWindow_GetScreenRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetscrollpos">external documentation</a>. -doc """ Returns the built-in scrollbar position. @@ -1220,7 +1333,6 @@ getScrollPos(#wx_ref{type=ThisT}=This,Orientation) wxe_util:queue_cmd(This,Orientation,?get_env(),?wxWindow_GetScrollPos), wxe_util:rec(?wxWindow_GetScrollPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetscrollrange">external documentation</a>. -doc """ Returns the built-in scrollbar range. @@ -1234,7 +1346,6 @@ getScrollRange(#wx_ref{type=ThisT}=This,Orientation) wxe_util:queue_cmd(This,Orientation,?get_env(),?wxWindow_GetScrollRange), wxe_util:rec(?wxWindow_GetScrollRange). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetscrollthumb">external documentation</a>. -doc """ Returns the built-in scrollbar thumb size. @@ -1248,8 +1359,7 @@ getScrollThumb(#wx_ref{type=ThisT}=This,Orientation) wxe_util:queue_cmd(This,Orientation,?get_env(),?wxWindow_GetScrollThumb), wxe_util:rec(?wxWindow_GetScrollThumb). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetsize">external documentation</a>. --doc "See the GetSize(int*,int*) overload for more info.". +-doc "See the GetSize(int\*,int\*) overload for more info.". -spec getSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). getSize(#wx_ref{type=ThisT}=This) -> @@ -1257,11 +1367,7 @@ getSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetSize), wxe_util:rec(?wxWindow_GetSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetsizer">external documentation</a>. --doc """ -Returns the sizer associated with the window by a previous call to `setSizer/3`, -or NULL. -""". +-doc "Returns the sizer associated with the window by a previous call to `setSizer/3`, or NULL.". -spec getSizer(This) -> wxSizer:wxSizer() when This::wxWindow(). getSizer(#wx_ref{type=ThisT}=This) -> @@ -1269,7 +1375,7 @@ getSizer(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetSizer), wxe_util:rec(?wxWindow_GetSizer). -%% @equiv getTextExtent(This,String, []) +-doc(#{equiv => getTextExtent(This,String, [])}). -spec getTextExtent(This, String) -> Result when Result ::{W::integer(), H::integer(), Descent::integer(), ExternalLeading::integer()}, This::wxWindow(), String::unicode:chardata(). @@ -1278,10 +1384,9 @@ getTextExtent(This,String) when is_record(This, wx_ref),?is_chardata(String) -> getTextExtent(This,String, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgettextextent">external documentation</a>. -doc """ -Gets the dimensions of the string as it would be drawn on the window with the -currently selected font. +Gets the dimensions of the string as it would be drawn on the window with the currently +selected font. The text extent is returned in the `w` and `h` pointers. """. @@ -1299,7 +1404,6 @@ getTextExtent(#wx_ref{type=ThisT}=This,String, Options) wxe_util:queue_cmd(This,String_UC, Opts,?get_env(),?wxWindow_GetTextExtent), wxe_util:rec(?wxWindow_GetTextExtent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetthemeenabled">external documentation</a>. -doc """ Returns true if the window uses the system theme for drawing its background. @@ -1312,7 +1416,6 @@ getThemeEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetThemeEnabled), wxe_util:rec(?wxWindow_GetThemeEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgettooltip">external documentation</a>. -doc "Get the associated tooltip or NULL if none.". -spec getToolTip(This) -> wxToolTip:wxToolTip() when This::wxWindow(). @@ -1321,15 +1424,14 @@ getToolTip(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetToolTip), wxe_util:rec(?wxWindow_GetToolTip). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetupdateregion">external documentation</a>. -doc """ -Gets the dimensions of the string as it would be drawn on the window with the -currently selected font. +Gets the dimensions of the string as it would be drawn on the window with the currently +selected font. -Returns the region specifying which parts of the window have been damaged. -Should only be called within an `m:wxPaintEvent` handler. +Returns the region specifying which parts of the window have been damaged. Should only be +called within an `m:wxPaintEvent` handler. -See: `m:wxRegion`, `wxRegionIterator` (not implemented in wx) +See: `m:wxRegion` """. -spec getUpdateRegion(This) -> wxRegion:wxRegion() when This::wxWindow(). @@ -1338,15 +1440,13 @@ getUpdateRegion(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetUpdateRegion), wxe_util:rec(?wxWindow_GetUpdateRegion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetvirtualsize">external documentation</a>. -doc """ This gets the virtual size of the window in pixels. -By default it returns the client size of the window, but after a call to -`setVirtualSize/3` it will return the size set with that method. +By default it returns the client size of the window, but after a call to `setVirtualSize/3` it will return +the size set with that method. -See: -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec getVirtualSize(This) -> {W::integer(), H::integer()} when This::wxWindow(). @@ -1355,12 +1455,10 @@ getVirtualSize(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetVirtualSize), wxe_util:rec(?wxWindow_GetVirtualSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetwindowstyleflag">external documentation</a>. -doc """ Gets the window style that was passed to the constructor or `create/4` method. -`GetWindowStyle()` (not implemented in wx) is another name for the same -function. +`GetWindowStyle()` (not implemented in wx) is another name for the same function. """. -spec getWindowStyleFlag(This) -> integer() when This::wxWindow(). @@ -1369,9 +1467,8 @@ getWindowStyleFlag(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetWindowStyleFlag), wxe_util:rec(?wxWindow_GetWindowStyleFlag). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetwindowvariant">external documentation</a>. -%%<br /> Res = ?wxWINDOW_VARIANT_NORMAL | ?wxWINDOW_VARIANT_SMALL | ?wxWINDOW_VARIANT_MINI | ?wxWINDOW_VARIANT_LARGE | ?wxWINDOW_VARIANT_MAX -doc "Returns the value previously passed to `setWindowVariant/2`.". +%% Res = ?wxWINDOW_VARIANT_NORMAL | ?wxWINDOW_VARIANT_SMALL | ?wxWINDOW_VARIANT_MINI | ?wxWINDOW_VARIANT_LARGE | ?wxWINDOW_VARIANT_MAX -spec getWindowVariant(This) -> wx:wx_enum() when This::wxWindow(). getWindowVariant(#wx_ref{type=ThisT}=This) -> @@ -1379,12 +1476,17 @@ getWindowVariant(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetWindowVariant), wxe_util:rec(?wxWindow_GetWindowVariant). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowhascapture">external documentation</a>. -doc """ Returns true if this window has the current mouse capture. -See: `captureMouse/1`, `releaseMouse/1`, `m:wxMouseCaptureLostEvent`, -`m:wxMouseCaptureChangedEvent` +See: +* `captureMouse/1` + +* `releaseMouse/1` + +* `m:wxMouseCaptureLostEvent` + +* `m:wxMouseCaptureChangedEvent` """. -spec hasCapture(This) -> boolean() when This::wxWindow(). @@ -1393,14 +1495,12 @@ hasCapture(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_HasCapture), wxe_util:rec(?wxWindow_HasCapture). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowhasscrollbar">external documentation</a>. -doc """ Returns true if this window currently has a scroll bar for this orientation. -This method may return false even when `CanScroll()` (not implemented in wx) for -the same orientation returns true, but if `CanScroll()` (not implemented in wx) -returns false, i.e. scrolling in this direction is not enabled at all, -`hasScrollbar/2` always returns false as well. +This method may return false even when `CanScroll()` (not implemented in wx) for the same +orientation returns true, but if `CanScroll()` (not implemented in wx) returns false, i.e. +scrolling in this direction is not enabled at all, `hasScrollbar/2` always returns false as well. """. -spec hasScrollbar(This, Orient) -> boolean() when This::wxWindow(), Orient::integer(). @@ -1410,14 +1510,13 @@ hasScrollbar(#wx_ref{type=ThisT}=This,Orient) wxe_util:queue_cmd(This,Orient,?get_env(),?wxWindow_HasScrollbar), wxe_util:rec(?wxWindow_HasScrollbar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowhastransparentbackground">external documentation</a>. -doc """ -Returns true if this window background is transparent (as, for example, for -`m:wxStaticText`) and should show the parent window background. +Returns true if this window background is transparent (as, for example, for `m:wxStaticText`) +and should show the parent window background. -This method is mostly used internally by the library itself and you normally -shouldn't have to call it. You may, however, have to override it in your -wxWindow-derived class to ensure that background is painted correctly. +This method is mostly used internally by the library itself and you normally shouldn't +have to call it. You may, however, have to override it in your wxWindow-derived class to +ensure that background is painted correctly. """. -spec hasTransparentBackground(This) -> boolean() when This::wxWindow(). @@ -1426,7 +1525,6 @@ hasTransparentBackground(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_HasTransparentBackground), wxe_util:rec(?wxWindow_HasTransparentBackground). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowhide">external documentation</a>. -doc "Equivalent to calling `show/2`(false).". -spec hide(This) -> boolean() when This::wxWindow(). @@ -1435,29 +1533,25 @@ hide(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_Hide), wxe_util:rec(?wxWindow_Hide). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowinheritattributes">external documentation</a>. --doc """ -This function is (or should be, in case of custom controls) called during window -creation to intelligently set up the window visual attributes, that is the font -and the foreground and background colours. - -By "intelligently" the following is meant: by default, all windows use their own -`GetClassDefaultAttributes()` (not implemented in wx) default attributes. -However if some of the parents attributes are explicitly (that is, using -`setFont/2` and not `setOwnFont/2`) changed and if the corresponding attribute -hadn't been explicitly set for this window itself, then this window takes the -same value as used by the parent. In addition, if the window overrides -`shouldInheritColours/1` to return false, the colours will not be changed no -matter what and only the font might. - -This rather complicated logic is necessary in order to accommodate the different -usage scenarios. The most common one is when all default attributes are used and -in this case, nothing should be inherited as in modern GUIs different controls -use different fonts (and colours) than their siblings so they can't inherit the -same value from the parent. However it was also deemed desirable to allow to -simply change the attributes of all children at once by just changing the font -or colour of their common parent, hence in this case we do inherit the parents -attributes. +-doc """ +This function is (or should be, in case of custom controls) called during window creation +to intelligently set up the window visual attributes, that is the font and the foreground +and background colours. + +By "intelligently" the following is meant: by default, all windows use their own `GetClassDefaultAttributes()` +(not implemented in wx) default attributes. However if some of the parents attributes are +explicitly (that is, using `setFont/2` and not `setOwnFont/2`) changed and if the corresponding attribute hadn't +been explicitly set for this window itself, then this window takes the same value as used +by the parent. In addition, if the window overrides `shouldInheritColours/1` to return false, the colours will not +be changed no matter what and only the font might. + +This rather complicated logic is necessary in order to accommodate the different usage +scenarios. The most common one is when all default attributes are used and in this case, +nothing should be inherited as in modern GUIs different controls use different fonts (and +colours) than their siblings so they can't inherit the same value from the parent. However +it was also deemed desirable to allow to simply change the attributes of all children at +once by just changing the font or colour of their common parent, hence in this case we do +inherit the parents attributes. """. -spec inheritAttributes(This) -> 'ok' when This::wxWindow(). @@ -1465,10 +1559,9 @@ inheritAttributes(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_InheritAttributes). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowinitdialog">external documentation</a>. -doc """ -Sends an `wxEVT_INIT_DIALOG` event, whose handler usually transfers data to the -dialog via validators. +Sends an `wxEVT\_INIT\_DIALOG` event, whose handler usually transfers data to the dialog +via validators. """. -spec initDialog(This) -> 'ok' when This::wxWindow(). @@ -1476,10 +1569,8 @@ initDialog(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_InitDialog). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowinvalidatebestsize">external documentation</a>. -doc """ -Resets the cached best size value so it will be recalculated the next time it is -needed. +Resets the cached best size value so it will be recalculated the next time it is needed. See: `cacheBestSize/2` """. @@ -1489,11 +1580,13 @@ invalidateBestSize(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_InvalidateBestSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisfrozen">external documentation</a>. -doc """ Returns true if the window is currently frozen by a call to `freeze/1`. -See: `freeze/1`, `thaw/1` +See: +* `freeze/1` + +* `thaw/1` """. -spec isFrozen(This) -> boolean() when This::wxWindow(). @@ -1502,14 +1595,12 @@ isFrozen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsFrozen), wxe_util:rec(?wxWindow_IsFrozen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisenabled">external documentation</a>. -doc """ -Returns true if the window is enabled, i.e. if it accepts user input, false -otherwise. +Returns true if the window is enabled, i.e. if it accepts user input, false otherwise. Notice that this method can return false even if this window itself hadn't been -explicitly disabled when one of its parent windows is disabled. To get the -intrinsic status of this window, use `IsThisEnabled()` (not implemented in wx) +explicitly disabled when one of its parent windows is disabled. To get the intrinsic +status of this window, use `IsThisEnabled()` (not implemented in wx) See: `enable/2` """. @@ -1520,14 +1611,9 @@ isEnabled(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsEnabled), wxe_util:rec(?wxWindow_IsEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisexposed">external documentation</a>. -%% <br /> Also:<br /> -%% isExposed(This, Rect) -> boolean() when<br /> -%% This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}.<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec isExposed(This, Pt) -> boolean() when This::wxWindow(), Pt::{X::integer(), Y::integer()}; @@ -1544,13 +1630,12 @@ isExposed(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) wxe_util:queue_cmd(This,Rect,?get_env(),?wxWindow_IsExposed_1_1), wxe_util:rec(?wxWindow_IsExposed_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisexposed">external documentation</a>. -doc """ -Returns true if the given point or rectangle area has been exposed since the -last repaint. +Returns true if the given point or rectangle area has been exposed since the last +repaint. -Call this in an paint event handler to optimize redrawing by only redrawing -those areas, which have been exposed. +Call this in an paint event handler to optimize redrawing by only redrawing those areas, +which have been exposed. """. -spec isExposed(This, X, Y) -> boolean() when This::wxWindow(), X::integer(), Y::integer(). @@ -1560,10 +1645,9 @@ isExposed(#wx_ref{type=ThisT}=This,X,Y) wxe_util:queue_cmd(This,X,Y,?get_env(),?wxWindow_IsExposed_2), wxe_util:rec(?wxWindow_IsExposed_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisexposed">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec isExposed(This, X, Y, W, H) -> boolean() when This::wxWindow(), X::integer(), Y::integer(), W::integer(), H::integer(). @@ -1573,7 +1657,6 @@ isExposed(#wx_ref{type=ThisT}=This,X,Y,W,H) wxe_util:queue_cmd(This,X,Y,W,H,?get_env(),?wxWindow_IsExposed_4), wxe_util:rec(?wxWindow_IsExposed_4). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisretained">external documentation</a>. -doc """ Returns true if the window is retained, false otherwise. @@ -1586,7 +1669,6 @@ isRetained(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsRetained), wxe_util:rec(?wxWindow_IsRetained). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisshown">external documentation</a>. -doc """ Returns true if the window is shown, false if it has been hidden. @@ -1599,12 +1681,11 @@ isShown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsShown), wxe_util:rec(?wxWindow_IsShown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowistoplevel">external documentation</a>. -doc """ Returns true if the given window is a top-level one. -Currently all frames and dialogs are considered to be top-level windows (even if -they have a parent window). +Currently all frames and dialogs are considered to be top-level windows (even if they +have a parent window). """. -spec isTopLevel(This) -> boolean() when This::wxWindow(). @@ -1613,10 +1694,9 @@ isTopLevel(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsTopLevel), wxe_util:rec(?wxWindow_IsTopLevel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisshownonscreen">external documentation</a>. -doc """ -Returns true if the window is physically visible on the screen, i.e. it is shown -and all its parents up to the toplevel window are shown as well. +Returns true if the window is physically visible on the screen, i.e. it is shown and all +its parents up to the toplevel window are shown as well. See: `isShown/1` """. @@ -1627,20 +1707,17 @@ isShownOnScreen(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsShownOnScreen), wxe_util:rec(?wxWindow_IsShownOnScreen). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowlayout">external documentation</a>. -doc """ Lays out the children of this window using the associated sizer. -If a sizer hadn't been associated with this window (see `setSizer/3`), this -function doesn't do anything, unless this is a top level window (see -`layout/1`). +If a sizer hadn't been associated with this window (see `setSizer/3`), this function doesn't do +anything, unless this is a top level window (see `layout/1`). -Note that this method is called automatically when the window size changes if it -has the associated sizer (or if `setAutoLayout/2` with true argument had been -explicitly called), ensuring that it is always laid out correctly. +Note that this method is called automatically when the window size changes if it has the +associated sizer (or if `setAutoLayout/2` with true argument had been explicitly called), ensuring that it +is always laid out correctly. -See: -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) Return: Always returns true, the return value is not useful. """. @@ -1651,7 +1728,6 @@ layout(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_Layout), wxe_util:rec(?wxWindow_Layout). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowlinedown">external documentation</a>. -doc "Same as `scrollLines/2` (1).". -spec lineDown(This) -> boolean() when This::wxWindow(). @@ -1660,7 +1736,6 @@ lineDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_LineDown), wxe_util:rec(?wxWindow_LineDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowlineup">external documentation</a>. -doc "Same as `scrollLines/2` (-1).". -spec lineUp(This) -> boolean() when This::wxWindow(). @@ -1669,7 +1744,6 @@ lineUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_LineUp), wxe_util:rec(?wxWindow_LineUp). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowlower">external documentation</a>. -doc """ Lowers the window to the bottom of the window hierarchy (Z-order). @@ -1683,7 +1757,7 @@ lower(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Lower). -%% @equiv move(This,Pt, []) +-doc(#{equiv => move(This,Pt, [])}). -spec move(This, Pt) -> 'ok' when This::wxWindow(), Pt::{X::integer(), Y::integer()}. @@ -1691,17 +1765,11 @@ move(This,{PtX,PtY} = Pt) when is_record(This, wx_ref),is_integer(PtX),is_integer(PtY) -> move(This,Pt, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowmove">external documentation</a>. -%% <br /> Also:<br /> -%% move(This, Pt, [Option]) -> 'ok' when<br /> -%% This::wxWindow(), Pt::{X::integer(), Y::integer()},<br /> -%% Option :: {'flags', integer()}.<br /> -%% -doc """ Moves the window to the given position. -Remark: Implementations of `setSize/6` can also implicitly implement the -`move/4` function, which is defined in the base `m:wxWindow` class as the call: +Remark: Implementations of `setSize/6` can also implicitly implement the `move/4` function, which is defined +in the base `m:wxWindow` class as the call: See: `setSize/6` """. @@ -1722,12 +1790,11 @@ move(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Pt, Opts,?get_env(),?wxWindow_Move_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowmove">external documentation</a>. -doc """ Moves the window to the given position. -Remark: Implementations of SetSize can also implicitly implement the `move/4` -function, which is defined in the base `m:wxWindow` class as the call: +Remark: Implementations of SetSize can also implicitly implement the `move/4` function, which is +defined in the base `m:wxWindow` class as the call: See: `setSize/6` """. @@ -1742,15 +1809,14 @@ move(#wx_ref{type=ThisT}=This,X,Y, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,X,Y, Opts,?get_env(),?wxWindow_Move_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowmoveafterintaborder">external documentation</a>. -doc """ Moves this window in the tab navigation order after the specified `win`. -This means that when the user presses `TAB` key on that other window, the focus -switches to this window. +This means that when the user presses `TAB` key on that other window, the focus switches +to this window. -Default tab order is the same as creation order, this function and -`moveBeforeInTabOrder/2` allow to change it after creating all the windows. +Default tab order is the same as creation order, this function and `moveBeforeInTabOrder/2` allow to change it +after creating all the windows. """. -spec moveAfterInTabOrder(This, Win) -> 'ok' when This::wxWindow(), Win::wxWindow(). @@ -1759,10 +1825,9 @@ moveAfterInTabOrder(#wx_ref{type=ThisT}=This,#wx_ref{type=WinT}=Win) -> ?CLASS(WinT,wxWindow), wxe_util:queue_cmd(This,Win,?get_env(),?wxWindow_MoveAfterInTabOrder). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowmovebeforeintaborder">external documentation</a>. -doc """ -Same as `moveAfterInTabOrder/2` except that it inserts this window just before -`win` instead of putting it right after it. +Same as `moveAfterInTabOrder/2` except that it inserts this window just before `win` +instead of putting it right after it. """. -spec moveBeforeInTabOrder(This, Win) -> 'ok' when This::wxWindow(), Win::wxWindow(). @@ -1771,7 +1836,7 @@ moveBeforeInTabOrder(#wx_ref{type=ThisT}=This,#wx_ref{type=WinT}=Win) -> ?CLASS(WinT,wxWindow), wxe_util:queue_cmd(This,Win,?get_env(),?wxWindow_MoveBeforeInTabOrder). -%% @equiv navigate(This, []) +-doc(#{equiv => navigate(This, [])}). -spec navigate(This) -> boolean() when This::wxWindow(). @@ -1779,21 +1844,18 @@ navigate(This) when is_record(This, wx_ref) -> navigate(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindownavigate">external documentation</a>. -doc """ Performs a keyboard navigation action starting from this window. -This method is equivalent to calling `NavigateIn()` (not implemented in wx) -method on the parent window. +This method is equivalent to calling `NavigateIn()` (not implemented in wx) method on the +parent window. -Return: Returns true if the focus was moved to another window or false if -nothing changed. +Return: Returns true if the focus was moved to another window or false if nothing changed. -Remark: You may wish to call this from a text control custom keypress handler to -do the default navigation behaviour for the tab key, since the standard default -behaviour for a multiline text control with the wxTE_PROCESS_TAB style is to -insert a tab and not navigate to the next control. See also -`m:wxNavigationKeyEvent` and HandleAsNavigationKey. +Remark: You may wish to call this from a text control custom keypress handler to do the +default navigation behaviour for the tab key, since the standard default behaviour for a +multiline text control with the wxTE_PROCESS_TAB style is to insert a tab and not navigate +to the next control. See also `m:wxNavigationKeyEvent` and HandleAsNavigationKey. """. -spec navigate(This, [Option]) -> boolean() when This::wxWindow(), @@ -1807,7 +1869,6 @@ navigate(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Navigate), wxe_util:rec(?wxWindow_Navigate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowpagedown">external documentation</a>. -doc "Same as `scrollPages/2` (1).". -spec pageDown(This) -> boolean() when This::wxWindow(). @@ -1816,7 +1877,6 @@ pageDown(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_PageDown), wxe_util:rec(?wxWindow_PageDown). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowpageup">external documentation</a>. -doc "Same as `scrollPages/2` (-1).". -spec pageUp(This) -> boolean() when This::wxWindow(). @@ -1825,7 +1885,7 @@ pageUp(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_PageUp), wxe_util:rec(?wxWindow_PageUp). -%% @equiv popupMenu(This,Menu, []) +-doc(#{equiv => popupMenu(This,Menu, [])}). -spec popupMenu(This, Menu) -> boolean() when This::wxWindow(), Menu::wxMenu:wxMenu(). @@ -1833,28 +1893,25 @@ popupMenu(This,Menu) when is_record(This, wx_ref),is_record(Menu, wx_ref) -> popupMenu(This,Menu, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowpopupmenu">external documentation</a>. -doc """ -Pops up the given menu at the specified coordinates, relative to this window, -and returns control when the user has dismissed the menu. +Pops up the given menu at the specified coordinates, relative to this window, and returns +control when the user has dismissed the menu. -If a menu item is selected, the corresponding menu event is generated and will -be processed as usual. If coordinates are not specified, the current mouse -cursor position is used. +If a menu item is selected, the corresponding menu event is generated and will be +processed as usual. If coordinates are not specified, the current mouse cursor position is used. `menu` is the menu to pop up. -The position where the menu will appear can be specified either as a \{X,Y\} -`pos` or by two integers (`x` and `y`). +The position where the menu will appear can be specified either as a {X,Y} `pos` or by +two integers (`x` and `y`). Note that this function switches focus to this window before showing the menu. -Remark: Just before the menu is popped up, `wxMenu::UpdateUI` (not implemented -in wx) is called to ensure that the menu items are in the correct state. The -menu does not get deleted by the window. It is recommended to not explicitly -specify coordinates when calling PopupMenu in response to mouse click, because -some of the ports (namely, wxGTK) can do a better job of positioning the menu in -that case. +Remark: Just before the menu is popped up, `wxMenu::UpdateUI` (not implemented in wx) is +called to ensure that the menu items are in the correct state. The menu does not get +deleted by the window. It is recommended to not explicitly specify coordinates when +calling PopupMenu in response to mouse click, because some of the ports (namely, wxGTK) +can do a better job of positioning the menu in that case. See: `m:wxMenu` """. @@ -1871,10 +1928,9 @@ popupMenu(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu, Options) wxe_util:queue_cmd(This,Menu, Opts,?get_env(),?wxWindow_PopupMenu_2), wxe_util:rec(?wxWindow_PopupMenu_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowpopupmenu">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec popupMenu(This, Menu, X, Y) -> boolean() when This::wxWindow(), Menu::wxMenu:wxMenu(), X::integer(), Y::integer(). @@ -1885,14 +1941,13 @@ popupMenu(#wx_ref{type=ThisT}=This,#wx_ref{type=MenuT}=Menu,X,Y) wxe_util:queue_cmd(This,Menu,X,Y,?get_env(),?wxWindow_PopupMenu_3), wxe_util:rec(?wxWindow_PopupMenu_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowraise">external documentation</a>. -doc """ Raises the window to the top of the window hierarchy (Z-order). -Notice that this function only requests the window manager to raise this window -to the top of Z-order. Depending on its configuration, the window manager may -raise the window, not do it at all or indicate that a window requested to be -raised in some other way, e.g. by flashing its icon if it is minimized. +Notice that this function only requests the window manager to raise this window to the +top of Z-order. Depending on its configuration, the window manager may raise the window, +not do it at all or indicate that a window requested to be raised in some other way, e.g. +by flashing its icon if it is minimized. Remark: This function only works for wxTopLevelWindow-derived classes. @@ -1904,7 +1959,7 @@ raise(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Raise). -%% @equiv refresh(This, []) +-doc(#{equiv => refresh(This, [])}). -spec refresh(This) -> 'ok' when This::wxWindow(). @@ -1912,14 +1967,12 @@ refresh(This) when is_record(This, wx_ref) -> refresh(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowrefresh">external documentation</a>. -doc """ -Causes this window, and all of its children recursively (except under wxGTK1 -where this is not implemented), to be repainted. +Causes this window, and all of its children recursively (except under wxGTK1 where this +is not implemented), to be repainted. -Note that repainting doesn't happen immediately but only during the next event -loop iteration, if you need to update the window immediately you should use -`update/1` instead. +Note that repainting doesn't happen immediately but only during the next event loop +iteration, if you need to update the window immediately you should use `update/1` instead. See: `refreshRect/3` """. @@ -1936,7 +1989,7 @@ refresh(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Refresh). -%% @equiv refreshRect(This,Rect, []) +-doc(#{equiv => refreshRect(This,Rect, [])}). -spec refreshRect(This, Rect) -> 'ok' when This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}. @@ -1944,14 +1997,11 @@ refreshRect(This,{RectX,RectY,RectW,RectH} = Rect) when is_record(This, wx_ref),is_integer(RectX),is_integer(RectY),is_integer(RectW),is_integer(RectH) -> refreshRect(This,Rect, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowrefreshrect">external documentation</a>. -doc """ -Redraws the contents of the given rectangle: only the area inside it will be -repainted. +Redraws the contents of the given rectangle: only the area inside it will be repainted. -This is the same as `refresh/2` but has a nicer syntax as it can be called with -a temporary \{X,Y,W,H\} object as argument like this -`RefreshRect(wxRect(x, y, w, h))`. +This is the same as `refresh/2` but has a nicer syntax as it can be called with a temporary +{X,Y,W,H} object as argument like this `RefreshRect(wxRect(x, y, w, h))`. """. -spec refreshRect(This, Rect, [Option]) -> 'ok' when This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}, @@ -1964,12 +2014,19 @@ refreshRect(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Rect, Opts,?get_env(),?wxWindow_RefreshRect). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowreleasemouse">external documentation</a>. -doc """ Releases mouse input captured with `captureMouse/1`. -See: `captureMouse/1`, `hasCapture/1`, `releaseMouse/1`, -`m:wxMouseCaptureLostEvent`, `m:wxMouseCaptureChangedEvent` +See: +* `captureMouse/1` + +* `hasCapture/1` + +* `releaseMouse/1` + +* `m:wxMouseCaptureLostEvent` + +* `m:wxMouseCaptureChangedEvent` """. -spec releaseMouse(This) -> 'ok' when This::wxWindow(). @@ -1977,13 +2034,12 @@ releaseMouse(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_ReleaseMouse). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowremovechild">external documentation</a>. -doc """ Removes a child window. -This is called automatically by window deletion functions so should not be -required by the application programmer. Notice that this function is mostly -internal to wxWidgets and shouldn't be called by the user code. +This is called automatically by window deletion functions so should not be required by +the application programmer. Notice that this function is mostly internal to wxWidgets and +shouldn't be called by the user code. """. -spec removeChild(This, Child) -> 'ok' when This::wxWindow(), Child::wxWindow(). @@ -1992,15 +2048,13 @@ removeChild(#wx_ref{type=ThisT}=This,#wx_ref{type=ChildT}=Child) -> ?CLASS(ChildT,wxWindow), wxe_util:queue_cmd(This,Child,?get_env(),?wxWindow_RemoveChild). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowreparent">external documentation</a>. -doc """ -Reparents the window, i.e. the window will be removed from its current parent -window (e.g. +Reparents the window, i.e. the window will be removed from its current parent window +(e.g. a non-standard toolbar in a `m:wxFrame`) and then re-inserted into another. -Notice that currently you need to explicitly call `wxBookCtrlBase:removePage/2` -before reparenting a notebook page. +Notice that currently you need to explicitly call `wxBookCtrlBase:removePage/2` before reparenting a notebook page. """. -spec reparent(This, NewParent) -> boolean() when This::wxWindow(), NewParent::wxWindow(). @@ -2010,7 +2064,6 @@ reparent(#wx_ref{type=ThisT}=This,#wx_ref{type=NewParentT}=NewParent) -> wxe_util:queue_cmd(This,NewParent,?get_env(),?wxWindow_Reparent), wxe_util:rec(?wxWindow_Reparent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowscreentoclient">external documentation</a>. -doc "Converts from screen to client window coordinates.". -spec screenToClient(This) -> {X::integer(), Y::integer()} when This::wxWindow(). @@ -2019,7 +2072,6 @@ screenToClient(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_ScreenToClient_2), wxe_util:rec(?wxWindow_ScreenToClient_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowscreentoclient">external documentation</a>. -doc "Converts from screen to client window coordinates.". -spec screenToClient(This, Pt) -> {X::integer(), Y::integer()} when This::wxWindow(), Pt::{X::integer(), Y::integer()}. @@ -2029,17 +2081,14 @@ screenToClient(#wx_ref{type=ThisT}=This,{PtX,PtY} = Pt) wxe_util:queue_cmd(This,Pt,?get_env(),?wxWindow_ScreenToClient_1), wxe_util:rec(?wxWindow_ScreenToClient_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowscrolllines">external documentation</a>. -doc """ -Scrolls the window by the given number of lines down (if `lines` is positive) or -up. +Scrolls the window by the given number of lines down (if `lines` is positive) or up. -Return: Returns true if the window was scrolled, false if it was already on -top/bottom and nothing was done. +Return: Returns true if the window was scrolled, false if it was already on top/bottom +and nothing was done. -Remark: This function is currently only implemented under MSW and `m:wxTextCtrl` -under wxGTK (it also works for `wxScrolled` (not implemented in wx) classes -under all platforms). +Remark: This function is currently only implemented under MSW and `m:wxTextCtrl` under +wxGTK (it also works for `wxScrolled` (not implemented in wx) classes under all platforms). See: `scrollPages/2` """. @@ -2051,13 +2100,11 @@ scrollLines(#wx_ref{type=ThisT}=This,Lines) wxe_util:queue_cmd(This,Lines,?get_env(),?wxWindow_ScrollLines), wxe_util:rec(?wxWindow_ScrollLines). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowscrollpages">external documentation</a>. -doc """ -Scrolls the window by the given number of pages down (if `pages` is positive) or -up. +Scrolls the window by the given number of pages down (if `pages` is positive) or up. -Return: Returns true if the window was scrolled, false if it was already on -top/bottom and nothing was done. +Return: Returns true if the window was scrolled, false if it was already on top/bottom +and nothing was done. Remark: This function is currently only implemented under MSW and wxGTK. @@ -2071,7 +2118,7 @@ scrollPages(#wx_ref{type=ThisT}=This,Pages) wxe_util:queue_cmd(This,Pages,?get_env(),?wxWindow_ScrollPages), wxe_util:rec(?wxWindow_ScrollPages). -%% @equiv scrollWindow(This,Dx,Dy, []) +-doc(#{equiv => scrollWindow(This,Dx,Dy, [])}). -spec scrollWindow(This, Dx, Dy) -> 'ok' when This::wxWindow(), Dx::integer(), Dy::integer(). @@ -2079,12 +2126,11 @@ scrollWindow(This,Dx,Dy) when is_record(This, wx_ref),is_integer(Dx),is_integer(Dy) -> scrollWindow(This,Dx,Dy, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowscrollwindow">external documentation</a>. -doc """ Physically scrolls the pixels in the window and move child windows accordingly. -Remark: Note that you can often use `wxScrolled` (not implemented in wx) instead -of using this function directly. +Remark: Note that you can often use `wxScrolled` (not implemented in wx) instead of using +this function directly. """. -spec scrollWindow(This, Dx, Dy, [Option]) -> 'ok' when This::wxWindow(), Dx::integer(), Dy::integer(), @@ -2097,7 +2143,6 @@ scrollWindow(#wx_ref{type=ThisT}=This,Dx,Dy, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Dx,Dy, Opts,?get_env(),?wxWindow_ScrollWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetacceleratortable">external documentation</a>. -doc """ Sets the accelerator table for this window. @@ -2110,16 +2155,15 @@ setAcceleratorTable(#wx_ref{type=ThisT}=This,#wx_ref{type=AccelT}=Accel) -> ?CLASS(AccelT,wxAcceleratorTable), wxe_util:queue_cmd(This,Accel,?get_env(),?wxWindow_SetAcceleratorTable). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetautolayout">external documentation</a>. -doc """ -Determines whether the `layout/1` function will be called automatically when the -window is resized. +Determines whether the `layout/1` function will be called automatically when the window +is resized. -This method is called implicitly by `setSizer/3` but if you use -`SetConstraints()` (not implemented in wx) you should call it manually or -otherwise the window layout won't be correctly updated when its size changes. +This method is called implicitly by `setSizer/3` but if you use `SetConstraints()` (not implemented +in wx) you should call it manually or otherwise the window layout won't be correctly +updated when its size changes. -See: `setSizer/3`, `SetConstraints()` (not implemented in wx) +See: `setSizer/3` """. -spec setAutoLayout(This, AutoLayout) -> 'ok' when This::wxWindow(), AutoLayout::boolean(). @@ -2128,30 +2172,38 @@ setAutoLayout(#wx_ref{type=ThisT}=This,AutoLayout) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,AutoLayout,?get_env(),?wxWindow_SetAutoLayout). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetbackgroundcolour">external documentation</a>. -doc """ Sets the background colour of the window. -Notice that as with `setForegroundColour/2`, setting the background colour of a -native control may not affect the entire control and could be not supported at -all depending on the control and platform. +Notice that as with `setForegroundColour/2`, setting the background colour of a native control may not affect +the entire control and could be not supported at all depending on the control and platform. -Please see `inheritAttributes/1` for explanation of the difference between this -method and `setOwnBackgroundColour/2`. +Please see `inheritAttributes/1` for explanation of the difference between this method and `setOwnBackgroundColour/2`. -Remark: The background colour is usually painted by the default `m:wxEraseEvent` -event handler function under Windows and automatically under GTK. Note that -setting the background colour does not cause an immediate refresh, so you may -wish to call `clearBackground/1` or `refresh/2` after calling this function. -Using this function will disable attempts to use themes for this window, if the -system supports them. Use with care since usually the themes represent the +Remark: The background colour is usually painted by the default `m:wxEraseEvent` event +handler function under Windows and automatically under GTK. Note that setting the +background colour does not cause an immediate refresh, so you may wish to call `clearBackground/1` or `refresh/2` after +calling this function. Using this function will disable attempts to use themes for this +window, if the system supports them. Use with care since usually the themes represent the appearance chosen by the user to be used for all applications on the system. -Return: true if the colour was really changed, false if it was already set to -this colour and nothing was done. +Return: true if the colour was really changed, false if it was already set to this colour +and nothing was done. + +See: +* `getBackgroundColour/1` + +* `setForegroundColour/2` -See: `getBackgroundColour/1`, `setForegroundColour/2`, `getForegroundColour/1`, -`clearBackground/1`, `refresh/2`, `m:wxEraseEvent`, `m:wxSystemSettings` +* `getForegroundColour/1` + +* `clearBackground/1` + +* `refresh/2` + +* `m:wxEraseEvent` + +* `m:wxSystemSettings` """. -spec setBackgroundColour(This, Colour) -> boolean() when This::wxWindow(), Colour::wx:wx_colour(). @@ -2161,43 +2213,43 @@ setBackgroundColour(#wx_ref{type=ThisT}=This,Colour) wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxWindow_SetBackgroundColour), wxe_util:rec(?wxWindow_SetBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetbackgroundstyle">external documentation</a>. -%%<br /> Style = ?wxBG_STYLE_ERASE | ?wxBG_STYLE_SYSTEM | ?wxBG_STYLE_PAINT | ?wxBG_STYLE_COLOUR | ?wxBG_STYLE_TRANSPARENT -doc """ Sets the background style of the window. -The default background style is `wxBG_STYLE_ERASE` which indicates that the -window background may be erased in `EVT_ERASE_BACKGROUND` handler. This is a -safe, compatibility default; however you may want to change it to -`wxBG_STYLE_SYSTEM` if you don't define any erase background event handlers at -all, to avoid unnecessary generation of erase background events and always let -system erase the background. And you should change the background style to -`wxBG_STYLE_PAINT` if you define an `EVT_PAINT` handler which completely -overwrites the window background as in this case erasing it previously, either -in `EVT_ERASE_BACKGROUND` handler or in the system default handler, would result -in flicker as the background pixels will be repainted twice every time the -window is redrawn. Do ensure that the background is entirely erased by your -`EVT_PAINT` handler in this case however as otherwise garbage may be left on -screen. - -Notice that in previous versions of wxWidgets a common way to work around the -above mentioned flickering problem was to define an empty `EVT_ERASE_BACKGROUND` -handler. Setting background style to `wxBG_STYLE_PAINT` is a simpler and more -efficient solution to the same problem. +The default background style is `wxBG_STYLE_ERASE` which indicates that the window +background may be erased in `EVT_ERASE_BACKGROUND` handler. This is a safe, compatibility +default; however you may want to change it to `wxBG_STYLE_SYSTEM` if you don't define any +erase background event handlers at all, to avoid unnecessary generation of erase +background events and always let system erase the background. And you should change the +background style to `wxBG_STYLE_PAINT` if you define an `EVT_PAINT` handler which +completely overwrites the window background as in this case erasing it previously, either +in `EVT_ERASE_BACKGROUND` handler or in the system default handler, would result in +flicker as the background pixels will be repainted twice every time the window is redrawn. +Do ensure that the background is entirely erased by your `EVT_PAINT` handler in this case +however as otherwise garbage may be left on screen. + +Notice that in previous versions of wxWidgets a common way to work around the above +mentioned flickering problem was to define an empty `EVT_ERASE_BACKGROUND` handler. +Setting background style to `wxBG_STYLE_PAINT` is a simpler and more efficient solution to +the same problem. + +Under wxGTK and wxOSX, you can use ?wxBG\_STYLE\_TRANSPARENT to obtain full transparency +of the window background. Note that wxGTK supports this only since GTK 2.12 with a +compositing manager enabled, call `IsTransparentBackgroundSupported()` (not implemented in +wx) to check whether this is the case. + +Also, in order for `SetBackgroundStyle(wxBG_STYLE_TRANSPARENT)` to work, it must be +called before `create/4`. If you're using your own wxWindow-derived class you should write your code +in the following way: -Under wxGTK and wxOSX, you can use ?wxBG_STYLE_TRANSPARENT to obtain full -transparency of the window background. Note that wxGTK supports this only since -GTK 2.12 with a compositing manager enabled, call -`IsTransparentBackgroundSupported()` (not implemented in wx) to check whether -this is the case. +See: +* `setBackgroundColour/2` -Also, in order for `SetBackgroundStyle(wxBG_STYLE_TRANSPARENT)` to work, it must -be called before `create/4`. If you're using your own wxWindow-derived class you -should write your code in the following way: +* `getForegroundColour/1` -See: `setBackgroundColour/2`, `getForegroundColour/1`, `setTransparent/2`, -`IsTransparentBackgroundSupported()` (not implemented in wx) +* `setTransparent/2` """. +%% Style = ?wxBG_STYLE_ERASE | ?wxBG_STYLE_SYSTEM | ?wxBG_STYLE_PAINT | ?wxBG_STYLE_COLOUR | ?wxBG_STYLE_TRANSPARENT -spec setBackgroundStyle(This, Style) -> boolean() when This::wxWindow(), Style::wx:wx_enum(). setBackgroundStyle(#wx_ref{type=ThisT}=This,Style) @@ -2206,7 +2258,6 @@ setBackgroundStyle(#wx_ref{type=ThisT}=This,Style) wxe_util:queue_cmd(This,Style,?get_env(),?wxWindow_SetBackgroundStyle), wxe_util:rec(?wxWindow_SetBackgroundStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetcaret">external documentation</a>. -doc "Sets the caret() associated with the window.". -spec setCaret(This, Caret) -> 'ok' when This::wxWindow(), Caret::wxCaret:wxCaret(). @@ -2215,14 +2266,9 @@ setCaret(#wx_ref{type=ThisT}=This,#wx_ref{type=CaretT}=Caret) -> ?CLASS(CaretT,wxCaret), wxe_util:queue_cmd(This,Caret,?get_env(),?wxWindow_SetCaret). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetclientsize">external documentation</a>. -%% <br /> Also:<br /> -%% setClientSize(This, Rect) -> 'ok' when<br /> -%% This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}.<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setClientSize(This, Size) -> 'ok' when This::wxWindow(), Size::{W::integer(), H::integer()}; @@ -2237,17 +2283,14 @@ setClientSize(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Rect,?get_env(),?wxWindow_SetClientSize_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetclientsize">external documentation</a>. -doc """ This sets the size of the window client area in pixels. -Using this function to size a window tends to be more device-independent than -`setSize/6`, since the application need not worry about what dimensions the -border or title bar have when trying to fit the window around panel items, for -example. +Using this function to size a window tends to be more device-independent than `setSize/6`, since the +application need not worry about what dimensions the border or title bar have when trying +to fit the window around panel items, for example. -See: -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setClientSize(This, Width, Height) -> 'ok' when This::wxWindow(), Width::integer(), Height::integer(). @@ -2256,15 +2299,14 @@ setClientSize(#wx_ref{type=ThisT}=This,Width,Height) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Width,Height,?get_env(),?wxWindow_SetClientSize_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetcontainingsizer">external documentation</a>. -doc """ -Used by `m:wxSizer` internally to notify the window about being managed by the -given sizer. +Used by `m:wxSizer` internally to notify the window about being managed by the given +sizer. -This method should not be called from outside the library, unless you're -implementing a custom sizer class - and in the latter case you must call this -method with the pointer to the sizer itself whenever a window is added to it and -with NULL argument when the window is removed from it. +This method should not be called from outside the library, unless you're implementing a +custom sizer class - and in the latter case you must call this method with the pointer to +the sizer itself whenever a window is added to it and with NULL argument when the window +is removed from it. """. -spec setContainingSizer(This, Sizer) -> 'ok' when This::wxWindow(), Sizer::wxSizer:wxSizer(). @@ -2273,17 +2315,17 @@ setContainingSizer(#wx_ref{type=ThisT}=This,#wx_ref{type=SizerT}=Sizer) -> ?CLASS(SizerT,wxSizer), wxe_util:queue_cmd(This,Sizer,?get_env(),?wxWindow_SetContainingSizer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetcursor">external documentation</a>. -doc """ Sets the window's cursor. -Notice that the window cursor also sets it for the children of the window -implicitly. +Notice that the window cursor also sets it for the children of the window implicitly. + +The `cursor` may be `wxNullCursor` in which case the window cursor will be reset back to default. -The `cursor` may be `wxNullCursor` in which case the window cursor will be reset -back to default. +See: +* `wx_misc:setCursor/1` -See: `wx_misc:setCursor/1`, `m:wxCursor` +* `m:wxCursor` """. -spec setCursor(This, Cursor) -> boolean() when This::wxWindow(), Cursor::wxCursor:wxCursor(). @@ -2293,13 +2335,11 @@ setCursor(#wx_ref{type=ThisT}=This,#wx_ref{type=CursorT}=Cursor) -> wxe_util:queue_cmd(This,Cursor,?get_env(),?wxWindow_SetCursor), wxe_util:rec(?wxWindow_SetCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetmaxsize">external documentation</a>. -doc """ -Sets the maximum size of the window, to indicate to the sizer layout mechanism -that this is the maximum possible size. +Sets the maximum size of the window, to indicate to the sizer layout mechanism that this +is the maximum possible size. -See: `SetMaxClientSize()` (not implemented in wx), -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setMaxSize(This, Size) -> 'ok' when This::wxWindow(), Size::{W::integer(), H::integer()}. @@ -2308,21 +2348,18 @@ setMaxSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxWindow_SetMaxSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetminsize">external documentation</a>. -doc """ -Sets the minimum size of the window, to indicate to the sizer layout mechanism -that this is the minimum required size. +Sets the minimum size of the window, to indicate to the sizer layout mechanism that this +is the minimum required size. -You may need to call this if you change the window size after construction and -before adding to its parent sizer. +You may need to call this if you change the window size after construction and before +adding to its parent sizer. -Notice that calling this method doesn't prevent the program from making the -window explicitly smaller than the specified size by calling `setSize/6`, it -just ensures that it won't become smaller than this size during the automatic -layout. +Notice that calling this method doesn't prevent the program from making the window +explicitly smaller than the specified size by calling `setSize/6`, it just ensures that it won't +become smaller than this size during the automatic layout. -See: `SetMinClientSize()` (not implemented in wx), -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setMinSize(This, Size) -> 'ok' when This::wxWindow(), Size::{W::integer(), H::integer()}. @@ -2331,12 +2368,14 @@ setMinSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxWindow_SetMinSize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetownbackgroundcolour">external documentation</a>. -doc """ -Sets the background colour of the window but prevents it from being inherited by -the children of this window. +Sets the background colour of the window but prevents it from being inherited by the +children of this window. + +See: +* `setBackgroundColour/2` -See: `setBackgroundColour/2`, `inheritAttributes/1` +* `inheritAttributes/1` """. -spec setOwnBackgroundColour(This, Colour) -> 'ok' when This::wxWindow(), Colour::wx:wx_colour(). @@ -2345,12 +2384,14 @@ setOwnBackgroundColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxWindow_SetOwnBackgroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetownfont">external documentation</a>. -doc """ -Sets the font of the window but prevents it from being inherited by the children -of this window. +Sets the font of the window but prevents it from being inherited by the children of this +window. -See: `setFont/2`, `inheritAttributes/1` +See: +* `setFont/2` + +* `inheritAttributes/1` """. -spec setOwnFont(This, Font) -> 'ok' when This::wxWindow(), Font::wxFont:wxFont(). @@ -2359,12 +2400,14 @@ setOwnFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> ?CLASS(FontT,wxFont), wxe_util:queue_cmd(This,Font,?get_env(),?wxWindow_SetOwnFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetownforegroundcolour">external documentation</a>. -doc """ -Sets the foreground colour of the window but prevents it from being inherited by -the children of this window. +Sets the foreground colour of the window but prevents it from being inherited by the +children of this window. + +See: +* `setForegroundColour/2` -See: `setForegroundColour/2`, `inheritAttributes/1` +* `inheritAttributes/1` """. -spec setOwnForegroundColour(This, Colour) -> 'ok' when This::wxWindow(), Colour::wx:wx_colour(). @@ -2373,14 +2416,15 @@ setOwnForegroundColour(#wx_ref{type=ThisT}=This,Colour) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxWindow_SetOwnForegroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetdroptarget">external documentation</a>. -doc """ Associates a drop target with this window. If the window already has a drop target, it is deleted. -See: `getDropTarget/1`, -[Overview dnd](https://docs.wxwidgets.org/3.1/overview_dnd.html#overview_dnd) +See: +* `getDropTarget/1` + +* [Overview dnd](https://docs.wxwidgets.org/3.2/overview_dnd.html#overview_dnd) """. -spec setDropTarget(This, Target) -> 'ok' when This::wxWindow(), Target::wx:wx_object(). @@ -2389,7 +2433,6 @@ setDropTarget(#wx_ref{type=ThisT}=This,#wx_ref{type=TargetT}=Target) -> ?CLASS(TargetT,wxDropTarget), wxe_util:queue_cmd(This,Target,?get_env(),?wxWindow_SetDropTarget). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetextrastyle">external documentation</a>. -doc """ Sets the extra style bits for the window. @@ -2402,12 +2445,15 @@ setExtraStyle(#wx_ref{type=ThisT}=This,ExStyle) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,ExStyle,?get_env(),?wxWindow_SetExtraStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetfocus">external documentation</a>. -doc """ This sets the window to receive keyboard input. -See: `HasFocus()` (not implemented in wx), `m:wxFocusEvent`, `setFocus/1`, -`wxPanel:setFocusIgnoringChildren/1` +See: +* `m:wxFocusEvent` + +* `setFocus/1` + +* `wxPanel:setFocusIgnoringChildren/1` """. -spec setFocus(This) -> 'ok' when This::wxWindow(). @@ -2415,13 +2461,12 @@ setFocus(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_SetFocus). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetfocusfromkbd">external documentation</a>. -doc """ -This function is called by wxWidgets keyboard navigation code when the user -gives the focus to this window from keyboard (e.g. using `TAB` key). +This function is called by wxWidgets keyboard navigation code when the user gives the +focus to this window from keyboard (e.g. using `TAB` key). -By default this method simply calls `setFocus/1` but can be overridden to do -something in addition to this in the derived classes. +By default this method simply calls `setFocus/1` but can be overridden to do something in addition to +this in the derived classes. """. -spec setFocusFromKbd(This) -> 'ok' when This::wxWindow(). @@ -2429,23 +2474,23 @@ setFocusFromKbd(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_SetFocusFromKbd). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetfont">external documentation</a>. -doc """ Sets the font for this window. -This function should not be called for the parent window if you don't want its -font to be inherited by its children, use `setOwnFont/2` instead in this case -and see `inheritAttributes/1` for more explanations. +This function should not be called for the parent window if you don't want its font to be +inherited by its children, use `setOwnFont/2` instead in this case and see `inheritAttributes/1` for more explanations. -Please notice that the given font is not automatically used for `m:wxPaintDC` -objects associated with this window, you need to call `wxDC:setFont/2` too. -However this font is used by any standard controls for drawing their text as -well as by `getTextExtent/3`. +Please notice that the given font is not automatically used for `m:wxPaintDC` objects +associated with this window, you need to call `wxDC:setFont/2` too. However this font is used by any +standard controls for drawing their text as well as by `getTextExtent/3`. -Return: true if the font was really changed, false if it was already set to this -font and nothing was done. +Return: true if the font was really changed, false if it was already set to this font and +nothing was done. -See: `getFont/1`, `inheritAttributes/1` +See: +* `getFont/1` + +* `inheritAttributes/1` """. -spec setFont(This, Font) -> boolean() when This::wxWindow(), Font::wxFont:wxFont(). @@ -2455,23 +2500,27 @@ setFont(#wx_ref{type=ThisT}=This,#wx_ref{type=FontT}=Font) -> wxe_util:queue_cmd(This,Font,?get_env(),?wxWindow_SetFont), wxe_util:rec(?wxWindow_SetFont). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetforegroundcolour">external documentation</a>. -doc """ Sets the foreground colour of the window. -The meaning of foreground colour varies according to the window class; it may be -the text colour or other colour, or it may not be used at all. Additionally, not -all native controls support changing their foreground colour so this method may -change their colour only partially or even not at all. +The meaning of foreground colour varies according to the window class; it may be the text +colour or other colour, or it may not be used at all. Additionally, not all native +controls support changing their foreground colour so this method may change their colour +only partially or even not at all. + +Please see `inheritAttributes/1` for explanation of the difference between this method and `setOwnForegroundColour/2`. -Please see `inheritAttributes/1` for explanation of the difference between this -method and `setOwnForegroundColour/2`. +Return: true if the colour was really changed, false if it was already set to this colour +and nothing was done. -Return: true if the colour was really changed, false if it was already set to -this colour and nothing was done. +See: +* `getForegroundColour/1` -See: `getForegroundColour/1`, `setBackgroundColour/2`, `getBackgroundColour/1`, -`shouldInheritColours/1` +* `setBackgroundColour/2` + +* `getBackgroundColour/1` + +* `shouldInheritColours/1` """. -spec setForegroundColour(This, Colour) -> boolean() when This::wxWindow(), Colour::wx:wx_colour(). @@ -2481,14 +2530,13 @@ setForegroundColour(#wx_ref{type=ThisT}=This,Colour) wxe_util:queue_cmd(This,wxe_util:color(Colour),?get_env(),?wxWindow_SetForegroundColour), wxe_util:rec(?wxWindow_SetForegroundColour). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsethelptext">external documentation</a>. -doc """ Sets the help text to be used as context-sensitive help for this window. -Note that the text is actually stored by the current `wxHelpProvider` (not -implemented in wx) implementation, and not in the window object itself. +Note that the text is actually stored by the current `wxHelpProvider` (not implemented in +wx) implementation, and not in the window object itself. -See: `getHelpText/1`, `wxHelpProvider::AddHelp()` (not implemented in wx) +See: `getHelpText/1` """. -spec setHelpText(This, HelpText) -> 'ok' when This::wxWindow(), HelpText::unicode:chardata(). @@ -2498,16 +2546,17 @@ setHelpText(#wx_ref{type=ThisT}=This,HelpText) HelpText_UC = unicode:characters_to_binary(HelpText), wxe_util:queue_cmd(This,HelpText_UC,?get_env(),?wxWindow_SetHelpText). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetid">external documentation</a>. -doc """ Sets the identifier of the window. -Remark: Each window has an integer identifier. If the application has not -provided one, an identifier will be generated. Normally, the identifier should -be provided on creation and should not be modified subsequently. +Remark: Each window has an integer identifier. If the application has not provided one, +an identifier will be generated. Normally, the identifier should be provided on creation +and should not be modified subsequently. + +See: +* `getId/1` -See: `getId/1`, -[Overview windowids](https://docs.wxwidgets.org/3.1/overview_windowids.html#overview_windowids) +* [Overview windowids](https://docs.wxwidgets.org/3.2/overview_windowids.html#overview_windowids) """. -spec setId(This, Winid) -> 'ok' when This::wxWindow(), Winid::integer(). @@ -2516,7 +2565,6 @@ setId(#wx_ref{type=ThisT}=This,Winid) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Winid,?get_env(),?wxWindow_SetId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetlabel">external documentation</a>. -doc """ Sets the window's label. @@ -2530,7 +2578,6 @@ setLabel(#wx_ref{type=ThisT}=This,Label) Label_UC = unicode:characters_to_binary(Label), wxe_util:queue_cmd(This,Label_UC,?get_env(),?wxWindow_SetLabel). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetname">external documentation</a>. -doc """ Sets the window's name. @@ -2544,8 +2591,11 @@ setName(#wx_ref{type=ThisT}=This,Name) Name_UC = unicode:characters_to_binary(Name), wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxWindow_SetName). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetpalette">external documentation</a>. --doc "Deprecated: use `wxDC:setPalette/2` instead.". +-doc """ +Deprecated: + +use `wxDC:setPalette/2` instead. +""". -spec setPalette(This, Pal) -> 'ok' when This::wxWindow(), Pal::wxPalette:wxPalette(). setPalette(#wx_ref{type=ThisT}=This,#wx_ref{type=PalT}=Pal) -> @@ -2553,7 +2603,7 @@ setPalette(#wx_ref{type=ThisT}=This,#wx_ref{type=PalT}=Pal) -> ?CLASS(PalT,wxPalette), wxe_util:queue_cmd(This,Pal,?get_env(),?wxWindow_SetPalette). -%% @equiv setScrollbar(This,Orientation,Position,ThumbSize,Range, []) +-doc(#{equiv => setScrollbar(This,Orientation,Position,ThumbSize,Range, [])}). -spec setScrollbar(This, Orientation, Position, ThumbSize, Range) -> 'ok' when This::wxWindow(), Orientation::integer(), Position::integer(), ThumbSize::integer(), Range::integer(). @@ -2561,23 +2611,24 @@ setScrollbar(This,Orientation,Position,ThumbSize,Range) when is_record(This, wx_ref),is_integer(Orientation),is_integer(Position),is_integer(ThumbSize),is_integer(Range) -> setScrollbar(This,Orientation,Position,ThumbSize,Range, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetscrollbar">external documentation</a>. -doc """ Sets the scrollbar properties of a built-in scrollbar. -Remark: Let's say you wish to display 50 lines of text, using the same font. The -window is sized so that you can only see 16 lines at a time. You would use: Note -that with the window at this size, the thumb position can never go above 50 -minus 16, or 34. You can determine how many lines are currently visible by -dividing the current view size by the character height in pixels. When defining -your own scrollbar behaviour, you will always need to recalculate the scrollbar -settings when the window size changes. You could therefore put your scrollbar -calculations and SetScrollbar call into a function named AdjustScrollbars, which -can be called initially and also from your `m:wxSizeEvent` handler function. +Remark: Let's say you wish to display 50 lines of text, using the same font. The window +is sized so that you can only see 16 lines at a time. You would use: Note that with the +window at this size, the thumb position can never go above 50 minus 16, or 34. You can +determine how many lines are currently visible by dividing the current view size by the +character height in pixels. When defining your own scrollbar behaviour, you will always +need to recalculate the scrollbar settings when the window size changes. You could +therefore put your scrollbar calculations and SetScrollbar call into a function named +AdjustScrollbars, which can be called initially and also from your `m:wxSizeEvent` handler function. See: -[Overview scrolling](https://docs.wxwidgets.org/3.1/overview_scrolling.html#overview_scrolling), -`m:wxScrollBar`, `wxScrolled` (not implemented in wx), `m:wxScrollWinEvent` +* [Overview scrolling](https://docs.wxwidgets.org/3.2/overview_scrolling.html#overview_scrolling) + +* `m:wxScrollBar` + +* `m:wxScrollWinEvent` """. -spec setScrollbar(This, Orientation, Position, ThumbSize, Range, [Option]) -> 'ok' when This::wxWindow(), Orientation::integer(), Position::integer(), ThumbSize::integer(), Range::integer(), @@ -2590,7 +2641,7 @@ setScrollbar(#wx_ref{type=ThisT}=This,Orientation,Position,ThumbSize,Range, Opti Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Orientation,Position,ThumbSize,Range, Opts,?get_env(),?wxWindow_SetScrollbar). -%% @equiv setScrollPos(This,Orientation,Pos, []) +-doc(#{equiv => setScrollPos(This,Orientation,Pos, [])}). -spec setScrollPos(This, Orientation, Pos) -> 'ok' when This::wxWindow(), Orientation::integer(), Pos::integer(). @@ -2598,16 +2649,20 @@ setScrollPos(This,Orientation,Pos) when is_record(This, wx_ref),is_integer(Orientation),is_integer(Pos) -> setScrollPos(This,Orientation,Pos, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetscrollpos">external documentation</a>. -doc """ Sets the position of one of the built-in scrollbars. -Remark: This function does not directly affect the contents of the window: it is -up to the application to take note of scrollbar attributes and redraw contents -accordingly. +Remark: This function does not directly affect the contents of the window: it is up to +the application to take note of scrollbar attributes and redraw contents accordingly. + +See: +* `setScrollbar/6` + +* `getScrollPos/2` -See: `setScrollbar/6`, `getScrollPos/2`, `getScrollThumb/2`, `m:wxScrollBar`, -`wxScrolled` (not implemented in wx) +* `getScrollThumb/2` + +* `m:wxScrollBar` """. -spec setScrollPos(This, Orientation, Pos, [Option]) -> 'ok' when This::wxWindow(), Orientation::integer(), Pos::integer(), @@ -2620,14 +2675,9 @@ setScrollPos(#wx_ref{type=ThisT}=This,Orientation,Pos, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Orientation,Pos, Opts,?get_env(),?wxWindow_SetScrollPos). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsize">external documentation</a>. -%% <br /> Also:<br /> -%% setSize(This, Size) -> 'ok' when<br /> -%% This::wxWindow(), Size::{W::integer(), H::integer()}.<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setSize(This, Rect) -> 'ok' when This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()}; @@ -2642,22 +2692,17 @@ setSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxWindow_SetSize_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsize">external documentation</a>. -%% <br /> Also:<br /> -%% setSize(This, Rect, [Option]) -> 'ok' when<br /> -%% This::wxWindow(), Rect::{X::integer(), Y::integer(), W::integer(), H::integer()},<br /> -%% Option :: {'sizeFlags', integer()}.<br /> -%% -doc """ Sets the size of the window in pixels. -The size is specified using a \{X,Y,W,H\}, \{Width,Height\} or by a couple of -`int` objects. +The size is specified using a {X,Y,W,H}, {Width,Height} or by a couple of `int` objects. Remark: This form must be used with non-default width and height values. -See: `move/4`, -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: +* `move/4` + +* [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setSize(This, Width, Height) -> 'ok' when This::wxWindow(), Width::integer(), Height::integer(); @@ -2676,7 +2721,7 @@ setSize(#wx_ref{type=ThisT}=This,{RectX,RectY,RectW,RectH} = Rect, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Rect, Opts,?get_env(),?wxWindow_SetSize_2_1). -%% @equiv setSize(This,X,Y,Width,Height, []) +-doc(#{equiv => setSize(This,X,Y,Width,Height, [])}). -spec setSize(This, X, Y, Width, Height) -> 'ok' when This::wxWindow(), X::integer(), Y::integer(), Width::integer(), Height::integer(). @@ -2684,17 +2729,17 @@ setSize(This,X,Y,Width,Height) when is_record(This, wx_ref),is_integer(X),is_integer(Y),is_integer(Width),is_integer(Height) -> setSize(This,X,Y,Width,Height, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsize">external documentation</a>. -doc """ Sets the size of the window in pixels. -Remark: This overload sets the position and optionally size, of the window. -Parameters may be wxDefaultCoord to indicate either that a default should be -supplied by wxWidgets, or that the current value of the dimension should be -used. +Remark: This overload sets the position and optionally size, of the window. Parameters +may be wxDefaultCoord to indicate either that a default should be supplied by wxWidgets, +or that the current value of the dimension should be used. -See: `move/4`, -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: +* `move/4` + +* [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setSize(This, X, Y, Width, Height, [Option]) -> 'ok' when This::wxWindow(), X::integer(), Y::integer(), Width::integer(), Height::integer(), @@ -2707,7 +2752,7 @@ setSize(#wx_ref{type=ThisT}=This,X,Y,Width,Height, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,X,Y,Width,Height, Opts,?get_env(),?wxWindow_SetSize_5). -%% @equiv setSizeHints(This,MinSize, []) +-doc(#{equiv => setSizeHints(This,MinSize, [])}). -spec setSizeHints(This, MinSize) -> 'ok' when This::wxWindow(), MinSize::{W::integer(), H::integer()}. @@ -2715,21 +2760,16 @@ setSizeHints(This,{MinSizeW,MinSizeH} = MinSize) when is_record(This, wx_ref),is_integer(MinSizeW),is_integer(MinSizeH) -> setSizeHints(This,MinSize, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsizehints">external documentation</a>. -%% <br /> Also:<br /> -%% setSizeHints(This, MinSize, [Option]) -> 'ok' when<br /> -%% This::wxWindow(), MinSize::{W::integer(), H::integer()},<br /> -%% Option :: {'maxSize', {W::integer(), H::integer()}}<br /> -%% | {'incSize', {W::integer(), H::integer()}}.<br /> -%% -doc """ -Use of this function for windows which are not toplevel windows (such as -`m:wxDialog` or `m:wxFrame`) is discouraged. +Use of this function for windows which are not toplevel windows (such as `m:wxDialog` or `m:wxFrame`) +is discouraged. Please use `setMinSize/2` and `setMaxSize/2` instead. -See: `setSizeHints/4`, -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: +* `setSizeHints/4` + +* [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setSizeHints(This, MinW, MinH) -> 'ok' when This::wxWindow(), MinW::integer(), MinH::integer(); @@ -2750,10 +2790,9 @@ setSizeHints(#wx_ref{type=ThisT}=This,{MinSizeW,MinSizeH} = MinSize, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,MinSize, Opts,?get_env(),?wxWindow_SetSizeHints_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsizehints">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setSizeHints(This, MinW, MinH, [Option]) -> 'ok' when This::wxWindow(), MinW::integer(), MinH::integer(), @@ -2772,7 +2811,7 @@ setSizeHints(#wx_ref{type=ThisT}=This,MinW,MinH, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,MinW,MinH, Opts,?get_env(),?wxWindow_SetSizeHints_3). -%% @equiv setSizer(This,Sizer, []) +-doc(#{equiv => setSizer(This,Sizer, [])}). -spec setSizer(This, Sizer) -> 'ok' when This::wxWindow(), Sizer::wxSizer:wxSizer(). @@ -2780,17 +2819,16 @@ setSizer(This,Sizer) when is_record(This, wx_ref),is_record(Sizer, wx_ref) -> setSizer(This,Sizer, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsizer">external documentation</a>. -doc """ Sets the window to have the given layout sizer. -The window will then own the object, and will take care of its deletion. If an -existing layout constraints object is already owned by the window, it will be -deleted if the `deleteOld` parameter is true. +The window will then own the object, and will take care of its deletion. If an existing +layout constraints object is already owned by the window, it will be deleted if the `deleteOld` +parameter is true. -Note that this function will also call `setAutoLayout/2` implicitly with true -parameter if the `sizer` is non-NULL and false otherwise so that the sizer will -be effectively used to layout the window children whenever it is resized. +Note that this function will also call `setAutoLayout/2` implicitly with true parameter if the `sizer` is +non-NULL and false otherwise so that the sizer will be effectively used to layout the +window children whenever it is resized. Remark: SetSizer enables and disables Layout automatically. """. @@ -2806,7 +2844,7 @@ setSizer(#wx_ref{type=ThisT}=This,#wx_ref{type=SizerT}=Sizer, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Sizer, Opts,?get_env(),?wxWindow_SetSizer). -%% @equiv setSizerAndFit(This,Sizer, []) +-doc(#{equiv => setSizerAndFit(This,Sizer, [])}). -spec setSizerAndFit(This, Sizer) -> 'ok' when This::wxWindow(), Sizer::wxSizer:wxSizer(). @@ -2814,16 +2852,13 @@ setSizerAndFit(This,Sizer) when is_record(This, wx_ref),is_record(Sizer, wx_ref) -> setSizerAndFit(This,Sizer, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetsizerandfit">external documentation</a>. -doc """ -Associate the sizer with the window and set the window size and minimal size -accordingly. +Associate the sizer with the window and set the window size and minimal size accordingly. -This method calls `setSizer/3` and then `wxSizer:setSizeHints/2` which sets the -initial window size to the size needed to accommodate all sizer elements and -sets the minimal size to the same size, this preventing the user from resizing -this window to be less than this minimal size (if it's a top-level window which -can be directly resized by the user). +This method calls `setSizer/3` and then `wxSizer:setSizeHints/2` which sets the initial window size to the size needed to +accommodate all sizer elements and sets the minimal size to the same size, this preventing +the user from resizing this window to be less than this minimal size (if it's a top-level +window which can be directly resized by the user). """. -spec setSizerAndFit(This, Sizer, [Option]) -> 'ok' when This::wxWindow(), Sizer::wxSizer:wxSizer(), @@ -2837,18 +2872,16 @@ setSizerAndFit(#wx_ref{type=ThisT}=This,#wx_ref{type=SizerT}=Sizer, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This,Sizer, Opts,?get_env(),?wxWindow_SetSizerAndFit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetthemeenabled">external documentation</a>. -doc """ -This function tells a window if it should use the system's "theme" code to draw -the windows' background instead of its own background drawing code. +This function tells a window if it should use the system's "theme" code to draw the +windows' background instead of its own background drawing code. -This does not always have any effect since the underlying platform obviously -needs to support the notion of themes in user defined windows. One such platform -is GTK+ where windows can have (very colourful) backgrounds defined by a user's -selected theme. +This does not always have any effect since the underlying platform obviously needs to +support the notion of themes in user defined windows. One such platform is GTK+ where +windows can have (very colourful) backgrounds defined by a user's selected theme. -Dialogs, notebook pages and the status bar have this flag set to true by default -so that the default look and feel is simulated best. +Dialogs, notebook pages and the status bar have this flag set to true by default so that +the default look and feel is simulated best. See: `getThemeEnabled/1` """. @@ -2859,14 +2892,9 @@ setThemeEnabled(#wx_ref{type=ThisT}=This,Enable) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Enable,?get_env(),?wxWindow_SetThemeEnabled). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsettooltip">external documentation</a>. -%% <br /> Also:<br /> -%% setToolTip(This, Tip) -> 'ok' when<br /> -%% This::wxWindow(), Tip::wxToolTip:wxToolTip().<br /> -%% -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setToolTip(This, TipString) -> 'ok' when This::wxWindow(), TipString::unicode:chardata(); @@ -2882,10 +2910,9 @@ setToolTip(#wx_ref{type=ThisT}=This,#wx_ref{type=TipT}=Tip) -> ?CLASS(TipT,wxToolTip), wxe_util:queue_cmd(This,Tip,?get_env(),?wxWindow_SetToolTip_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetvirtualsize">external documentation</a>. -doc """ -This is an overloaded member function, provided for convenience. It differs from -the above function only in what argument(s) it accepts. +This is an overloaded member function, provided for convenience. It differs from the +above function only in what argument(s) it accepts. """. -spec setVirtualSize(This, Size) -> 'ok' when This::wxWindow(), Size::{W::integer(), H::integer()}. @@ -2894,12 +2921,10 @@ setVirtualSize(#wx_ref{type=ThisT}=This,{SizeW,SizeH} = Size) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Size,?get_env(),?wxWindow_SetVirtualSize_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetvirtualsize">external documentation</a>. -doc """ Sets the virtual size of the window in pixels. -See: -[Overview windowsizing](https://docs.wxwidgets.org/3.1/overview_windowsizing.html#overview_windowsizing) +See: [Overview windowsizing](https://docs.wxwidgets.org/3.2/overview_windowsizing.html#overview_windowsizing) """. -spec setVirtualSize(This, Width, Height) -> 'ok' when This::wxWindow(), Width::integer(), Height::integer(). @@ -2908,7 +2933,6 @@ setVirtualSize(#wx_ref{type=ThisT}=This,Width,Height) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Width,Height,?get_env(),?wxWindow_SetVirtualSize_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetwindowstyle">external documentation</a>. -doc "See `setWindowStyleFlag/2` for more info.". -spec setWindowStyle(This, Style) -> 'ok' when This::wxWindow(), Style::integer(). @@ -2917,13 +2941,11 @@ setWindowStyle(#wx_ref{type=ThisT}=This,Style) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Style,?get_env(),?wxWindow_SetWindowStyle). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetwindowstyleflag">external documentation</a>. -doc """ Sets the style of the window. -Please note that some styles cannot be changed after the window creation and -that `refresh/2` might need to be called after changing the others for the -change to take place immediately. +Please note that some styles cannot be changed after the window creation and that `refresh/2` might +need to be called after changing the others for the change to take place immediately. See Window styles for more information about flags. @@ -2936,20 +2958,19 @@ setWindowStyleFlag(#wx_ref{type=ThisT}=This,Style) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Style,?get_env(),?wxWindow_SetWindowStyleFlag). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetwindowvariant">external documentation</a>. -%%<br /> Variant = ?wxWINDOW_VARIANT_NORMAL | ?wxWINDOW_VARIANT_SMALL | ?wxWINDOW_VARIANT_MINI | ?wxWINDOW_VARIANT_LARGE | ?wxWINDOW_VARIANT_MAX -doc """ Chooses a different variant of the window display to use. -Window variants currently just differ in size, as can be seen from -?wxWindowVariant documentation. Under all platforms but macOS, this function -does nothing more than change the font used by the window. However under macOS -it is implemented natively and selects the appropriate variant of the native -widget, which has better appearance than just scaled down or up version of the -normal variant, so it should be preferred to directly tweaking the font size. +Window variants currently just differ in size, as can be seen from ?wxWindowVariant +documentation. Under all platforms but macOS, this function does nothing more than change +the font used by the window. However under macOS it is implemented natively and selects +the appropriate variant of the native widget, which has better appearance than just scaled +down or up version of the normal variant, so it should be preferred to directly tweaking +the font size. By default the controls naturally use the normal variant. """. +%% Variant = ?wxWINDOW_VARIANT_NORMAL | ?wxWINDOW_VARIANT_SMALL | ?wxWINDOW_VARIANT_MINI | ?wxWINDOW_VARIANT_LARGE | ?wxWINDOW_VARIANT_MAX -spec setWindowVariant(This, Variant) -> 'ok' when This::wxWindow(), Variant::wx:wx_enum(). setWindowVariant(#wx_ref{type=ThisT}=This,Variant) @@ -2957,15 +2978,13 @@ setWindowVariant(#wx_ref{type=ThisT}=This,Variant) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,Variant,?get_env(),?wxWindow_SetWindowVariant). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowshouldinheritcolours">external documentation</a>. -doc """ -Return true from here to allow the colours of this window to be changed by -`inheritAttributes/1`. +Return true from here to allow the colours of this window to be changed by `inheritAttributes/1`. Returning false forbids inheriting them from the parent window. -The base class version returns false, but this method is overridden in -`m:wxControl` where it returns true. +The base class version returns false, but this method is overridden in `m:wxControl` +where it returns true. """. -spec shouldInheritColours(This) -> boolean() when This::wxWindow(). @@ -2974,7 +2993,7 @@ shouldInheritColours(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_ShouldInheritColours), wxe_util:rec(?wxWindow_ShouldInheritColours). -%% @equiv show(This, []) +-doc(#{equiv => show(This, [])}). -spec show(This) -> boolean() when This::wxWindow(). @@ -2982,23 +3001,27 @@ show(This) when is_record(This, wx_ref) -> show(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowshow">external documentation</a>. -doc """ Shows or hides the window. -You may need to call `raise/1` for a top level window if you want to bring it to -top, although this is not needed if `show/2` is called immediately after the -frame creation. +You may need to call `raise/1` for a top level window if you want to bring it to top, although +this is not needed if `show/2` is called immediately after the frame creation. + +Notice that the default state of newly created top level windows is hidden (to allow you +to create their contents without flicker) unlike for all the other, not derived from `m:wxTopLevelWindow`, +windows that are by default created in the shown state. + +Return: true if the window has been shown or hidden or false if nothing was done because +it already was in the requested state. + +See: +* `isShown/1` -Notice that the default state of newly created top level windows is hidden (to -allow you to create their contents without flicker) unlike for all the other, -not derived from `m:wxTopLevelWindow`, windows that are by default created in -the shown state. +* `hide/1` -Return: true if the window has been shown or hidden or false if nothing was done -because it already was in the requested state. +* `wxRadioBox:show/3` -See: `isShown/1`, `hide/1`, `wxRadioBox:show/3`, `m:wxShowEvent` +* `m:wxShowEvent` """. -spec show(This, [Option]) -> boolean() when This::wxWindow(), @@ -3012,16 +3035,17 @@ show(#wx_ref{type=ThisT}=This, Options) wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_Show), wxe_util:rec(?wxWindow_Show). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowthaw">external documentation</a>. -doc """ Re-enables window updating after a previous call to `freeze/1`. -To really thaw the control, it must be called exactly the same number of times -as `freeze/1`. +To really thaw the control, it must be called exactly the same number of times as `freeze/1`. If the window has any children, they are recursively thawed too. -See: `wxWindowUpdateLocker` (not implemented in wx), `freeze/1`, `isFrozen/1` +See: +* `freeze/1` + +* `isFrozen/1` """. -spec thaw(This) -> 'ok' when This::wxWindow(). @@ -3029,18 +3053,17 @@ thaw(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Thaw). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowtransferdatafromwindow">external documentation</a>. -doc """ -Transfers values from child controls to data areas specified by their -validators. +Transfers values from child controls to data areas specified by their validators. Returns false if a transfer failed. -Notice that this also calls `transferDataFromWindow/1` for all children -recursively. +Notice that this also calls `transferDataFromWindow/1` for all children recursively. + +See: +* `transferDataToWindow/1` -See: `transferDataToWindow/1`, `wxValidator` (not implemented in wx), -`validate/1` +* `validate/1` """. -spec transferDataFromWindow(This) -> boolean() when This::wxWindow(). @@ -3049,18 +3072,17 @@ transferDataFromWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_TransferDataFromWindow), wxe_util:rec(?wxWindow_TransferDataFromWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowtransferdatatowindow">external documentation</a>. -doc """ -Transfers values to child controls from data areas specified by their -validators. +Transfers values to child controls from data areas specified by their validators. -Notice that this also calls `transferDataToWindow/1` for all children -recursively. +Notice that this also calls `transferDataToWindow/1` for all children recursively. Return: Returns false if a transfer failed. -See: `transferDataFromWindow/1`, `wxValidator` (not implemented in wx), -`validate/1` +See: +* `transferDataFromWindow/1` + +* `validate/1` """. -spec transferDataToWindow(This) -> boolean() when This::wxWindow(). @@ -3069,15 +3091,14 @@ transferDataToWindow(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_TransferDataToWindow), wxe_util:rec(?wxWindow_TransferDataToWindow). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowupdate">external documentation</a>. -doc """ -Calling this method immediately repaints the invalidated area of the window and -all of its children recursively (this normally only happens when the flow of -control returns to the event loop). +Calling this method immediately repaints the invalidated area of the window and all of +its children recursively (this normally only happens when the flow of control returns to +the event loop). -Notice that this function doesn't invalidate any area of the window so nothing -happens if nothing has been invalidated (i.e. marked as requiring a redraw). Use -`refresh/2` first if you want to immediately redraw the window unconditionally. +Notice that this function doesn't invalidate any area of the window so nothing happens if +nothing has been invalidated (i.e. marked as requiring a redraw). Use `refresh/2` first if you want +to immediately redraw the window unconditionally. """. -spec update(This) -> 'ok' when This::wxWindow(). @@ -3085,7 +3106,7 @@ update(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,?get_env(),?wxWindow_Update). -%% @equiv updateWindowUI(This, []) +-doc(#{equiv => updateWindowUI(This, [])}). -spec updateWindowUI(This) -> 'ok' when This::wxWindow(). @@ -3093,30 +3114,26 @@ updateWindowUI(This) when is_record(This, wx_ref) -> updateWindowUI(This, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowupdatewindowui">external documentation</a>. -doc """ This function sends one or more `m:wxUpdateUIEvent` to the window. -The particular implementation depends on the window; for example a `m:wxToolBar` -will send an update UI event for each toolbar button, and a `m:wxFrame` will -send an update UI event for each menubar menu item. +The particular implementation depends on the window; for example a `m:wxToolBar` will +send an update UI event for each toolbar button, and a `m:wxFrame` will send an update UI +event for each menubar menu item. -You can call this function from your application to ensure that your UI is -up-to-date at this point (as far as your `m:wxUpdateUIEvent` handlers are -concerned). This may be necessary if you have called `wxUpdateUIEvent:setMode/1` -or `wxUpdateUIEvent:setUpdateInterval/1` to limit the overhead that wxWidgets -incurs by sending update UI events in idle time. `flags` should be a bitlist of -one or more of the ?wxUpdateUI enumeration. +You can call this function from your application to ensure that your UI is up-to-date at +this point (as far as your `m:wxUpdateUIEvent` handlers are concerned). This may be +necessary if you have called `wxUpdateUIEvent:setMode/1` or `wxUpdateUIEvent:setUpdateInterval/1` to limit the overhead that wxWidgets incurs by sending +update UI events in idle time. `flags` should be a bitlist of one or more of the +?wxUpdateUI enumeration. -If you are calling this function from an OnInternalIdle or OnIdle function, make -sure you pass the wxUPDATE_UI_FROMIDLE flag, since this tells the window to only -update the UI elements that need to be updated in idle time. Some windows update -their elements only when necessary, for example when a menu is about to be -shown. The following is an example of how to call UpdateWindowUI from an idle -function. +If you are calling this function from an OnInternalIdle or OnIdle function, make sure you +pass the wxUPDATE_UI_FROMIDLE flag, since this tells the window to only update the UI +elements that need to be updated in idle time. Some windows update their elements only +when necessary, for example when a menu is about to be shown. The following is an example +of how to call UpdateWindowUI from an idle function. -See: `m:wxUpdateUIEvent`, `DoUpdateWindowUI()` (not implemented in wx), -`OnInternalIdle()` (not implemented in wx) +See: `m:wxUpdateUIEvent` """. -spec updateWindowUI(This, [Option]) -> 'ok' when This::wxWindow(), @@ -3129,7 +3146,6 @@ updateWindowUI(#wx_ref{type=ThisT}=This, Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(This, Opts,?get_env(),?wxWindow_UpdateWindowUI). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowvalidate">external documentation</a>. -doc """ Validates the current values of the child controls using their validators. @@ -3137,8 +3153,10 @@ Notice that this also calls `validate/1` for all children recursively. Return: Returns false if any of the validations failed. -See: `transferDataFromWindow/1`, `transferDataToWindow/1`, `wxValidator` (not -implemented in wx) +See: +* `transferDataFromWindow/1` + +* `transferDataToWindow/1` """. -spec validate(This) -> boolean() when This::wxWindow(). @@ -3147,14 +3165,12 @@ validate(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_Validate), wxe_util:rec(?wxWindow_Validate). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowwarppointer">external documentation</a>. -doc """ Moves the pointer to the given position on the window. -Note: Apple Human Interface Guidelines forbid moving the mouse cursor -programmatically so you should avoid using this function in Mac applications -(and probably avoid using it under the other platforms without good reason as -well). +Note: Apple Human Interface Guidelines forbid moving the mouse cursor programmatically so +you should avoid using this function in Mac applications (and probably avoid using it +under the other platforms without good reason as well). """. -spec warpPointer(This, X, Y) -> 'ok' when This::wxWindow(), X::integer(), Y::integer(). @@ -3163,16 +3179,15 @@ warpPointer(#wx_ref{type=ThisT}=This,X,Y) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,X,Y,?get_env(),?wxWindow_WarpPointer). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsettransparent">external documentation</a>. -doc """ Set the transparency of the window. -If the system supports transparent windows, returns true, otherwise returns -false and the window remains fully opaque. See also `canSetTransparent/1`. +If the system supports transparent windows, returns true, otherwise returns false and the +window remains fully opaque. See also `canSetTransparent/1`. -The parameter `alpha` is in the range 0..255 where 0 corresponds to a fully -transparent window and 255 to the fully opaque one. The constants -`wxIMAGE_ALPHA_TRANSPARENT` and `wxIMAGE_ALPHA_OPAQUE` can be used. +The parameter `alpha` is in the range 0..255 where 0 corresponds to a fully transparent +window and 255 to the fully opaque one. The constants `wxIMAGE_ALPHA_TRANSPARENT` and `wxIMAGE_ALPHA_OPAQUE` +can be used. """. -spec setTransparent(This, Alpha) -> boolean() when This::wxWindow(), Alpha::integer(). @@ -3182,13 +3197,12 @@ setTransparent(#wx_ref{type=ThisT}=This,Alpha) wxe_util:queue_cmd(This,Alpha,?get_env(),?wxWindow_SetTransparent), wxe_util:rec(?wxWindow_SetTransparent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowcansettransparent">external documentation</a>. -doc """ -Returns true if the system supports transparent windows and calling -`setTransparent/2` may succeed. +Returns true if the system supports transparent windows and calling `setTransparent/2` +may succeed. -If this function returns false, transparent windows are definitely not supported -by the current system. +If this function returns false, transparent windows are definitely not supported by the +current system. """. -spec canSetTransparent(This) -> boolean() when This::wxWindow(). @@ -3197,11 +3211,10 @@ canSetTransparent(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_CanSetTransparent), wxe_util:rec(?wxWindow_CanSetTransparent). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowisdoublebuffered">external documentation</a>. -doc """ -Returns true if the window contents is double-buffered by the system, i.e. if -any drawing done on the window is really done on a temporary backing surface and -transferred to the screen all at once later. +Returns true if the window contents is double-buffered by the system, i.e. if any drawing +done on the window is really done on a temporary backing surface and transferred to the +screen all at once later. See: `m:wxBufferedDC` """. @@ -3212,7 +3225,6 @@ isDoubleBuffered(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_IsDoubleBuffered), wxe_util:rec(?wxWindow_IsDoubleBuffered). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowsetdoublebuffered">external documentation</a>. -doc "Turn on or off double buffering of the window if the system supports it.". -spec setDoubleBuffered(This, On) -> 'ok' when This::wxWindow(), On::boolean(). @@ -3221,29 +3233,25 @@ setDoubleBuffered(#wx_ref{type=ThisT}=This,On) ?CLASS(ThisT,wxWindow), wxe_util:queue_cmd(This,On,?get_env(),?wxWindow_SetDoubleBuffered). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetcontentscalefactor">external documentation</a>. -doc """ Returns the factor mapping logical pixels of this window to physical pixels. -This function can be used to portably determine the number of physical pixels in -a window of the given size, by multiplying the window size by the value returned -from it. I.e. it returns the factor converting window coordinates to "content -view" coordinates, where the view can be just a simple window displaying a -`m:wxBitmap` or `m:wxGLCanvas` or any other kind of window rendering arbitrary -"content" on screen. - -For the platforms not doing any pixel mapping, i.e. where logical and physical -pixels are one and the same, this function always returns 1.0 and so using it -is, in principle, unnecessary and could be avoided by using preprocessor check -for `wxHAVE_DPI_INDEPENDENT_PIXELS` `not` being defined, however using this -function unconditionally under all platforms is usually simpler and so -preferable. - -Note: Current behaviour of this function is compatible with wxWidgets 3.0, but -different from its behaviour in versions 3.1.0 to 3.1.3, where it returned the -same value as `getDPIScaleFactor/1`. Please use the other function if you need -to use a scaling factor greater than 1.0 even for the platforms without -`wxHAVE_DPI_INDEPENDENT_PIXELS`, such as wxMSW. +This function can be used to portably determine the number of physical pixels in a window +of the given size, by multiplying the window size by the value returned from it. I.e. it +returns the factor converting window coordinates to "content view" coordinates, where the +view can be just a simple window displaying a `m:wxBitmap` or `m:wxGLCanvas` or any other +kind of window rendering arbitrary "content" on screen. + +For the platforms not doing any pixel mapping, i.e. where logical and physical pixels are +one and the same, this function always returns 1.0 and so using it is, in principle, +unnecessary and could be avoided by using preprocessor check for `wxHAVE_DPI_INDEPENDENT_PIXELS` +`not` being defined, however using this function unconditionally under all platforms is +usually simpler and so preferable. + +Note: Current behaviour of this function is compatible with wxWidgets 3.0, but different +from its behaviour in versions 3.1.0 to 3.1.3, where it returned the same value as `getDPIScaleFactor/1`. +Please use the other function if you need to use a scaling factor greater than 1.0 even +for the platforms without `wxHAVE_DPI_INDEPENDENT_PIXELS`, such as wxMSW. Since: 2.9.5 """. @@ -3254,16 +3262,15 @@ getContentScaleFactor(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetContentScaleFactor), wxe_util:rec(?wxWindow_GetContentScaleFactor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowgetdpi">external documentation</a>. -doc """ Return the DPI of the display used by this window. -The returned value can be different for different windows on systems with -support for per-monitor DPI values, such as Microsoft Windows 10. +The returned value can be different for different windows on systems with support for +per-monitor DPI values, such as Microsoft Windows 10. -If the DPI is not available, returns \{Width,Height\} object. +If the DPI is not available, returns `{Width,Height}` object. -See: `wxDisplay:getPPI/1`, `wxDPIChangedEvent` (not implemented in wx) +See: `wxDisplay:getPPI/1` Since: 3.1.3 """. @@ -3274,37 +3281,27 @@ getDPI(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxWindow_GetDPI), wxe_util:rec(?wxWindow_GetDPI). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowfromdip">external documentation</a>. -%% <br /> Also:<br /> -%% fromDIP(Sz, W) -> {W::integer(), H::integer()} when<br /> -%% Sz::{W::integer(), H::integer()}, W::wxWindow();<br /> -%% (This, D) -> integer() when<br /> -%% This::wxWindow(), D::integer();<br /> -%% (This, Sz) -> {W::integer(), H::integer()} when<br /> -%% This::wxWindow(), Sz::{W::integer(), H::integer()}.<br /> -%% --doc """ -Convert DPI-independent pixel values to the value in pixels appropriate for the -current toolkit. - -A DPI-independent pixel is just a pixel at the standard 96 DPI resolution. To -keep the same physical size at higher resolution, the physical pixel value must -be scaled by `getDPIScaleFactor/1` but this scaling may be already done by the -underlying toolkit (GTK+, Cocoa, ...) automatically. This method performs the -conversion only if it is not already done by the lower level toolkit and so by -using it with pixel values you can guarantee that the physical size of the -corresponding elements will remain the same in all resolutions under all -platforms. For example, instead of creating a bitmap of the hard coded size of -32 pixels you should use to avoid using tiny bitmaps on high DPI screens. - -Notice that this function is only needed when using hard coded pixel values. It -is not necessary if the sizes are already based on the DPI-independent units -such as dialog units or if you are relying on the controls automatic best size -determination and using sizers to lay out them. - -Also note that if either component of `sz` has the special value of -1, it is -returned unchanged independently of the current DPI, to preserve the special -value of -1 in wxWidgets API (it is often used to mean "unspecified"). +-doc """ +Convert DPI-independent pixel values to the value in pixels appropriate for the current +toolkit. + +A DPI-independent pixel is just a pixel at the standard 96 DPI resolution. To keep the +same physical size at higher resolution, the physical pixel value must be scaled by `getDPIScaleFactor/1` but +this scaling may be already done by the underlying toolkit (GTK+, Cocoa, ...) +automatically. This method performs the conversion only if it is not already done by the +lower level toolkit and so by using it with pixel values you can guarantee that the +physical size of the corresponding elements will remain the same in all resolutions under +all platforms. For example, instead of creating a bitmap of the hard coded size of 32 +pixels you should use to avoid using tiny bitmaps on high DPI screens. + +Notice that this function is only needed when using hard coded pixel values. It is not +necessary if the sizes are already based on the DPI-independent units such as dialog units +or if you are relying on the controls automatic best size determination and using sizers +to lay out them. + +Also note that if either component of `sz` has the special value of -1, it is returned +unchanged independently of the current DPI, to preserve the special value of -1 in +wxWidgets API (it is often used to mean "unspecified"). Since: 3.1.0 """. @@ -3337,29 +3334,19 @@ fromDIP(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz) wxe_util:queue_cmd(This,Sz,?get_env(),?wxWindow_FromDIP_1_1), wxe_util:rec(?wxWindow_FromDIP_1_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindow.html#wxwindowtodip">external documentation</a>. -%% <br /> Also:<br /> -%% toDIP(Sz, W) -> {W::integer(), H::integer()} when<br /> -%% Sz::{W::integer(), H::integer()}, W::wxWindow();<br /> -%% (This, D) -> integer() when<br /> -%% This::wxWindow(), D::integer();<br /> -%% (This, Sz) -> {W::integer(), H::integer()} when<br /> -%% This::wxWindow(), Sz::{W::integer(), H::integer()}.<br /> -%% -doc """ Convert pixel values of the current toolkit to DPI-independent pixel values. -A DPI-independent pixel is just a pixel at the standard 96 DPI resolution. To -keep the same physical size at higher resolution, the physical pixel value must -be scaled by `getDPIScaleFactor/1` but this scaling may be already done by the -underlying toolkit (GTK+, Cocoa, ...) automatically. This method performs the -conversion only if it is not already done by the lower level toolkit, For -example, you may want to use this to store window sizes and positions so that -they can be re-used regardless of the display DPI: +A DPI-independent pixel is just a pixel at the standard 96 DPI resolution. To keep the +same physical size at higher resolution, the physical pixel value must be scaled by `getDPIScaleFactor/1` but +this scaling may be already done by the underlying toolkit (GTK+, Cocoa, ...) +automatically. This method performs the conversion only if it is not already done by the +lower level toolkit, For example, you may want to use this to store window sizes and +positions so that they can be re-used regardless of the display DPI: -Also note that if either component of `sz` has the special value of -1, it is -returned unchanged independently of the current DPI, to preserve the special -value of -1 in wxWidgets API (it is often used to mean "unspecified"). +Also note that if either component of `sz` has the special value of -1, it is returned +unchanged independently of the current DPI, to preserve the special value of -1 in +wxWidgets API (it is often used to mean "unspecified"). Since: 3.1.0 """. @@ -3392,34 +3379,20 @@ toDIP(#wx_ref{type=ThisT}=This,{SzW,SzH} = Sz) wxe_util:queue_cmd(This,Sz,?get_env(),?wxWindow_ToDIP_1_1), wxe_util:rec(?wxWindow_ToDIP_1_1). -%% @doc Destroys this object, do not use object again --doc """ -Destructor. - -Deletes all sub-windows, then deletes itself. Instead of using the `delete` -operator explicitly, you should normally use `'Destroy'/1` so that wxWidgets can -delete a window only when it is safe to do so, in idle time. - -See: Window Deletion Overview, `'Destroy'/1`, `m:wxCloseEvent` -""". +-doc "Destroys the object". -spec destroy(This::wxWindow()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxWindow), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxEvtHandler -%% @hidden -doc false. disconnect(This,EventType, Options) -> wxEvtHandler:disconnect(This,EventType, Options). -%% @hidden -doc false. disconnect(This,EventType) -> wxEvtHandler:disconnect(This,EventType). -%% @hidden -doc false. disconnect(This) -> wxEvtHandler:disconnect(This). -%% @hidden -doc false. connect(This,EventType, Options) -> wxEvtHandler:connect(This,EventType, Options). -%% @hidden -doc false. connect(This,EventType) -> wxEvtHandler:connect(This,EventType). diff --git a/lib/wx/src/gen/wxWindowCreateEvent.erl b/lib/wx/src/gen/wxWindowCreateEvent.erl index 01a879376794..7bc40c12289f 100644 --- a/lib/wx/src/gen/wxWindowCreateEvent.erl +++ b/lib/wx/src/gen/wxWindowCreateEvent.erl @@ -20,29 +20,27 @@ -module(wxWindowCreateEvent). -moduledoc """ -Functions for wxWindowCreateEvent class +This event is sent just after the actual window associated with a `m:wxWindow` object has +been created. -This event is sent just after the actual window associated with a `m:wxWindow` -object has been created. - -Since it is derived from `m:wxCommandEvent`, the event propagates up the window -hierarchy. +Since it is derived from `m:wxCommandEvent`, the event propagates up the window hierarchy. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxWindowDestroyEvent` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxWindowDestroyEvent` + +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxWindowCreateEvent](https://docs.wxwidgets.org/3.1/classwx_window_create_event.html) +wxWidgets docs: [wxWindowCreateEvent](https://docs.wxwidgets.org/3.2/classwx_window_create_event.html) ## Events -Use `wxEvtHandler:connect/3` with -[`wxWindowCreateEventType`](`t:wxWindowCreateEventType/0`) to subscribe to -events of this type. +Use `wxEvtHandler:connect/3` with `wxWindowCreateEventType` to subscribe to events of this type. """. -include("wxe.hrl"). -export([]). @@ -57,65 +55,46 @@ events of this type. -include("wx.hrl"). -type wxWindowCreateEventType() :: 'create'. -export_type([wxWindowCreateEvent/0, wxWindowCreate/0, wxWindowCreateEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxWindowDC.erl b/lib/wx/src/gen/wxWindowDC.erl index 22d8d46d3e7c..4cd66954a5b7 100644 --- a/lib/wx/src/gen/wxWindowDC.erl +++ b/lib/wx/src/gen/wxWindowDC.erl @@ -20,27 +20,36 @@ -module(wxWindowDC). -moduledoc """ -Functions for wxWindowDC class +A `m:wxWindowDC` must be constructed if an application wishes to paint on the whole area +of a window (client and decorations). -A `m:wxWindowDC` must be constructed if an application wishes to paint on the -whole area of a window (client and decorations). This should normally be -constructed as a temporary stack object; don't store a `m:wxWindowDC` object. +This should normally be constructed as a temporary stack object; don't store a `m:wxWindowDC` +object. -To draw on a window from inside an EVT_PAINT() handler, construct a -`m:wxPaintDC` object instead. +To draw on a window from inside an EVT_PAINT() handler, construct a `m:wxPaintDC` object instead. -To draw on the client area of a window from outside an EVT_PAINT() handler, -construct a `m:wxClientDC` object. +To draw on the client area of a window from outside an EVT_PAINT() handler, construct a `m:wxClientDC` +object. -A `m:wxWindowDC` object is initialized to use the same font and colours as the -window it is associated with. +A `m:wxWindowDC` object is initialized to use the same font and colours as the window it +is associated with. -See: `m:wxDC`, `m:wxMemoryDC`, `m:wxPaintDC`, `m:wxClientDC`, `m:wxScreenDC` +See: +* `m:wxDC` -This class is derived (and can use functions) from: `m:wxDC` +* `m:wxMemoryDC` -wxWidgets docs: -[wxWindowDC](https://docs.wxwidgets.org/3.1/classwx_window_d_c.html) +* `m:wxPaintDC` + +* `m:wxClientDC` + +* `m:wxScreenDC` + +This class is derived, and can use functions, from: + +* `m:wxDC` + +wxWidgets docs: [wxWindowDC](https://docs.wxwidgets.org/3.2/classwx_window_d_c.html) """. -include("wxe.hrl"). -export([destroy/1,new/1]). @@ -69,12 +78,10 @@ wxWidgets docs: -type wxWindowDC() :: wx:wx_object(). -export_type([wxWindowDC/0]). -%% @hidden -doc false. parent_class(wxDC) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxwindowdc.html#wxwindowdcwxwindowdc">external documentation</a>. -doc """ Constructor. @@ -87,287 +94,194 @@ new(#wx_ref{type=WindowT}=Window) -> wxe_util:queue_cmd(Window,?get_env(),?wxWindowDC_new), wxe_util:rec(?wxWindowDC_new). -%% @doc Destroys this object, do not use object again --doc "Destroys the object.". +-doc "Destroys the object". -spec destroy(This::wxWindowDC()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxWindowDC), wxe_util:queue_cmd(Obj, ?get_env(), ?DESTROY_OBJECT), ok. %% From wxDC -%% @hidden -doc false. startPage(This) -> wxDC:startPage(This). -%% @hidden -doc false. startDoc(This,Message) -> wxDC:startDoc(This,Message). -%% @hidden -doc false. setUserScale(This,XScale,YScale) -> wxDC:setUserScale(This,XScale,YScale). -%% @hidden -doc false. setTextForeground(This,Colour) -> wxDC:setTextForeground(This,Colour). -%% @hidden -doc false. setTextBackground(This,Colour) -> wxDC:setTextBackground(This,Colour). -%% @hidden -doc false. setPen(This,Pen) -> wxDC:setPen(This,Pen). -%% @hidden -doc false. setPalette(This,Palette) -> wxDC:setPalette(This,Palette). -%% @hidden -doc false. setMapMode(This,Mode) -> wxDC:setMapMode(This,Mode). -%% @hidden -doc false. setLogicalFunction(This,Function) -> wxDC:setLogicalFunction(This,Function). -%% @hidden -doc false. setLayoutDirection(This,Dir) -> wxDC:setLayoutDirection(This,Dir). -%% @hidden -doc false. setFont(This,Font) -> wxDC:setFont(This,Font). -%% @hidden -doc false. setDeviceOrigin(This,X,Y) -> wxDC:setDeviceOrigin(This,X,Y). -%% @hidden -doc false. setClippingRegion(This,Pt,Sz) -> wxDC:setClippingRegion(This,Pt,Sz). -%% @hidden -doc false. setClippingRegion(This,Rect) -> wxDC:setClippingRegion(This,Rect). -%% @hidden -doc false. setBrush(This,Brush) -> wxDC:setBrush(This,Brush). -%% @hidden -doc false. setBackgroundMode(This,Mode) -> wxDC:setBackgroundMode(This,Mode). -%% @hidden -doc false. setBackground(This,Brush) -> wxDC:setBackground(This,Brush). -%% @hidden -doc false. setAxisOrientation(This,XLeftRight,YBottomUp) -> wxDC:setAxisOrientation(This,XLeftRight,YBottomUp). -%% @hidden -doc false. resetBoundingBox(This) -> wxDC:resetBoundingBox(This). -%% @hidden -doc false. isOk(This) -> wxDC:isOk(This). -%% @hidden -doc false. minY(This) -> wxDC:minY(This). -%% @hidden -doc false. minX(This) -> wxDC:minX(This). -%% @hidden -doc false. maxY(This) -> wxDC:maxY(This). -%% @hidden -doc false. maxX(This) -> wxDC:maxX(This). -%% @hidden -doc false. logicalToDeviceYRel(This,Y) -> wxDC:logicalToDeviceYRel(This,Y). -%% @hidden -doc false. logicalToDeviceY(This,Y) -> wxDC:logicalToDeviceY(This,Y). -%% @hidden -doc false. logicalToDeviceXRel(This,X) -> wxDC:logicalToDeviceXRel(This,X). -%% @hidden -doc false. logicalToDeviceX(This,X) -> wxDC:logicalToDeviceX(This,X). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour, Options) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour, Options). -%% @hidden -doc false. gradientFillLinear(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillLinear(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour,CircleCenter). -%% @hidden -doc false. gradientFillConcentric(This,Rect,InitialColour,DestColour) -> wxDC:gradientFillConcentric(This,Rect,InitialColour,DestColour). -%% @hidden -doc false. getUserScale(This) -> wxDC:getUserScale(This). -%% @hidden -doc false. getTextForeground(This) -> wxDC:getTextForeground(This). -%% @hidden -doc false. getTextExtent(This,String, Options) -> wxDC:getTextExtent(This,String, Options). -%% @hidden -doc false. getTextExtent(This,String) -> wxDC:getTextExtent(This,String). -%% @hidden -doc false. getTextBackground(This) -> wxDC:getTextBackground(This). -%% @hidden -doc false. getSizeMM(This) -> wxDC:getSizeMM(This). -%% @hidden -doc false. getSize(This) -> wxDC:getSize(This). -%% @hidden -doc false. getPPI(This) -> wxDC:getPPI(This). -%% @hidden -doc false. getPixel(This,Pos) -> wxDC:getPixel(This,Pos). -%% @hidden -doc false. getPen(This) -> wxDC:getPen(This). -%% @hidden -doc false. getPartialTextExtents(This,Text) -> wxDC:getPartialTextExtents(This,Text). -%% @hidden -doc false. getMultiLineTextExtent(This,String, Options) -> wxDC:getMultiLineTextExtent(This,String, Options). -%% @hidden -doc false. getMultiLineTextExtent(This,String) -> wxDC:getMultiLineTextExtent(This,String). -%% @hidden -doc false. getMapMode(This) -> wxDC:getMapMode(This). -%% @hidden -doc false. getLogicalFunction(This) -> wxDC:getLogicalFunction(This). -%% @hidden -doc false. getLayoutDirection(This) -> wxDC:getLayoutDirection(This). -%% @hidden -doc false. getFont(This) -> wxDC:getFont(This). -%% @hidden -doc false. getClippingBox(This) -> wxDC:getClippingBox(This). -%% @hidden -doc false. getCharWidth(This) -> wxDC:getCharWidth(This). -%% @hidden -doc false. getCharHeight(This) -> wxDC:getCharHeight(This). -%% @hidden -doc false. getBrush(This) -> wxDC:getBrush(This). -%% @hidden -doc false. getBackgroundMode(This) -> wxDC:getBackgroundMode(This). -%% @hidden -doc false. getBackground(This) -> wxDC:getBackground(This). -%% @hidden -doc false. floodFill(This,Pt,Col, Options) -> wxDC:floodFill(This,Pt,Col, Options). -%% @hidden -doc false. floodFill(This,Pt,Col) -> wxDC:floodFill(This,Pt,Col). -%% @hidden -doc false. endPage(This) -> wxDC:endPage(This). -%% @hidden -doc false. endDoc(This) -> wxDC:endDoc(This). -%% @hidden -doc false. drawText(This,Text,Pt) -> wxDC:drawText(This,Text,Pt). -%% @hidden -doc false. drawRoundedRectangle(This,Pt,Sz,Radius) -> wxDC:drawRoundedRectangle(This,Pt,Sz,Radius). -%% @hidden -doc false. drawRoundedRectangle(This,Rect,Radius) -> wxDC:drawRoundedRectangle(This,Rect,Radius). -%% @hidden -doc false. drawRotatedText(This,Text,Point,Angle) -> wxDC:drawRotatedText(This,Text,Point,Angle). -%% @hidden -doc false. drawRectangle(This,Pt,Sz) -> wxDC:drawRectangle(This,Pt,Sz). -%% @hidden -doc false. drawRectangle(This,Rect) -> wxDC:drawRectangle(This,Rect). -%% @hidden -doc false. drawPoint(This,Pt) -> wxDC:drawPoint(This,Pt). -%% @hidden -doc false. drawPolygon(This,Points, Options) -> wxDC:drawPolygon(This,Points, Options). -%% @hidden -doc false. drawPolygon(This,Points) -> wxDC:drawPolygon(This,Points). -%% @hidden -doc false. drawLines(This,Points, Options) -> wxDC:drawLines(This,Points, Options). -%% @hidden -doc false. drawLines(This,Points) -> wxDC:drawLines(This,Points). -%% @hidden -doc false. drawLine(This,Pt1,Pt2) -> wxDC:drawLine(This,Pt1,Pt2). -%% @hidden -doc false. drawLabel(This,Text,Rect, Options) -> wxDC:drawLabel(This,Text,Rect, Options). -%% @hidden -doc false. drawLabel(This,Text,Rect) -> wxDC:drawLabel(This,Text,Rect). -%% @hidden -doc false. drawIcon(This,Icon,Pt) -> wxDC:drawIcon(This,Icon,Pt). -%% @hidden -doc false. drawEllipticArc(This,Pt,Sz,Sa,Ea) -> wxDC:drawEllipticArc(This,Pt,Sz,Sa,Ea). -%% @hidden -doc false. drawEllipse(This,Pt,Size) -> wxDC:drawEllipse(This,Pt,Size). -%% @hidden -doc false. drawEllipse(This,Rect) -> wxDC:drawEllipse(This,Rect). -%% @hidden -doc false. drawCircle(This,Pt,Radius) -> wxDC:drawCircle(This,Pt,Radius). -%% @hidden -doc false. drawCheckMark(This,Rect) -> wxDC:drawCheckMark(This,Rect). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt, Options) -> wxDC:drawBitmap(This,Bmp,Pt, Options). -%% @hidden -doc false. drawBitmap(This,Bmp,Pt) -> wxDC:drawBitmap(This,Bmp,Pt). -%% @hidden -doc false. drawArc(This,PtStart,PtEnd,Centre) -> wxDC:drawArc(This,PtStart,PtEnd,Centre). -%% @hidden -doc false. deviceToLogicalYRel(This,Y) -> wxDC:deviceToLogicalYRel(This,Y). -%% @hidden -doc false. deviceToLogicalY(This,Y) -> wxDC:deviceToLogicalY(This,Y). -%% @hidden -doc false. deviceToLogicalXRel(This,X) -> wxDC:deviceToLogicalXRel(This,X). -%% @hidden -doc false. deviceToLogicalX(This,X) -> wxDC:deviceToLogicalX(This,X). -%% @hidden -doc false. destroyClippingRegion(This) -> wxDC:destroyClippingRegion(This). -%% @hidden -doc false. crossHair(This,Pt) -> wxDC:crossHair(This,Pt). -%% @hidden -doc false. clear(This) -> wxDC:clear(This). -%% @hidden -doc false. calcBoundingBox(This,X,Y) -> wxDC:calcBoundingBox(This,X,Y). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src, Options) -> wxDC:blit(This,Dest,Size,Source,Src, Options). -%% @hidden -doc false. blit(This,Dest,Size,Source,Src) -> wxDC:blit(This,Dest,Size,Source,Src). diff --git a/lib/wx/src/gen/wxWindowDestroyEvent.erl b/lib/wx/src/gen/wxWindowDestroyEvent.erl index 5d87a35860b2..f7dd7a8136b9 100644 --- a/lib/wx/src/gen/wxWindowDestroyEvent.erl +++ b/lib/wx/src/gen/wxWindowDestroyEvent.erl @@ -20,35 +20,34 @@ -module(wxWindowDestroyEvent). -moduledoc """ -Functions for wxWindowDestroyEvent class - This event is sent as early as possible during the window destruction process. -For the top level windows, as early as possible means that this is done by -`m:wxFrame` or `m:wxDialog` destructor, i.e. after the destructor of the derived -class was executed and so any methods specific to the derived class can't be -called any more from this event handler. If you need to do this, you must call -`wxWindow::SendDestroyEvent()` (not implemented in wx) from your derived class -destructor. +For the top level windows, as early as possible means that this is done by `m:wxFrame` or `m:wxDialog` +destructor, i.e. after the destructor of the derived class was executed and so any +methods specific to the derived class can't be called any more from this event handler. If +you need to do this, you must call `wxWindow::SendDestroyEvent()` (not implemented in wx) +from your derived class destructor. -For the child windows, this event is generated just before deleting the window -from `wxWindow:'Destroy'/1` (which is also called when the parent window is -deleted) or from the window destructor if operator `delete` was used directly -(which is not recommended for this very reason). +For the child windows, this event is generated just before deleting the window from `wxWindow:'Destroy'/1` +(which is also called when the parent window is deleted) or from the window destructor if +operator `delete` was used directly (which is not recommended for this very reason). -It is usually pointless to handle this event in the window itself but it ca be -very useful to receive notifications about the window destruction in the parent -window or in any other object interested in this window. +It is usually pointless to handle this event in the window itself but it ca be very +useful to receive notifications about the window destruction in the parent window or in +any other object interested in this window. See: -[Overview events](https://docs.wxwidgets.org/3.1/overview_events.html#overview_events), -`m:wxWindowCreateEvent` +* [Overview events](https://docs.wxwidgets.org/3.2/overview_events.html#overview_events) + +* `m:wxWindowCreateEvent` + +This class is derived, and can use functions, from: + +* `m:wxCommandEvent` -This class is derived (and can use functions) from: `m:wxCommandEvent` -`m:wxEvent` +* `m:wxEvent` -wxWidgets docs: -[wxWindowDestroyEvent](https://docs.wxwidgets.org/3.1/classwx_window_destroy_event.html) +wxWidgets docs: [wxWindowDestroyEvent](https://docs.wxwidgets.org/3.2/classwx_window_destroy_event.html) """. -include("wxe.hrl"). -export([]). @@ -63,65 +62,46 @@ wxWidgets docs: -include("wx.hrl"). -type wxWindowDestroyEventType() :: 'destroy'. -export_type([wxWindowDestroyEvent/0, wxWindowDestroy/0, wxWindowDestroyEventType/0]). -%% @hidden -doc false. parent_class(wxCommandEvent) -> true; parent_class(wxEvent) -> true; parent_class(_Class) -> erlang:error({badtype, ?MODULE}). %% From wxCommandEvent -%% @hidden -doc false. setString(This,String) -> wxCommandEvent:setString(This,String). -%% @hidden -doc false. setInt(This,IntCommand) -> wxCommandEvent:setInt(This,IntCommand). -%% @hidden -doc false. isSelection(This) -> wxCommandEvent:isSelection(This). -%% @hidden -doc false. isChecked(This) -> wxCommandEvent:isChecked(This). -%% @hidden -doc false. getString(This) -> wxCommandEvent:getString(This). -%% @hidden -doc false. getSelection(This) -> wxCommandEvent:getSelection(This). -%% @hidden -doc false. getInt(This) -> wxCommandEvent:getInt(This). -%% @hidden -doc false. getExtraLong(This) -> wxCommandEvent:getExtraLong(This). -%% @hidden -doc false. getClientData(This) -> wxCommandEvent:getClientData(This). %% From wxEvent -%% @hidden -doc false. stopPropagation(This) -> wxEvent:stopPropagation(This). -%% @hidden -doc false. skip(This, Options) -> wxEvent:skip(This, Options). -%% @hidden -doc false. skip(This) -> wxEvent:skip(This). -%% @hidden -doc false. shouldPropagate(This) -> wxEvent:shouldPropagate(This). -%% @hidden -doc false. resumePropagation(This,PropagationLevel) -> wxEvent:resumePropagation(This,PropagationLevel). -%% @hidden -doc false. isCommandEvent(This) -> wxEvent:isCommandEvent(This). -%% @hidden -doc false. getTimestamp(This) -> wxEvent:getTimestamp(This). -%% @hidden -doc false. getSkipped(This) -> wxEvent:getSkipped(This). -%% @hidden -doc false. getId(This) -> wxEvent:getId(This). diff --git a/lib/wx/src/gen/wxXmlResource.erl b/lib/wx/src/gen/wxXmlResource.erl index b8f1beaaa8a6..f8c66e83f305 100644 --- a/lib/wx/src/gen/wxXmlResource.erl +++ b/lib/wx/src/gen/wxXmlResource.erl @@ -20,22 +20,19 @@ -module(wxXmlResource). -moduledoc """ -Functions for wxXmlResource class - This is the main class for interacting with the XML-based resource system. -The class holds XML resources from one or more .xml files, binary files or zip -archive files. +The class holds XML resources from one or more .xml files, binary files or zip archive files. -Note that this is a singleton class and you'll never allocate/deallocate it. -Just use the static `get/0` getter. +Note that this is a singleton class and you'll never allocate/deallocate it. Just use the +static `get/0` getter. See: -[Overview xrc](https://docs.wxwidgets.org/3.1/overview_xrc.html#overview_xrc), -[Overview xrcformat](https://docs.wxwidgets.org/3.1/overview_xrcformat.html#overview_xrcformat) +* [Overview xrc](https://docs.wxwidgets.org/3.2/overview_xrc.html#overview_xrc) + +* [Overview xrcformat](https://docs.wxwidgets.org/3.2/overview_xrcformat.html#overview_xrcformat) -wxWidgets docs: -[wxXmlResource](https://docs.wxwidgets.org/3.1/classwxXml_resource.html) +wxWidgets docs: [wxXmlResource](https://docs.wxwidgets.org/3.2/classwxXml_resource.html) """. -include("wxe.hrl"). -export([ xrcctrl/3 ,attachUnknownControl/3,attachUnknownControl/4,clearHandlers/1, @@ -50,17 +47,15 @@ wxWidgets docs: -type wxXmlResource() :: wx:wx_object(). -export_type([wxXmlResource/0]). -%% @hidden -doc false. parent_class(_Class) -> erlang:error({badtype, ?MODULE}). -%% @equiv new([]) +-doc(#{equiv => new([])}). -spec new() -> wxXmlResource(). new() -> new([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcewxxmlresource">external documentation</a>. -doc "Constructor.". -spec new([Option]) -> wxXmlResource() when Option :: {'flags', integer()} @@ -74,7 +69,6 @@ new(Options) wxe_util:queue_cmd(Opts,?get_env(),?wxXmlResource_new_1), wxe_util:rec(?wxXmlResource_new_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcewxxmlresource">external documentation</a>. -doc "Constructor.". -spec new(Filemask, [Option]) -> wxXmlResource() when Filemask::unicode:chardata(), @@ -90,7 +84,7 @@ new(Filemask, Options) wxe_util:queue_cmd(Filemask_UC, Opts,?get_env(),?wxXmlResource_new_2), wxe_util:rec(?wxXmlResource_new_2). -%% @equiv attachUnknownControl(This,Name,Control, []) +-doc(#{equiv => attachUnknownControl(This,Name,Control, [])}). -spec attachUnknownControl(This, Name, Control) -> boolean() when This::wxXmlResource(), Name::unicode:chardata(), Control::wxWindow:wxWindow(). @@ -98,7 +92,6 @@ attachUnknownControl(This,Name,Control) when is_record(This, wx_ref),?is_chardata(Name),is_record(Control, wx_ref) -> attachUnknownControl(This,Name,Control, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceattachunknowncontrol">external documentation</a>. -doc """ Attaches an unknown control to the given panel/window/dialog. @@ -118,10 +111,9 @@ attachUnknownControl(#wx_ref{type=ThisT}=This,Name,#wx_ref{type=ControlT}=Contro wxe_util:queue_cmd(This,Name_UC,Control, Opts,?get_env(),?wxXmlResource_AttachUnknownControl), wxe_util:rec(?wxXmlResource_AttachUnknownControl). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceclearhandlers">external documentation</a>. -doc """ -Removes all handlers and deletes them (this means that any handlers added using -`AddHandler()` (not implemented in wx) must be allocated on the heap). +Removes all handlers and deletes them (this means that any handlers added using `AddHandler()` +(not implemented in wx) must be allocated on the heap). """. -spec clearHandlers(This) -> 'ok' when This::wxXmlResource(). @@ -129,12 +121,11 @@ clearHandlers(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxXmlResource), wxe_util:queue_cmd(This,?get_env(),?wxXmlResource_ClearHandlers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcecompareversion">external documentation</a>. -doc """ Compares the XRC version to the argument. -Returns -1 if the XRC version is less than the argument, +1 if greater, and 0 if -they are equal. +Returns -1 if the XRC version is less than the argument, +1 if greater, and 0 if they are +equal. """. -spec compareVersion(This, Major, Minor, Release, Revision) -> integer() when This::wxXmlResource(), Major::integer(), Minor::integer(), Release::integer(), Revision::integer(). @@ -144,14 +135,12 @@ compareVersion(#wx_ref{type=ThisT}=This,Major,Minor,Release,Revision) wxe_util:queue_cmd(This,Major,Minor,Release,Revision,?get_env(),?wxXmlResource_CompareVersion), wxe_util:rec(?wxXmlResource_CompareVersion). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceget">external documentation</a>. -doc "Gets the global resources object or creates one if none exists.". -spec get() -> wxXmlResource(). get() -> wxe_util:queue_cmd(?get_env(), ?wxXmlResource_Get), wxe_util:rec(?wxXmlResource_Get). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcegetflags">external documentation</a>. -doc "Returns flags, which may be a bitlist of ?wxXmlResourceFlags enumeration values.". -spec getFlags(This) -> integer() when This::wxXmlResource(). @@ -160,10 +149,7 @@ getFlags(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxXmlResource_GetFlags), wxe_util:rec(?wxXmlResource_GetFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcegetversion">external documentation</a>. --doc """ -Returns version information (a.b.c.d = d + 256*c + 2562*b + 2563\*a). -""". +-doc "Returns version information (a.b.c.d = d + 256\*c + 2562\*b + 2563\*a).". -spec getVersion(This) -> integer() when This::wxXmlResource(). getVersion(#wx_ref{type=ThisT}=This) -> @@ -171,7 +157,7 @@ getVersion(#wx_ref{type=ThisT}=This) -> wxe_util:queue_cmd(This,?get_env(),?wxXmlResource_GetVersion), wxe_util:rec(?wxXmlResource_GetVersion). -%% @equiv getXRCID(Str_id, []) +-doc(#{equiv => getXRCID(Str_id, [])}). -spec getXRCID(Str_id) -> integer() when Str_id::unicode:chardata(). @@ -179,22 +165,19 @@ getXRCID(Str_id) when ?is_chardata(Str_id) -> getXRCID(Str_id, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcegetxrcid">external documentation</a>. -doc """ -Returns a numeric ID that is equivalent to the string ID used in an XML -resource. +Returns a numeric ID that is equivalent to the string ID used in an XML resource. -If an unknown `str_id` is requested (i.e. other than wxID_XXX or integer), a new -record is created which associates the given string with a number. +If an unknown `str_id` is requested (i.e. other than wxID_XXX or integer), a new record +is created which associates the given string with a number. -If `value_if_not_found` is `wxID_NONE`, the number is obtained via -`wx_misc:newId/0`. Otherwise `value_if_not_found` is used. +If `value_if_not_found` is `wxID_NONE`, the number is obtained via `wx_misc:newId/0`. Otherwise `value_if_not_found` +is used. Macro `XRCID(name)` is provided for convenient use in event tables. -Note: IDs returned by XRCID() cannot be used with the `EVT_*_RANGE` macros, -because the order in which they are assigned to symbolic `name` values is not -guaranteed. +Note: IDs returned by XRCID() cannot be used with the `EVT_*_RANGE` macros, because the +order in which they are assigned to symbolic `name` values is not guaranteed. """. -spec getXRCID(Str_id, [Option]) -> integer() when Str_id::unicode:chardata(), @@ -208,12 +191,11 @@ getXRCID(Str_id, Options) wxe_util:queue_cmd(Str_id_UC, Opts,?get_env(),?wxXmlResource_GetXRCID), wxe_util:rec(?wxXmlResource_GetXRCID). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceinitallhandlers">external documentation</a>. -doc """ Initializes handlers for all supported controls/windows. -This will make the executable quite big because it forces linking against most -of the wxWidgets library. +This will make the executable quite big because it forces linking against most of the +wxWidgets library. """. -spec initAllHandlers(This) -> 'ok' when This::wxXmlResource(). @@ -221,21 +203,16 @@ initAllHandlers(#wx_ref{type=ThisT}=This) -> ?CLASS(ThisT,wxXmlResource), wxe_util:queue_cmd(This,?get_env(),?wxXmlResource_InitAllHandlers). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceload">external documentation</a>. -doc """ Loads resources from XML files that match given filemask. Example: Note: If wxUSE_FILESYS is enabled, this method understands `wxFileSystem` (not -implemented in wx) URLs (see `wxFileSystem::FindFirst()` (not implemented in -wx)). - -Note: If you are sure that the argument is name of single XRC file (rather than -an URL or a wildcard), use `LoadFile()` (not implemented in wx) instead. +implemented in wx) URLs (see `wxFileSystem::FindFirst()` (not implemented in wx)). -See: `LoadFile()` (not implemented in wx), `LoadAllFiles()` (not implemented in -wx) +Note: If you are sure that the argument is name of single XRC file (rather than an URL or +a wildcard), use `LoadFile()` (not implemented in wx) instead. """. -spec load(This, Filemask) -> boolean() when This::wxXmlResource(), Filemask::unicode:chardata(). @@ -246,7 +223,6 @@ load(#wx_ref{type=ThisT}=This,Filemask) wxe_util:queue_cmd(This,Filemask_UC,?get_env(),?wxXmlResource_Load), wxe_util:rec(?wxXmlResource_Load). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadbitmap">external documentation</a>. -doc "Loads a bitmap resource from a file.". -spec loadBitmap(This, Name) -> wxBitmap:wxBitmap() when This::wxXmlResource(), Name::unicode:chardata(). @@ -257,7 +233,6 @@ loadBitmap(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxXmlResource_LoadBitmap), wxe_util:rec(?wxXmlResource_LoadBitmap). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloaddialog">external documentation</a>. -doc """ Loads a dialog. @@ -273,15 +248,13 @@ loadDialog(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Name) wxe_util:queue_cmd(This,Parent,Name_UC,?get_env(),?wxXmlResource_LoadDialog_2), wxe_util:rec(?wxXmlResource_LoadDialog_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloaddialog">external documentation</a>. -doc """ Loads a dialog. `parent` points to parent window (if any). -This form is used to finish creation of an already existing instance (the main -reason for this is that you may want to use derived class with a new event -table). Example: +This form is used to finish creation of an already existing instance (the main reason for +this is that you may want to use derived class with a new event table). Example: """. -spec loadDialog(This, Dlg, Parent, Name) -> boolean() when This::wxXmlResource(), Dlg::wxDialog:wxDialog(), Parent::wxWindow:wxWindow(), Name::unicode:chardata(). @@ -294,7 +267,6 @@ loadDialog(#wx_ref{type=ThisT}=This,#wx_ref{type=DlgT}=Dlg,#wx_ref{type=ParentT} wxe_util:queue_cmd(This,Dlg,Parent,Name_UC,?get_env(),?wxXmlResource_LoadDialog_3), wxe_util:rec(?wxXmlResource_LoadDialog_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadframe">external documentation</a>. -doc """ Loads a frame from the resource. @@ -310,13 +282,11 @@ loadFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Name) wxe_util:queue_cmd(This,Parent,Name_UC,?get_env(),?wxXmlResource_LoadFrame_2), wxe_util:rec(?wxXmlResource_LoadFrame_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadframe">external documentation</a>. -doc """ Loads the contents of a frame onto an existing `m:wxFrame`. -This form is used to finish creation of an already existing instance (the main -reason for this is that you may want to use derived class with a new event -table). +This form is used to finish creation of an already existing instance (the main reason for +this is that you may want to use derived class with a new event table). """. -spec loadFrame(This, Frame, Parent, Name) -> boolean() when This::wxXmlResource(), Frame::wxFrame:wxFrame(), Parent::wxWindow:wxWindow(), Name::unicode:chardata(). @@ -329,7 +299,6 @@ loadFrame(#wx_ref{type=ThisT}=This,#wx_ref{type=FrameT}=Frame,#wx_ref{type=Paren wxe_util:queue_cmd(This,Frame,Parent,Name_UC,?get_env(),?wxXmlResource_LoadFrame_3), wxe_util:rec(?wxXmlResource_LoadFrame_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadicon">external documentation</a>. -doc "Loads an icon resource from a file.". -spec loadIcon(This, Name) -> wxIcon:wxIcon() when This::wxXmlResource(), Name::unicode:chardata(). @@ -340,7 +309,6 @@ loadIcon(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxXmlResource_LoadIcon), wxe_util:rec(?wxXmlResource_LoadIcon). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadmenu">external documentation</a>. -doc """ Loads menu from resource. @@ -355,7 +323,7 @@ loadMenu(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxXmlResource_LoadMenu), wxe_util:rec(?wxXmlResource_LoadMenu). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadmenubar">external documentation</a>. +-doc "". -spec loadMenuBar(This, Name) -> wxMenuBar:wxMenuBar() when This::wxXmlResource(), Name::unicode:chardata(). loadMenuBar(#wx_ref{type=ThisT}=This,Name) @@ -365,7 +333,6 @@ loadMenuBar(#wx_ref{type=ThisT}=This,Name) wxe_util:queue_cmd(This,Name_UC,?get_env(),?wxXmlResource_LoadMenuBar_1), wxe_util:rec(?wxXmlResource_LoadMenuBar_1). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadmenubar">external documentation</a>. -doc """ Loads a menubar from resource. @@ -381,7 +348,6 @@ loadMenuBar(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Name) wxe_util:queue_cmd(This,Parent,Name_UC,?get_env(),?wxXmlResource_LoadMenuBar_2), wxe_util:rec(?wxXmlResource_LoadMenuBar_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadpanel">external documentation</a>. -doc """ Loads a panel. @@ -397,12 +363,11 @@ loadPanel(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Name) wxe_util:queue_cmd(This,Parent,Name_UC,?get_env(),?wxXmlResource_LoadPanel_2), wxe_util:rec(?wxXmlResource_LoadPanel_2). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadpanel">external documentation</a>. -doc """ Loads a panel. -`parent` points to the parent window. This form is used to finish creation of an -already existing instance. +`parent` points to the parent window. This form is used to finish creation of an already +existing instance. """. -spec loadPanel(This, Panel, Parent, Name) -> boolean() when This::wxXmlResource(), Panel::wxPanel:wxPanel(), Parent::wxWindow:wxWindow(), Name::unicode:chardata(). @@ -415,7 +380,6 @@ loadPanel(#wx_ref{type=ThisT}=This,#wx_ref{type=PanelT}=Panel,#wx_ref{type=Paren wxe_util:queue_cmd(This,Panel,Parent,Name_UC,?get_env(),?wxXmlResource_LoadPanel_3), wxe_util:rec(?wxXmlResource_LoadPanel_3). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceloadtoolbar">external documentation</a>. -doc "Loads a toolbar.". -spec loadToolBar(This, Parent, Name) -> wxToolBar:wxToolBar() when This::wxXmlResource(), Parent::wxWindow:wxWindow(), Name::unicode:chardata(). @@ -427,11 +391,7 @@ loadToolBar(#wx_ref{type=ThisT}=This,#wx_ref{type=ParentT}=Parent,Name) wxe_util:queue_cmd(This,Parent,Name_UC,?get_env(),?wxXmlResource_LoadToolBar), wxe_util:rec(?wxXmlResource_LoadToolBar). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceset">external documentation</a>. --doc """ -Sets the global resources object and returns a pointer to the previous one (may -be NULL). -""". +-doc "Sets the global resources object and returns a pointer to the previous one (may be NULL).". -spec set(Res) -> wxXmlResource() when Res::wxXmlResource(). set(#wx_ref{type=ResT}=Res) -> @@ -439,7 +399,6 @@ set(#wx_ref{type=ResT}=Res) -> wxe_util:queue_cmd(Res,?get_env(),?wxXmlResource_Set), wxe_util:rec(?wxXmlResource_Set). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourcesetflags">external documentation</a>. -doc "Sets flags (bitlist of ?wxXmlResourceFlags enumeration values).". -spec setFlags(This, Flags) -> 'ok' when This::wxXmlResource(), Flags::integer(). @@ -448,12 +407,11 @@ setFlags(#wx_ref{type=ThisT}=This,Flags) ?CLASS(ThisT,wxXmlResource), wxe_util:queue_cmd(This,Flags,?get_env(),?wxXmlResource_SetFlags). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_wxxmlresource.html#wxxmlresourceunload">external documentation</a>. -doc """ This function unloads a resource previously loaded by `load/2`. -Returns true if the resource was successfully unloaded and false if it hasn't -been found in the list of loaded resources. +Returns true if the resource was successfully unloaded and false if it hasn't been found +in the list of loaded resources. """. -spec unload(This, Filename) -> boolean() when This::wxXmlResource(), Filename::unicode:chardata(). @@ -465,12 +423,6 @@ unload(#wx_ref{type=ThisT}=This,Filename) wxe_util:rec(?wxXmlResource_Unload). --doc """ -Looks up a control. - -Get a control with `Name` in a window created with XML resources. You can use it -to set/get values from controls. The object is type casted to `Type`. Example: -""". -spec xrcctrl(Window, Name, Type) -> wx:wx_object() when Window::wxWindow:wxWindow(), Name::string(), @@ -482,8 +434,7 @@ xrcctrl(Window = #wx_ref{}, Name, Type) when is_list(Name), is_atom(Type) -> Res = wxWindow:findWindow(Window,ID), wx:typeCast(Res, Type). -%% @doc Destroys this object, do not use object again --doc "Destructor.". +-doc "Destroys the object". -spec destroy(This::wxXmlResource()) -> 'ok'. destroy(Obj=#wx_ref{type=Type}) -> ?CLASS(Type,wxXmlResource), diff --git a/lib/wx/src/gen/wx_misc.erl b/lib/wx/src/gen/wx_misc.erl index a6509e19d3df..a9029c27230d 100644 --- a/lib/wx/src/gen/wx_misc.erl +++ b/lib/wx/src/gen/wx_misc.erl @@ -23,12 +23,12 @@ %% This module contains wxWidgets utility functions. -module(wx_misc). +-include("wxe.hrl"). + -moduledoc """ Miscellaneous functions. -Miscellaneous functions. """. --include("wxe.hrl"). -export([beginBusyCursor/0,beginBusyCursor/1,bell/0,endBusyCursor/0,findMenuItemId/3, findWindowAtPoint/1,getCurrentId/0,getEmailAddress/0,getHomeDir/0, getKeyState/1,getMousePosition/0,getMouseState/0,getOsDescription/0, @@ -42,7 +42,6 @@ Miscellaneous functions. %% @doc See <a href="https://docs.wxwidgets.org/3.1.4/classwx_web_view_i_e.html#a7a45d02cb7dd6dbfcc09566449a1f3bd">external documentation</a>. %%<br /> Level = ?wxWEBVIEWIE_EMU_DEFAULT | ?wxWEBVIEWIE_EMU_IE7 | ?wxWEBVIEWIE_EMU_IE8 | ?wxWEBVIEWIE_EMU_IE8_FORCE | ?wxWEBVIEWIE_EMU_IE9 | ?wxWEBVIEWIE_EMU_IE9_FORCE | ?wxWEBVIEWIE_EMU_IE10 | ?wxWEBVIEWIE_EMU_IE10_FORCE | ?wxWEBVIEWIE_EMU_IE11 | ?wxWEBVIEWIE_EMU_IE11_FORCE --doc false. -spec mSWSetEmulationLevel(Level) -> boolean() when Level :: wx:wx_enum(). mSWSetEmulationLevel(Level) when is_integer(Level) -> @@ -52,7 +51,6 @@ mSWSetEmulationLevel(Level) when is_integer(Level) -> %% @doc See <a href="https://docs.wxwidgets.org/3.1.4/classwx_web_view_i_e.html#a7a45d02cb7dd6dbfcc09566449a1f3bd">external documentation</a>. %%<br /> Level = ?wxWEBVIEWIE_EMU_DEFAULT | ?wxWEBVIEWIE_EMU_IE7 | ?wxWEBVIEWIE_EMU_IE8 | ?wxWEBVIEWIE_EMU_IE8_FORCE | ?wxWEBVIEWIE_EMU_IE9 | ?wxWEBVIEWIE_EMU_IE9_FORCE | ?wxWEBVIEWIE_EMU_IE10 | ?wxWEBVIEWIE_EMU_IE10_FORCE | ?wxWEBVIEWIE_EMU_IE11 | ?wxWEBVIEWIE_EMU_IE11_FORCE --doc false. -spec mSWSetEmulationLevel(Level, Executable) -> boolean() when Level :: wx:wx_enum(), Executable :: string(). @@ -63,21 +61,20 @@ mSWSetEmulationLevel(Level, Executable) -> ok = win32reg:set_value(Reg, Executable, Level), ok = win32reg:close(Reg), true. -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetkeystate">external documentation</a>. -%%<br /> Key = ?WXK_NONE | ?WXK_CONTROL_A | ?WXK_CONTROL_B | ?WXK_CONTROL_C | ?WXK_CONTROL_D | ?WXK_CONTROL_E | ?WXK_CONTROL_F | ?WXK_CONTROL_G | ?WXK_CONTROL_H | ?WXK_CONTROL_I | ?WXK_CONTROL_J | ?WXK_CONTROL_K | ?WXK_CONTROL_L | ?WXK_CONTROL_M | ?WXK_CONTROL_N | ?WXK_CONTROL_O | ?WXK_CONTROL_P | ?WXK_CONTROL_Q | ?WXK_CONTROL_R | ?WXK_CONTROL_S | ?WXK_CONTROL_T | ?WXK_CONTROL_U | ?WXK_CONTROL_V | ?WXK_CONTROL_W | ?WXK_CONTROL_X | ?WXK_CONTROL_Y | ?WXK_CONTROL_Z | ?WXK_BACK | ?WXK_TAB | ?WXK_RETURN | ?WXK_ESCAPE | ?WXK_SPACE | ?WXK_DELETE | ?WXK_START | ?WXK_LBUTTON | ?WXK_RBUTTON | ?WXK_CANCEL | ?WXK_MBUTTON | ?WXK_CLEAR | ?WXK_SHIFT | ?WXK_ALT | ?WXK_CONTROL | ?WXK_MENU | ?WXK_PAUSE | ?WXK_CAPITAL | ?WXK_END | ?WXK_HOME | ?WXK_LEFT | ?WXK_UP | ?WXK_RIGHT | ?WXK_DOWN | ?WXK_SELECT | ?WXK_PRINT | ?WXK_EXECUTE | ?WXK_SNAPSHOT | ?WXK_INSERT | ?WXK_HELP | ?WXK_NUMPAD0 | ?WXK_NUMPAD1 | ?WXK_NUMPAD2 | ?WXK_NUMPAD3 | ?WXK_NUMPAD4 | ?WXK_NUMPAD5 | ?WXK_NUMPAD6 | ?WXK_NUMPAD7 | ?WXK_NUMPAD8 | ?WXK_NUMPAD9 | ?WXK_MULTIPLY | ?WXK_ADD | ?WXK_SEPARATOR | ?WXK_SUBTRACT | ?WXK_DECIMAL | ?WXK_DIVIDE | ?WXK_F1 | ?WXK_F2 | ?WXK_F3 | ?WXK_F4 | ?WXK_F5 | ?WXK_F6 | ?WXK_F7 | ?WXK_F8 | ?WXK_F9 | ?WXK_F10 | ?WXK_F11 | ?WXK_F12 | ?WXK_F13 | ?WXK_F14 | ?WXK_F15 | ?WXK_F16 | ?WXK_F17 | ?WXK_F18 | ?WXK_F19 | ?WXK_F20 | ?WXK_F21 | ?WXK_F22 | ?WXK_F23 | ?WXK_F24 | ?WXK_NUMLOCK | ?WXK_SCROLL | ?WXK_PAGEUP | ?WXK_PAGEDOWN | ?WXK_NUMPAD_SPACE | ?WXK_NUMPAD_TAB | ?WXK_NUMPAD_ENTER | ?WXK_NUMPAD_F1 | ?WXK_NUMPAD_F2 | ?WXK_NUMPAD_F3 | ?WXK_NUMPAD_F4 | ?WXK_NUMPAD_HOME | ?WXK_NUMPAD_LEFT | ?WXK_NUMPAD_UP | ?WXK_NUMPAD_RIGHT | ?WXK_NUMPAD_DOWN | ?WXK_NUMPAD_PAGEUP | ?WXK_NUMPAD_PAGEDOWN | ?WXK_NUMPAD_END | ?WXK_NUMPAD_BEGIN | ?WXK_NUMPAD_INSERT | ?WXK_NUMPAD_DELETE | ?WXK_NUMPAD_EQUAL | ?WXK_NUMPAD_MULTIPLY | ?WXK_NUMPAD_ADD | ?WXK_NUMPAD_SEPARATOR | ?WXK_NUMPAD_SUBTRACT | ?WXK_NUMPAD_DECIMAL | ?WXK_NUMPAD_DIVIDE | ?WXK_WINDOWS_LEFT | ?WXK_WINDOWS_RIGHT | ?WXK_WINDOWS_MENU | ?WXK_RAW_CONTROL | ?WXK_COMMAND | ?WXK_SPECIAL1 | ?WXK_SPECIAL2 | ?WXK_SPECIAL3 | ?WXK_SPECIAL4 | ?WXK_SPECIAL5 | ?WXK_SPECIAL6 | ?WXK_SPECIAL7 | ?WXK_SPECIAL8 | ?WXK_SPECIAL9 | ?WXK_SPECIAL10 | ?WXK_SPECIAL11 | ?WXK_SPECIAL12 | ?WXK_SPECIAL13 | ?WXK_SPECIAL14 | ?WXK_SPECIAL15 | ?WXK_SPECIAL16 | ?WXK_SPECIAL17 | ?WXK_SPECIAL18 | ?WXK_SPECIAL19 | ?WXK_SPECIAL20 | ?WXK_BROWSER_BACK | ?WXK_BROWSER_FORWARD | ?WXK_BROWSER_REFRESH | ?WXK_BROWSER_STOP | ?WXK_BROWSER_SEARCH | ?WXK_BROWSER_FAVORITES | ?WXK_BROWSER_HOME | ?WXK_VOLUME_MUTE | ?WXK_VOLUME_DOWN | ?WXK_VOLUME_UP | ?WXK_MEDIA_NEXT_TRACK | ?WXK_MEDIA_PREV_TRACK | ?WXK_MEDIA_STOP | ?WXK_MEDIA_PLAY_PAUSE | ?WXK_LAUNCH_MAIL | ?WXK_LAUNCH_APP1 | ?WXK_LAUNCH_APP2 -doc """ For normal keys, returns true if the specified key is currently down. -For togglable keys (Caps Lock, Num Lock and Scroll Lock), returns true if the -key is toggled such that its LED indicator is lit. There is currently no way to -test whether togglable keys are up or down. +For togglable keys (Caps Lock, Num Lock and Scroll Lock), returns true if the key is +toggled such that its LED indicator is lit. There is currently no way to test whether +togglable keys are up or down. -Even though there are virtual key codes defined for mouse buttons, they cannot -be used with this function currently. +Even though there are virtual key codes defined for mouse buttons, they cannot be used +with this function currently. -In wxGTK, this function can be only used with modifier keys (`WXK_ALT`, -`WXK_CONTROL` and `WXK_SHIFT`) when not using X11 backend currently. +In wxGTK, this function can be only used with modifier keys (`WXK_ALT`, `WXK_CONTROL` and `WXK_SHIFT`) +when not using X11 backend currently. """. +%% Key = ?WXK_NONE | ?WXK_CONTROL_A | ?WXK_CONTROL_B | ?WXK_CONTROL_C | ?WXK_CONTROL_D | ?WXK_CONTROL_E | ?WXK_CONTROL_F | ?WXK_CONTROL_G | ?WXK_CONTROL_H | ?WXK_CONTROL_I | ?WXK_CONTROL_J | ?WXK_CONTROL_K | ?WXK_CONTROL_L | ?WXK_CONTROL_M | ?WXK_CONTROL_N | ?WXK_CONTROL_O | ?WXK_CONTROL_P | ?WXK_CONTROL_Q | ?WXK_CONTROL_R | ?WXK_CONTROL_S | ?WXK_CONTROL_T | ?WXK_CONTROL_U | ?WXK_CONTROL_V | ?WXK_CONTROL_W | ?WXK_CONTROL_X | ?WXK_CONTROL_Y | ?WXK_CONTROL_Z | ?WXK_BACK | ?WXK_TAB | ?WXK_RETURN | ?WXK_ESCAPE | ?WXK_SPACE | ?WXK_DELETE | ?WXK_START | ?WXK_LBUTTON | ?WXK_RBUTTON | ?WXK_CANCEL | ?WXK_MBUTTON | ?WXK_CLEAR | ?WXK_SHIFT | ?WXK_ALT | ?WXK_CONTROL | ?WXK_MENU | ?WXK_PAUSE | ?WXK_CAPITAL | ?WXK_END | ?WXK_HOME | ?WXK_LEFT | ?WXK_UP | ?WXK_RIGHT | ?WXK_DOWN | ?WXK_SELECT | ?WXK_PRINT | ?WXK_EXECUTE | ?WXK_SNAPSHOT | ?WXK_INSERT | ?WXK_HELP | ?WXK_NUMPAD0 | ?WXK_NUMPAD1 | ?WXK_NUMPAD2 | ?WXK_NUMPAD3 | ?WXK_NUMPAD4 | ?WXK_NUMPAD5 | ?WXK_NUMPAD6 | ?WXK_NUMPAD7 | ?WXK_NUMPAD8 | ?WXK_NUMPAD9 | ?WXK_MULTIPLY | ?WXK_ADD | ?WXK_SEPARATOR | ?WXK_SUBTRACT | ?WXK_DECIMAL | ?WXK_DIVIDE | ?WXK_F1 | ?WXK_F2 | ?WXK_F3 | ?WXK_F4 | ?WXK_F5 | ?WXK_F6 | ?WXK_F7 | ?WXK_F8 | ?WXK_F9 | ?WXK_F10 | ?WXK_F11 | ?WXK_F12 | ?WXK_F13 | ?WXK_F14 | ?WXK_F15 | ?WXK_F16 | ?WXK_F17 | ?WXK_F18 | ?WXK_F19 | ?WXK_F20 | ?WXK_F21 | ?WXK_F22 | ?WXK_F23 | ?WXK_F24 | ?WXK_NUMLOCK | ?WXK_SCROLL | ?WXK_PAGEUP | ?WXK_PAGEDOWN | ?WXK_NUMPAD_SPACE | ?WXK_NUMPAD_TAB | ?WXK_NUMPAD_ENTER | ?WXK_NUMPAD_F1 | ?WXK_NUMPAD_F2 | ?WXK_NUMPAD_F3 | ?WXK_NUMPAD_F4 | ?WXK_NUMPAD_HOME | ?WXK_NUMPAD_LEFT | ?WXK_NUMPAD_UP | ?WXK_NUMPAD_RIGHT | ?WXK_NUMPAD_DOWN | ?WXK_NUMPAD_PAGEUP | ?WXK_NUMPAD_PAGEDOWN | ?WXK_NUMPAD_END | ?WXK_NUMPAD_BEGIN | ?WXK_NUMPAD_INSERT | ?WXK_NUMPAD_DELETE | ?WXK_NUMPAD_EQUAL | ?WXK_NUMPAD_MULTIPLY | ?WXK_NUMPAD_ADD | ?WXK_NUMPAD_SEPARATOR | ?WXK_NUMPAD_SUBTRACT | ?WXK_NUMPAD_DECIMAL | ?WXK_NUMPAD_DIVIDE | ?WXK_WINDOWS_LEFT | ?WXK_WINDOWS_RIGHT | ?WXK_WINDOWS_MENU | ?WXK_RAW_CONTROL | ?WXK_COMMAND | ?WXK_SPECIAL1 | ?WXK_SPECIAL2 | ?WXK_SPECIAL3 | ?WXK_SPECIAL4 | ?WXK_SPECIAL5 | ?WXK_SPECIAL6 | ?WXK_SPECIAL7 | ?WXK_SPECIAL8 | ?WXK_SPECIAL9 | ?WXK_SPECIAL10 | ?WXK_SPECIAL11 | ?WXK_SPECIAL12 | ?WXK_SPECIAL13 | ?WXK_SPECIAL14 | ?WXK_SPECIAL15 | ?WXK_SPECIAL16 | ?WXK_SPECIAL17 | ?WXK_SPECIAL18 | ?WXK_SPECIAL19 | ?WXK_SPECIAL20 | ?WXK_BROWSER_BACK | ?WXK_BROWSER_FORWARD | ?WXK_BROWSER_REFRESH | ?WXK_BROWSER_STOP | ?WXK_BROWSER_SEARCH | ?WXK_BROWSER_FAVORITES | ?WXK_BROWSER_HOME | ?WXK_VOLUME_MUTE | ?WXK_VOLUME_DOWN | ?WXK_VOLUME_UP | ?WXK_MEDIA_NEXT_TRACK | ?WXK_MEDIA_PREV_TRACK | ?WXK_MEDIA_STOP | ?WXK_MEDIA_PLAY_PAUSE | ?WXK_LAUNCH_MAIL | ?WXK_LAUNCH_APP1 | ?WXK_LAUNCH_APP2 -spec getKeyState(Key) -> boolean() when Key::wx:wx_enum(). getKeyState(Key) @@ -85,31 +82,27 @@ getKeyState(Key) wxe_util:queue_cmd(Key,?get_env(),?utils_wxGetKeyState), wxe_util:rec(?utils_wxGetKeyState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetmouseposition">external documentation</a>. -doc "Returns the mouse position in screen coordinates.". -spec getMousePosition() -> {X::integer(), Y::integer()}. getMousePosition() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetMousePosition), wxe_util:rec(?utils_wxGetMousePosition). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetmousestate">external documentation</a>. -doc """ Returns the current state of the mouse. -Returns a [`wx_wxMouseState()`](`t:wx:wx_wxMouseState/0`) instance that contains -the current position of the mouse pointer in screen coordinates, as well as -boolean values indicating the up/down status of the mouse buttons and the -modifier keys. +Returns a `wx_wxMouseState()` instance that contains the current position of the mouse pointer in screen +coordinates, as well as boolean values indicating the up/down status of the mouse buttons +and the modifier keys. """. -spec getMouseState() -> wx:wx_wxMouseState(). getMouseState() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetMouseState), wxe_util:rec(?utils_wxGetMouseState). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxsetdetectableautorepeat">external documentation</a>. -doc """ -Don't synthesize KeyUp events holding down a key and producing KeyDown events -with autorepeat. +Don't synthesize KeyUp events holding down a key and producing KeyDown events with +autorepeat. On by default and always on in wxMSW. """. @@ -120,7 +113,6 @@ setDetectableAutoRepeat(Flag) wxe_util:queue_cmd(Flag,?get_env(),?utils_wxSetDetectableAutoRepeat), wxe_util:rec(?utils_wxSetDetectableAutoRepeat). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxbell">external documentation</a>. -doc """ Ring the system bell. @@ -130,7 +122,6 @@ Note: This function is categorized as a GUI one and so is not thread-safe. bell() -> wxe_util:queue_cmd(?get_env(), ?utils_wxBell). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxfindmenuitemid">external documentation</a>. -doc "Find a menu item identifier associated with the given frame's menu bar.". -spec findMenuItemId(Frame, MenuString, ItemString) -> integer() when Frame::wxFrame:wxFrame(), MenuString::unicode:chardata(), ItemString::unicode:chardata(). @@ -142,13 +133,12 @@ findMenuItemId(#wx_ref{type=FrameT}=Frame,MenuString,ItemString) wxe_util:queue_cmd(Frame,MenuString_UC,ItemString_UC,?get_env(),?utils_wxFindMenuItemId), wxe_util:rec(?utils_wxFindMenuItemId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxfindwindowatpoint">external documentation</a>. -doc """ -Find the deepest window at the given mouse position in screen coordinates, -returning the window if found, or NULL if not. +Find the deepest window at the given mouse position in screen coordinates, returning the +window if found, or NULL if not. -This function takes child windows at the given position into account even if -they are disabled. The hidden children are however skipped by it. +This function takes child windows at the given position into account even if they are +disabled. The hidden children are however skipped by it. """. -spec findWindowAtPoint(Pt) -> wxWindow:wxWindow() when Pt::{X::integer(), Y::integer()}. @@ -157,21 +147,19 @@ findWindowAtPoint({PtX,PtY} = Pt) wxe_util:queue_cmd(Pt,?get_env(),?utils_wxFindWindowAtPoint), wxe_util:rec(?utils_wxFindWindowAtPoint). -%% @equiv beginBusyCursor([]) +-doc(#{equiv => beginBusyCursor([])}). -spec beginBusyCursor() -> 'ok'. beginBusyCursor() -> beginBusyCursor([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxbeginbusycursor">external documentation</a>. -doc """ Changes the cursor to the given cursor for all windows in the application. -Use `endBusyCursor/0` to revert the cursor back to its previous state. These two -calls can be nested, and a counter ensures that only the outer calls take -effect. +Use `wx_misc:endBusyCursor/0` to revert the cursor back to its previous state. These two calls can be nested, and +a counter ensures that only the outer calls take effect. -See: `isBusy/0`, `wxBusyCursor` (not implemented in wx) +See: `wx_misc:isBusy/0` """. -spec beginBusyCursor([Option]) -> 'ok' when Option :: {'cursor', wxCursor:wxCursor()}. @@ -182,44 +170,38 @@ beginBusyCursor(Options) Opts = lists:map(MOpts, Options), wxe_util:queue_cmd(Opts,?get_env(),?utils_wxBeginBusyCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxendbusycursor">external documentation</a>. -doc """ -Changes the cursor back to the original cursor, for all windows in the -application. +Changes the cursor back to the original cursor, for all windows in the application. -Use with `beginBusyCursor/1`. +Use with `wx_misc:beginBusyCursor/1`. -See: `isBusy/0`, `wxBusyCursor` (not implemented in wx) +See: `wx_misc:isBusy/0` """. -spec endBusyCursor() -> 'ok'. endBusyCursor() -> wxe_util:queue_cmd(?get_env(), ?utils_wxEndBusyCursor). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxisbusy">external documentation</a>. -doc """ -Returns true if between two `beginBusyCursor/1` and `endBusyCursor/0` calls. - -See: `wxBusyCursor` (not implemented in wx) +Returns true if between two `wx_misc:beginBusyCursor/1` and `wx_misc:endBusyCursor/0` +calls. """. -spec isBusy() -> boolean(). isBusy() -> wxe_util:queue_cmd(?get_env(), ?utils_wxIsBusy), wxe_util:rec(?utils_wxIsBusy). -%% @equiv shutdown([]) +-doc(#{equiv => shutdown([])}). -spec shutdown() -> boolean(). shutdown() -> shutdown([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxshutdown">external documentation</a>. -doc """ -This function shuts down or reboots the computer depending on the value of the -`flags`. +This function shuts down or reboots the computer depending on the value of the `flags`. Note: Note that performing the shutdown requires the corresponding access rights -(superuser under Unix, SE_SHUTDOWN privilege under Windows) and that this -function is only implemented under Unix and MSW. +(superuser under Unix, SE_SHUTDOWN privilege under Windows) and that this function is only +implemented under Unix and MSW. Return: true on success, false if an error occurred. """. @@ -233,20 +215,18 @@ shutdown(Options) wxe_util:queue_cmd(Opts,?get_env(),?utils_wxShutdown), wxe_util:rec(?utils_wxShutdown). -%% @equiv shell([]) +-doc(#{equiv => shell([])}). -spec shell() -> boolean(). shell() -> shell([]). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxshell">external documentation</a>. -doc """ Executes a command in an interactive shell window. If no command is specified, then just the shell is spawned. -See: `wxExecute()` (not implemented in wx), -[Examples](https://docs.wxwidgets.org/3.1/page_samples.html#page_samples_exec) +See: [Examples](https://docs.wxwidgets.org/3.2/page_samples.html#page_samples_exec) """. -spec shell([Option]) -> boolean() when Option :: {'command', unicode:chardata()}. @@ -258,7 +238,7 @@ shell(Options) wxe_util:queue_cmd(Opts,?get_env(),?utils_wxShell), wxe_util:rec(?utils_wxShell). -%% @equiv launchDefaultBrowser(Url, []) +-doc(#{equiv => launchDefaultBrowser(Url, [])}). -spec launchDefaultBrowser(Url) -> boolean() when Url::unicode:chardata(). @@ -266,27 +246,32 @@ launchDefaultBrowser(Url) when ?is_chardata(Url) -> launchDefaultBrowser(Url, []). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxlaunchdefaultbrowser">external documentation</a>. -doc """ Opens the `url` in user's default browser. -If the `flags` parameter contains `wxBROWSER_NEW_WINDOW` flag, a new window is -opened for the URL (currently this is only supported under Windows). +If the `flags` parameter contains `wxBROWSER_NEW_WINDOW` flag, a new window is opened for +the URL (currently this is only supported under Windows). -And unless the `flags` parameter contains `wxBROWSER_NOBUSYCURSOR` flag, a busy -cursor is shown while the browser is being launched (using `wxBusyCursor` (not -implemented in wx)). +And unless the `flags` parameter contains `wxBROWSER_NOBUSYCURSOR` flag, a busy cursor is +shown while the browser is being launched (using `wxBusyCursor` (not implemented in wx)). The parameter `url` is interpreted as follows: -Returns true if the application was successfully launched. +* if it has a valid scheme (e.g. `"file:"`, `"http:"` or `"mailto:"`) it is passed to the +appropriate browser configured in the user system. + +* if it has no valid scheme (e.g. it's a local file path without the `"file:"` prefix), +then ?wxFileExists and ?wxDirExists are used to test if it's a local file/directory; if it +is, then the browser is called with the `url` parameter eventually prefixed by `"file:"`. -Note: For some configurations of the running user, the application which is -launched to open the given URL may be URL-dependent (e.g. a browser may be used -for local URLs while another one may be used for remote URLs). +* if it has no valid scheme and it's not a local file/directory, then `"http:"` is +prepended and the browser is called. + +Returns true if the application was successfully launched. -See: `wxLaunchDefaultApplication()` (not implemented in wx), `wxExecute()` (not -implemented in wx) +Note: For some configurations of the running user, the application which is launched to +open the given URL may be URL-dependent (e.g. a browser may be used for local URLs while +another one may be used for remote URLs). """. -spec launchDefaultBrowser(Url, [Option]) -> boolean() when Url::unicode:chardata(), @@ -300,11 +285,9 @@ launchDefaultBrowser(Url, Options) wxe_util:queue_cmd(Url_UC, Opts,?get_env(),?utils_wxLaunchDefaultBrowser), wxe_util:rec(?utils_wxLaunchDefaultBrowser). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetemailaddress">external documentation</a>. -doc """ -Copies the user's email address into the supplied buffer, by concatenating the -values returned by `wxGetFullHostName()` (not implemented in wx) and -`getUserId/0`. +Copies the user's email address into the supplied buffer, by concatenating the values +returned by `wxGetFullHostName()` (not implemented in wx) and `wx_misc:getUserId/0`. Return: true if successful, false otherwise. """. @@ -313,42 +296,33 @@ getEmailAddress() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetEmailAddress), wxe_util:rec(?utils_wxGetEmailAddress). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetuserid">external documentation</a>. -doc """ This function returns the "user id" also known as "login name" under Unix (i.e. -something like "jsmith"). It uniquely identifies the current user (on this -system). Under Windows or NT, this function first looks in the environment -variables USER and LOGNAME; if neither of these is found, the entry `UserId` in -the `wxWidgets` section of the WIN.INI file is tried. +something like "jsmith"). It uniquely identifies the current user (on this system). Under +Windows or NT, this function first looks in the environment variables USER and LOGNAME; if +neither of these is found, the entry `UserId` in the `wxWidgets` section of the WIN.INI +file is tried. Return: The login name if successful or an empty string otherwise. - -See: `wxGetUserName()` (not implemented in wx) """. -spec getUserId() -> unicode:charlist(). getUserId() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetUserId), wxe_util:rec(?utils_wxGetUserId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgethomedir">external documentation</a>. --doc """ -Return the (current) user's home directory. - -See: `wxGetUserHome()` (not implemented in wx), `wxStandardPaths` (not -implemented in wx) -""". +-doc "Return the (current) user's home directory.". -spec getHomeDir() -> unicode:charlist(). getHomeDir() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetHomeDir), wxe_util:rec(?utils_wxGetHomeDir). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxnewid">external documentation</a>. -doc """ -Deprecated: Ids generated by it can conflict with the Ids defined by the user -code, use `wxID_ANY` to assign ids which are guaranteed to not conflict with the -user-defined ids for the controls and menu items you create instead of using -this function. +Deprecated: + +Ids generated by it can conflict with the Ids defined by the user code, use `wxID_ANY` to +assign ids which are guaranteed to not conflict with the user-defined ids for the controls +and menu items you create instead of using this function. Generates an integer identifier unique to this run of the program. """. @@ -357,40 +331,31 @@ newId() -> wxe_util:queue_cmd(?get_env(), ?utils_wxNewId), wxe_util:rec(?utils_wxNewId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxregisterid">external documentation</a>. --doc """ -Ensures that Ids subsequently generated by `newId/0` do not clash with the given -`id`. -""". +-doc "Ensures that Ids subsequently generated by `wx_misc:newId/0` do not clash with the given `id`.". -spec registerId(Id) -> 'ok' when Id::integer(). registerId(Id) when is_integer(Id) -> wxe_util:queue_cmd(Id,?get_env(),?utils_wxRegisterId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetcurrentid">external documentation</a>. -doc "Returns the current id.". -spec getCurrentId() -> integer(). getCurrentId() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetCurrentId), wxe_util:rec(?utils_wxGetCurrentId). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxgetosdescription">external documentation</a>. -doc """ -Returns the string containing the description of the current platform in a -user-readable form. +Returns the string containing the description of the current platform in a user-readable +form. -For example, this function may return strings like "Windows 10 (build 10240), -64-bit edition" or "Linux 4.1.4 i386". - -See: `wxGetOsVersion()` (not implemented in wx) +For example, this function may return strings like "Windows 10 (build 10240), 64-bit +edition" or "Linux 4.1.4 i386". """. -spec getOsDescription() -> unicode:charlist(). getOsDescription() -> wxe_util:queue_cmd(?get_env(), ?utils_wxGetOsDescription), wxe_util:rec(?utils_wxGetOsDescription). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxisplatformlittleendian">external documentation</a>. -doc """ Returns true if the current platform is little endian (instead of big endian). @@ -401,48 +366,47 @@ isPlatformLittleEndian() -> wxe_util:queue_cmd(?get_env(), ?utils_wxIsPlatformLittleEndian), wxe_util:rec(?utils_wxIsPlatformLittleEndian). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_miscellany.html#wxisplatform64bit">external documentation</a>. -doc """ Returns true if the operating system the program is running under is 64 bit. The check is performed at run-time and may differ from the value available at -compile-time (at compile-time you can just check if `sizeof(void*) == 8`) since -the program could be running in emulation mode or in a mixed 32/64 bit system -(bi-architecture operating system). +compile-time (at compile-time you can just check if `sizeof(void*) == 8`) since the +program could be running in emulation mode or in a mixed 32/64 bit system (bi-architecture +operating system). -Note: This function is not 100% reliable on some systems given the fact that -there isn't always a standard way to do a reliable check on the OS architecture. +Note: This function is not 100% reliable on some systems given the fact that there isn't +always a standard way to do a reliable check on the OS architecture. """. -spec isPlatform64Bit() -> boolean(). isPlatform64Bit() -> wxe_util:queue_cmd(?get_env(), ?utils_wxIsPlatform64Bit), wxe_util:rec(?utils_wxIsPlatform64Bit). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_gdicmn.html#gdicmnwxdisplaysize">external documentation</a>. -doc """ Returns the display size in pixels. -Note: Use of this function is not recommended in the new code as it only works -for the primary display. Use `wxDisplay:getGeometry/1` to retrieve the size of -the appropriate display instead. +Note: Use of this function is not recommended in the new code as it only works for the +primary display. Use `wxDisplay:getGeometry/1` to retrieve the size of the appropriate display instead. Either of output pointers can be NULL if the caller is not interested in the corresponding value. -See: `wxGetDisplaySize()` (not implemented in wx), `m:wxDisplay` +See: `m:wxDisplay` """. -spec displaySize() -> {Width::integer(), Height::integer()}. displaySize() -> wxe_util:queue_cmd(?get_env(), ?gdicmn_wxDisplaySize), wxe_util:rec(?gdicmn_wxDisplaySize). -%% @doc See <a href="http://www.wxwidgets.org/manuals/2.8.12/wx_gdicmn.html#gdicmnwxsetcursor">external documentation</a>. -doc """ Globally sets the cursor; only has an effect on Windows, Mac and GTK+. You should call this function with wxNullCursor to restore the system cursor. -See: `m:wxCursor`, `wxWindow:setCursor/2` +See: +* `m:wxCursor` + +* `wxWindow:setCursor/2` """. -spec setCursor(Cursor) -> 'ok' when Cursor::wxCursor:wxCursor().