Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
0207-xmerl-Add-missing-types.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0207-xmerl-Add-missing-types.patch of Package erlang
From 779bac4fffa206dad5f1bb0d6c6d969134e1aa77 Mon Sep 17 00:00:00 2001 From: Lukas Larsson <lukas@erlang.org> Date: Mon, 9 Oct 2023 15:57:18 +0200 Subject: [PATCH 07/13] xmerl: Add missing types --- lib/xmerl/src/xmerl_eventp.erl | 30 +++++----- lib/xmerl/src/xmerl_sax_parser.erl | 72 +++++++++++++++++++++++ lib/xmerl/src/xmerl_scan.erl | 67 ++++++++++++--------- lib/xmerl/src/xmerl_xpath.erl | 94 +++++++++++++++++++----------- lib/xmerl/src/xmerl_xsd.erl | 72 ++++++++++++++--------- 5 files changed, 232 insertions(+), 103 deletions(-) diff --git a/lib/xmerl/src/xmerl_eventp.erl b/lib/xmerl/src/xmerl_eventp.erl index 96bcd49766..fcda2c5efc 100644 --- a/lib/xmerl/src/xmerl_eventp.erl +++ b/lib/xmerl/src/xmerl_eventp.erl @@ -24,9 +24,21 @@ %% of XML documents in streams and for parsing in SAX style. %% Each contain more elaborate settings of xmerl_scan that makes usage of %% the customization functions. -%% +-module(xmerl_eventp). +-vsn('0.19'). +-date('03-09-17'). + +-export([stream/2,stream_sax/4, file_sax/4, string_sax/4]). + +% -export([cont/3, rules_read/3,rules_write/4,fetch/2,close/1]). + +-include("xmerl.hrl"). +-include("xmerl_internal.hrl"). +-include_lib("kernel/include/file.hrl"). + %% @type xmlElement() = #xmlElement{}. -%% +-type xmlElement() :: #xmlElement{}. + %% @type option_list(). <p>Options allow to customize the behaviour of the %% scanner. %% See also <a href="xmerl_examples.html">tutorial</a> on customization @@ -108,18 +120,7 @@ %% <dd>Set to 'true' if xmerl should add to elements missing attributes %% with a defined default value (default 'false').</dd> %% </dl> -%% --module(xmerl_eventp). --vsn('0.19'). --date('03-09-17'). - --export([stream/2,stream_sax/4, file_sax/4, string_sax/4]). - -% -export([cont/3, rules_read/3,rules_write/4,fetch/2,close/1]). - --include("xmerl.hrl"). --include("xmerl_internal.hrl"). --include_lib("kernel/include/file.hrl"). +-type option_list() :: [{atom(),term()}]. %% @spec stream(Fname::string(), Options::option_list()) -> xmlElement() %% @@ -129,6 +130,7 @@ %% Note that the <code>continuation_fun</code>, <code>acc_fun</code>, %% <code>fetch_fun</code>, <code>rules</code> and <code>close_fun</code> %% options cannot be user defined using this parser. +-spec stream(Fname::string(), Options::option_list()) -> {xmlElement(), list()} | {error, Reason :: term()}. stream(Fname, Options) -> AccF = fun(X, Acc, S) -> acc(X,Acc,S) end, case file:open(Fname, [read, raw, binary]) of diff --git a/lib/xmerl/src/xmerl_sax_parser.erl b/lib/xmerl/src/xmerl_sax_parser.erl index ce338d7343..c38dbce42c 100644 --- a/lib/xmerl/src/xmerl_sax_parser.erl +++ b/lib/xmerl/src/xmerl_sax_parser.erl @@ -41,6 +41,58 @@ %%---------------------------------------------------------------------- -export([default_continuation_cb/1]). +%%---------------------------------------------------------------------- +%% Types +%%---------------------------------------------------------------------- +-type options() :: [{continuation_fun, continuation_fun()} | + {continuation_state, continuation_state()} | + {event_fun, event_fun()} | + {event_state, event_state()} | + {file_type, normal | dtd} | + {encoding, utf | {utf16, big} | {utf16,little} | latin1 | list } | + skip_external_dtd | disallow_entities | + {entity_recurse_limit, non_neg_integer()} | + {external_entities, all | file | none} | + {fail_undeclared_ref, boolean()}]. +-type continuation_state() :: term(). +-type continuation_fun() :: fun((continuation_state()) -> + {NewBytes :: binary() | list(), + continuation_state()}). +-type event_state() :: term(). +-type event_fun() :: fun((event(), event_location(), event_state()) -> event_state()). +-type event_location() :: {CurrentLocation :: string(), + Entityname :: string(), + LineNo :: integer()}. +-type event() :: startDocument | endDocument | + {startPrefixMapping, Prefix :: string(), Uri :: string()} | + {endPrefixMapping, Prefix :: string()} | + {startElement, Uri :: string(), LocalName :: string(), + QualifiedName :: string(), Attributes :: string()} | + {endElement, Uri :: string(), LocalName :: string(), QualifiedName :: string()} | + {characters, string()} | + {ignorableWhitespace, string()} | + {processingInstruction, Target :: string(), Data :: string()} | + {comment, string()} | + startCDATA | + endCDATA | + {startDTD, Name :: string(), PublicId :: string(), SystemId :: string()} | + endDTD | + {startEntity, SysId :: string()} | + {endEntity, SysId :: string()} | + {elementDecl, Name :: string(), Model :: string()} | + {attributeDecl, ElementName :: string(), AttributeName :: string(), + Type :: string(), Mode :: string(), Value :: string()} | + {internalEntityDecl, Name :: string(), Value :: string()} | + {externalEntityDecl, Name :: string(), PublicId :: string(), SystemId :: string()} | + {unparsedEntityDecl, Name :: string(), PublicId :: string(), SystemId :: string(), Ndata :: string()} | + {notationDecl, Name :: string(), PublicId :: string(), SystemId :: string()}. + +-type unicode_char() :: char(). +-type unicode_binary() :: binary(). +-type latin1_binary() :: unicode:latin1_binary(). + +-export_type([options/0, unicode_char/0, unicode_binary/0, latin1_binary/0]). + %%---------------------------------------------------------------------- %% Macros %%---------------------------------------------------------------------- @@ -63,6 +115,16 @@ %% EventState = term() %% Description: Parse file containing an XML document. %%---------------------------------------------------------------------- +-spec file(Name, Options) -> {ok, EventState, Rest} | ErrorOrUserReturn when + Name :: file:filename(), + Options :: options(), + EventState :: event_state(), + Rest :: unicode_binary() | latin1_binary(), + ErrorOrUserReturn :: {Tag, Location, Reason, EndTags, EventState}, + Tag :: fatal_error | atom(), + Location :: event_location(), + Reason :: term(), + EndTags :: term(). file(Name,Options) -> case file:open(Name, [raw, read_ahead, read,binary]) of {error, Reason} -> @@ -94,6 +156,16 @@ file(Name,Options) -> %% EventState = term() %% Description: Parse a stream containing an XML document. %%---------------------------------------------------------------------- +-spec stream(Xml, Options) -> {ok, EventState, Rest} | ErrorOrUserReturn when + Xml :: unicode_binary() | latin1_binary() | [unicode_char], + Options :: options(), + EventState :: event_state(), + Rest :: unicode_binary() | latin1_binary(), + ErrorOrUserReturn :: {Tag, Location, Reason, EndTags, EventState}, + Tag :: fatal_error | atom(), + Location :: event_location(), + Reason :: term(), + EndTags :: term(). stream(Xml, Options) -> stream(Xml, Options, stream). diff --git a/lib/xmerl/src/xmerl_scan.erl b/lib/xmerl/src/xmerl_scan.erl index 54a2494ef3..47713a7eee 100644 --- a/lib/xmerl/src/xmerl_scan.erl +++ b/lib/xmerl/src/xmerl_scan.erl @@ -27,9 +27,38 @@ %% It returns records of the type defined in xmerl.hrl. %% See also <a href="xmerl_examples.html">tutorial</a> on customization %% functions. + +-module(xmerl_scan). +-vsn('0.20'). +-date('03-09-16'). + +%% main API +-export([string/1, string/2, + file/1, file/2]). + +%% access functions for various states +-export([user_state/1, user_state/2, + event_state/1, event_state/2, + hook_state/1, hook_state/2, + rules_state/1, rules_state/2, + fetch_state/1, fetch_state/2, + cont_state/1, cont_state/2]). + +%% helper functions. To xmerl_lib ?? +-export([accumulate_whitespace/4]). + +-export_type([xmlElement/0]). + +%-define(debug, 1). +-include("xmerl.hrl"). % record def, macros +-include("xmerl_internal.hrl"). +-include_lib("kernel/include/file.hrl"). + %% @type global_state(). <p> %% The global state of the scanner, represented by the #xmerl_scanner{} record. %% </p> +-type global_state() :: #xmerl_scanner{}. + %% @type option_list(). <p>Options allow to customize the behaviour of the %% scanner. %% See also <a href="xmerl_examples.html">tutorial</a> on customization @@ -114,43 +143,22 @@ %% <dd>Set to 'false' if xmerl_scan should fail when there is an ENTITY declaration %% in the XML document (default 'true').</dd> %% </dl> +-type option_list() :: [{atom(),term()}]. + %% @type xmlElement() = #xmlElement{}. %% The record definition is found in xmerl.hrl. +-type xmlElement() :: #xmlElement{}. + %% @type xmlDocument() = #xmlDocument{}. %% The record definition is found in xmerl.hrl. +-type xmlDocument() :: #xmlDocument{}. + %% @type document() = xmlElement() | xmlDocument(). <p> %% The document returned by <code>xmerl_scan:string/[1,2]</code> and %% <code>xmerl_scan:file/[1,2]</code>. The type of the returned record depends on %% the value of the document option passed to the function. %% </p> - --module(xmerl_scan). --vsn('0.20'). --date('03-09-16'). - -%% main API --export([string/1, string/2, - file/1, file/2]). - -%% access functions for various states --export([user_state/1, user_state/2, - event_state/1, event_state/2, - hook_state/1, hook_state/2, - rules_state/1, rules_state/2, - fetch_state/1, fetch_state/2, - cont_state/1, cont_state/2]). - -%% helper functions. To xmerl_lib ?? --export([accumulate_whitespace/4]). - --export_type([xmlElement/0]). - -%-define(debug, 1). --include("xmerl.hrl"). % record def, macros --include("xmerl_internal.hrl"). --include_lib("kernel/include/file.hrl"). - --type xmlElement() :: #xmlElement{}. +-type document() :: xmlElement() | xmlDocument(). -define(fatal(Reason, S), if @@ -198,6 +206,7 @@ cont_state(#xmerl_scanner{fun_states = #xmerl_fun_states{cont = S}}) -> S. %%% @spec user_state(UserState, S::global_state()) -> global_state() %%% @doc For controlling the UserState, to be used in a user function. %%% See <a href="xmerl_examples.html">tutorial</a> on customization functions. +-spec user_state(UserState :: term(), S :: global_state()) -> global_state(). user_state(X, S) -> S#xmerl_scanner{user_state = X}. @@ -252,6 +261,8 @@ file(F) -> %% @spec file(Filename::string(), Options::option_list()) -> {document(),Rest} %% Rest = list() %%% @doc Parse file containing an XML document +-spec file(Filename :: string(), Options :: option_list()) -> + {document(), Rest :: list()} | {error, Reason :: term()}. file(F, Options) -> ExtCharset=case lists:keysearch(encoding,1,Options) of {value,{_,Val}} -> Val; diff --git a/lib/xmerl/src/xmerl_xpath.erl b/lib/xmerl/src/xmerl_xpath.erl index 2354f9d6cd..45e7f7b1f6 100644 --- a/lib/xmerl/src/xmerl_xpath.erl +++ b/lib/xmerl/src/xmerl_xpath.erl @@ -41,7 +41,34 @@ % xmerl_xpath_parse:parse(xmerl_xpath_scan:tokens("descendant-or-self::node()")). % xmerl_xpath_parse:parse(xmerl_xpath_scan:tokens("parent::processing-instruction('foo')")). %% </pre> -%% +-module(xmerl_xpath). + + +%% main API +-export([string/2, + string/3, + string/5]). + +%% exported helper functions, internal for the XPath support +-export([eval_path/3, + axis/3, axis/4]). + +%% debug function +-export([write_node/1]). + + +-include("xmerl.hrl"). +-include("xmerl_internal.hrl"). + + +-record(state, {context = #xmlContext{}, + acc = []}). + + +-define(nodeset(NS), #state{context = #xmlContext{nodeset = NS}}). +-define(context(C), #state{context = C}). + + %% @type nodeEntity() = %% #xmlElement{} %% | #xmlAttribute{} @@ -50,19 +77,38 @@ %% | #xmlComment{} %% | #xmlNsNode{} %% | #xmlDocument{} -%% +-type nodeEntity() :: + #xmlElement{} + | #xmlAttribute{} + | #xmlText{} + | #xmlPI{} + | #xmlComment{} + | #xmlNsNode{} + | #xmlDocument{}. + %% @type docNodes() = #xmlElement{} %% | #xmlAttribute{} %% | #xmlText{} %% | #xmlPI{} %% | #xmlComment{} %% | #xmlNsNode{} -%% +-type docNodes() :: #xmlElement{} + | #xmlAttribute{} + | #xmlText{} + | #xmlPI{} + | #xmlComment{} + | #xmlNsNode{}. + + %% @type docEntity() = #xmlDocument{} | [docNodes()] -%% +-type docEntity() :: #xmlDocument{} | [docNodes()]. + %% @type xPathString() = string() -%% +-type xPathString() :: string(). + %% @type parentList() = [{atom(), integer()}] +-type parentList() :: [{atom(), integer()}]. + %% %% @type option_list(). <p>Options allows to customize the behaviour of the %% XPath scanner. @@ -76,40 +122,12 @@ %% <dt><code>{namespace, Nodes}</code></dt> %% <dd>Set namespace nodes in xmlContext.</dd> %% </dl> +-type option_list() :: [{atom(),term()}]. %% <dt><code>{bindings, Bs}</code></dt> %% <dd></dd> %% <dt><code>{functions, Fs}</code></dt> %% <dd></dd> --module(xmerl_xpath). - - -%% main API --export([string/2, - string/3, - string/5]). - -%% exported helper functions, internal for the XPath support --export([eval_path/3, - axis/3, axis/4]). - -%% debug function --export([write_node/1]). - - --include("xmerl.hrl"). --include("xmerl_internal.hrl"). - - --record(state, {context = #xmlContext{}, - acc = []}). - - --define(nodeset(NS), #state{context = #xmlContext{nodeset = NS}}). --define(context(C), #state{context = C}). - - - %% @spec string(Str, Doc) -> [docEntity()] | Scalar %% @equiv string(Str,Doc, []) @@ -133,6 +151,14 @@ string(Str, Doc, Options) -> %% @doc Extracts the nodes from the parsed XML tree according to XPath. %% xmlObj is a record with fields type and value, %% where type is boolean | number | string +-spec string(Str,Node,Parents,Doc,Options) -> + docEntity() | Scalar when + Str :: xPathString(), + Node :: nodeEntity(), + Parents :: parentList(), + Doc :: nodeEntity(), + Options :: option_list(), + Scalar :: #xmlObj{}. string(Str, Node, Parents, Doc, Options) -> %% record with fields type and value, %% where type is boolean | number | string diff --git a/lib/xmerl/src/xmerl_xsd.erl b/lib/xmerl/src/xmerl_xsd.erl index 10ea8df66e..09dda8bc68 100644 --- a/lib/xmerl/src/xmerl_xsd.erl +++ b/lib/xmerl/src/xmerl_xsd.erl @@ -24,33 +24,6 @@ %% of XML Schema second edition 28 october 2004. For an introduction to %% XML Schema study <a href="http://www.w3.org/TR/xmlschema-0/">part 0.</a> %% An XML structure is validated by xmerl_xsd:validate/[2,3]. -%% @type global_state(). <p>The global state of the validator. It is -%% represented by the <code>#xsd_state{}</code> record. -%% </p> -%% @type option_list(). <p>Options allow to customize the behaviour of the -%% validation. -%% </p> -%% <p> -%% Possible options are : -%% </p> -%% <dl> -%% <dt><code>{tab2file,boolean()}</code></dt> -%% <dd>Enables saving of abstract structure on file for debugging -%% purpose.</dd> -%% <dt><code>{xsdbase,filename()}</code></dt> -%% <dd>XSD Base directory.</dd> -%% <dt><code>{fetch_fun,FetchFun}</code></dt> -%% <dd>Call back function to fetch an external resource.</dd> -%% <dt><code>{fetch_path,PathList}</code></dt> -%% <dd>PathList is a list of directories to search when fetching files. -%% If the file in question is not in the fetch_path, the URI will -%% be used as a file name.</dd> -%% <dt><code>{state,State}</code></dt> -%% <dd>It is possible by this option to provide a state with process -%% information from an earlier validation.</dd> -%% </dl> -%% @type filename() = string() -%% @end %%%------------------------------------------------------------------- -module(xmerl_xsd). @@ -85,6 +58,43 @@ splitwith/2,mapfoldl/3,keysearch/3,keymember/3, keyreplace/4,keydelete/3]). +%%---------------------------------------------------------------------- +%% Types +%%---------------------------------------------------------------------- + +%% @type global_state(). <p>The global state of the validator. It is +%% represented by the <code>#xsd_state{}</code> record. +%% </p> +-type global_state() :: #xsd_state{}. + +%% @type option_list(). <p>Options allow to customize the behaviour of the +%% validation. +%% </p> +%% <p> +%% Possible options are : +%% </p> +%% <dl> +%% <dt><code>{tab2file,boolean()}</code></dt> +%% <dd>Enables saving of abstract structure on file for debugging +%% purpose.</dd> +%% <dt><code>{xsdbase,filename()}</code></dt> +%% <dd>XSD Base directory.</dd> +%% <dt><code>{fetch_fun,FetchFun}</code></dt> +%% <dd>Call back function to fetch an external resource.</dd> +%% <dt><code>{fetch_path,PathList}</code></dt> +%% <dd>PathList is a list of directories to search when fetching files. +%% If the file in question is not in the fetch_path, the URI will +%% be used as a file name.</dd> +%% <dt><code>{state,State}</code></dt> +%% <dd>It is possible by this option to provide a state with process +%% information from an earlier validation.</dd> +%% </dl> +-type option_list() :: [{xsdbase,filename()} | + {atom(),term()}]. + +%% @type filename() = string() +%% @end +-type filename() :: string(). %%====================================================================== @@ -124,6 +134,14 @@ validate(Xml,State) -> %% </p> %% <p> Observe that E2 may differ from E if for instance there are default %% values defined in <code>my_XML_Schema.xsd</code>.</p> +-spec validate(Element,State,Options) -> Result when + Element :: #xmlElement{}, + Options :: option_list(), + Result :: {ValidElement,global_state()} | {error,Reasons}, + ValidElement :: #xmlElement{}, + State :: global_state(), + Reasons :: [ErrorReason] | ErrorReason, + ErrorReason :: term(). validate(Xml,State,Opts) when is_record(State,xsd_state) -> S2 = initiate_state2(State,Opts), S3 = validation_options(S2,Opts), -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor