File 1361-Fix-typos-in-lib-xmerl.patch of Package erlang

From f7dbb2fdeb8db2bbad67f1a006f21e8acf3e3d47 Mon Sep 17 00:00:00 2001
From: Kian-Meng Ang <kianmeng@cpan.org>
Date: Fri, 7 Jan 2022 21:11:07 +0800
Subject: [PATCH] Fix typos in lib/xmerl

---
 lib/xmerl/doc/examples/xml/xmerl.xml       |   4 +-
 lib/xmerl/doc/src/xmerl_examples.html      |   4 +-
 lib/xmerl/include/xmerl_xsd.hrl            |  10 +-
 lib/xmerl/src/xmerl_regexp.erl             |   4 +-
 lib/xmerl/src/xmerl_sax_parser.erl         |   2 +-
 lib/xmerl/src/xmerl_sax_parser.hrl         |   4 +-
 lib/xmerl/src/xmerl_sax_parser_base.erlsrc |  10 +-
 lib/xmerl/src/xmerl_sax_parser_list.erlsrc |   2 +-
 lib/xmerl/src/xmerl_scan.erl               |  26 ++---
 lib/xmerl/src/xmerl_ucs.erl                |   2 +-
 lib/xmerl/src/xmerl_validate.erl           |   2 +-
 lib/xmerl/src/xmerl_xpath.erl              |   2 +-
 lib/xmerl/src/xmerl_xsd.erl                | 116 ++++++++++-----------
 lib/xmerl/src/xmerl_xsd_type.erl           |   2 +-
 lib/xmerl/test/xmerl_SUITE.erl             |  10 +-
 lib/xmerl/test/xmerl_sax_std_SUITE.erl     |  30 +++---
 16 files changed, 115 insertions(+), 115 deletions(-)

diff --git a/lib/xmerl/doc/examples/xml/xmerl.xml b/lib/xmerl/doc/examples/xml/xmerl.xml
index f02282dbef..983a0bfde1 100644
--- a/lib/xmerl/doc/examples/xml/xmerl.xml
+++ b/lib/xmerl/doc/examples/xml/xmerl.xml
@@ -127,7 +127,7 @@ xmerl_scan:file(Filename [ , Options ]) -> #xmlElement{}. </programlisting>
 	e.g. <computeroutput>xmerl_eventp.erl</computeroutput>) is for
 	customization functions to share one of the local states (in
 	<computeroutput>xmerl_eventp.erl</computeroutput>, the
-	continuation function and the fetch function both acces the
+	continuation function and the fetch function both access the
 	<computeroutput>cont_state</computeroutput>.)</para>
 
 	<para>Functions to access user state:</para>
@@ -357,7 +357,7 @@ Occurrence  ::= '*' | '?' | '+'
 
 	<para>The accumulator function is called to accumulate the
 	contents of an entity.When parsing very large files, it may
-	not be desireable to do so.In this case, an acc function can
+	not be desirable to do so.In this case, an acc function can
 	be provided that simply doesn't accumulate.</para>
 
 	<para>Note that it is possible to even modify the parsed
diff --git a/lib/xmerl/doc/src/xmerl_examples.html b/lib/xmerl/doc/src/xmerl_examples.html
index 1305f59d4a..7c8ef3d4bb 100644
--- a/lib/xmerl/doc/src/xmerl_examples.html
+++ b/lib/xmerl/doc/src/xmerl_examples.html
@@ -71,7 +71,7 @@
  	e.g. <tt>xmerl_eventp.erl</tt>) is for
  	customization functions to share one of the local states (in
  	<tt>xmerl_eventp.erl</tt>, the
- 	continuation function and the fetch function both acces the
+ 	continuation function and the fetch function both access the
  	<tt>cont_state</tt>.)</p>
 
  	<p>Functions to access user state:</p>
@@ -310,7 +310,7 @@
 
  	<p>The accumulator function is called to accumulate the
  	contents of an entity.When parsing very large files, it may
- 	not be desireable to do so.In this case, an acc function can
+ 	not be desirable to do so.In this case, an acc function can
  	be provided that simply doesn't accumulate.</p>
 
  	<p>Note that it is possible to even modify the parsed
diff --git a/lib/xmerl/include/xmerl_xsd.hrl b/lib/xmerl/include/xmerl_xsd.hrl
index e3ee8efd40..31633d01da 100644
--- a/lib/xmerl/include/xmerl_xsd.hrl
+++ b/lib/xmerl/include/xmerl_xsd.hrl
@@ -51,7 +51,7 @@
 	  global_namespace_nodes=[],
 	  checked_namespace_nodes=[{"xml",[],'http://www.w3.org/XML/1998/namespace'}],
 	  table,
-	  tab2file=false, %% for debuging of abstract syntax
+	  tab2file=false, %% for debugging of abstract syntax
 	  redefine=false,
 	  finalDefault, %% undefined | '#all' | [atom()] 
 	                %% atom() -> extension |
@@ -89,7 +89,7 @@
 	  scope,
 	  form,             %% unqualified | qualified
 	  id,
-	  occurance={1,1},  %% {minOccurs,maxOccurs}
+	  occurrence={1,1},  %% {minOccurs,maxOccurs}
 	  value_constraint, %% undefined | {default,Value} | {fixed,Value}
 	  nillable=false,   %% true | false
 	  abstract=false,   %% true | false
@@ -153,7 +153,7 @@
 	  id,
 	  ref, %% in this case no name or content
 	  content=[],
-	  occurance={1,1}
+	  occurrence={1,1}
 	 }).
 -record(schema_extension,{
 	  base,
@@ -189,9 +189,9 @@
 %% alterantive, a collection of objects of which only one is chosen.
 -record(chain,{
 	  content,
-	  occurance={1,1}
+	  occurrence={1,1}
 	 }).
 -record(alternative,{
 	  content,
-	  occurance={0,1}
+	  occurrence={0,1}
 	 }).
diff --git a/lib/xmerl/src/xmerl_regexp.erl b/lib/xmerl/src/xmerl_regexp.erl
index 1bf8496673..dc5e944f9d 100644
--- a/lib/xmerl/src/xmerl_regexp.erl
+++ b/lib/xmerl/src/xmerl_regexp.erl
@@ -510,7 +510,7 @@ gsub_comp([], _P, _RE, _Bef, _Rep) -> no.
 
 %% split(String, RegExp) -> {ok,[SubString]} | {error,E}.
 %%  Split a string into substrings where the RegExp describes the
-%%  field seperator. The RegExp " " is specially treated.
+%%  field separator. The RegExp " " is specially treated.
 
 split(String, " ") ->				%This is really special
     {ok,{regexp,RE}} = parse("[ \t]+"),
@@ -1289,7 +1289,7 @@ accept([], _NFA) -> no.
 %% minimise_dfa(DFA, StartState, FirstState) -> {DFA,StartState}.
 %%  Minimise the DFA by removing equivalent states. We consider a
 %%  state if both the transitions and the their accept state is the
-%%  same.  First repeatedly run throught the DFA state list removing
+%%  same.  First repeatedly run through the DFA state list removing
 %%  equivalent states and updating remaining transitions with
 %%  remaining equivalent state numbers. When no more reductions are
 %%  possible then pack the remaining state numbers to get consecutive
diff --git a/lib/xmerl/src/xmerl_sax_parser.erl b/lib/xmerl/src/xmerl_sax_parser.erl
index 1b17b1d5cb..e582a910d1 100644
--- a/lib/xmerl/src/xmerl_sax_parser.erl
+++ b/lib/xmerl/src/xmerl_sax_parser.erl
@@ -158,7 +158,7 @@ parse_binary(Xml, #xmerl_sax_parser_state{encoding={utf16,big}}=State, F) ->
 parse_binary(Xml, #xmerl_sax_parser_state{encoding=latin1}=State, F) ->
     xmerl_sax_parser_latin1:F(Xml, State);
 parse_binary(_, #xmerl_sax_parser_state{encoding=Enc}, State) ->
-    ?fatal_error(State, lists:flatten(io_lib:format("Charcter set ~p not supported", [Enc]))).
+    ?fatal_error(State, lists:flatten(io_lib:format("Character set ~p not supported", [Enc]))).
 
 %%----------------------------------------------------------------------
 %% Function: initial_state/0
diff --git a/lib/xmerl/src/xmerl_sax_parser.hrl b/lib/xmerl/src/xmerl_sax_parser.hrl
index aac155ac63..7103e05719 100644
--- a/lib/xmerl/src/xmerl_sax_parser.hrl
+++ b/lib/xmerl/src/xmerl_sax_parser.hrl
@@ -47,7 +47,7 @@
 -define(is_hex_digit(C), $0 =< C, C =< $9; $a =< C, C =< $f; $A =< C, C =< $F). 
 
 %%----------------------------------------------------------------------
-%% Definition of XML charcters
+%% Definition of XML characters
 %%
 %% [2] Char #x9 | #xA | #xD | [#x20-#xD7FF] | [#xE000-#xFFFD] | [#x10000-#x10FFFF]
 %%----------------------------------------------------------------------
@@ -82,7 +82,7 @@
 	  current_tag = [],         % Current tag 
 	  end_tags = [],            % Stack of tags used for end tag matching 
 	  match_end_tags = true,    % Flag which defines if the parser should match on end tags
-	  ref_table,                % Table containing entitity definitions
+	  ref_table,                % Table containing entity definitions
 	  standalone = no,          % yes if the document is standalone and don't need an external DTD.
 	  file_type = normal,       % Can be normal, dtd and entity
 	  current_location,         % Location of the currently parsed XML entity
diff --git a/lib/xmerl/src/xmerl_sax_parser_base.erlsrc b/lib/xmerl/src/xmerl_sax_parser_base.erlsrc
index 49a9a6ada6..7a19cb38bc 100644
--- a/lib/xmerl/src/xmerl_sax_parser_base.erlsrc
+++ b/lib/xmerl/src/xmerl_sax_parser_base.erlsrc
@@ -1727,7 +1727,7 @@ parse_reference(?STRING_UNBOUND_REST(C, Rest), State, HaveToExist) ->
     end;
 parse_reference(Bytes, State, HaveToExist) ->
     unicode_incomplete_check([Bytes, State, HaveToExist, fun parse_reference/3], 
-			     underfined).
+			     undefined).
 
 
 parse_reference_1(?STRING_REST(";", Rest), State, HaveToExist, Name) ->
@@ -1799,7 +1799,7 @@ parse_pe_reference(?STRING_UNBOUND_REST(C, Rest), State) ->
     end;
 parse_pe_reference(Bytes, State) ->
     unicode_incomplete_check([Bytes, State, fun parse_pe_reference/2], 
-			     underfined).
+			     undefined).
 
 
 parse_pe_reference_1(?STRING_REST(";", Rest), State, Name) ->
@@ -2028,7 +2028,7 @@ normalize_whitespace([], Acc) ->
 %%             State = #xmerl_sax_parser_state{}
 %% Result    : {Rest, State}
 %% Description: This function starts an parsing of the DTD
-%%              that sends apropriate events. 
+%%              that sends appropriate events. 
 %%              [28] doctypedecl ::= '<!DOCTYPE' S Name (S ExternalID)? S? 
 %%                          ('[' (markupdecl | PEReference | S)* ']' S?)? '>'
 %%----------------------------------------------------------------------
@@ -2057,7 +2057,7 @@ parse_doctype(Bytes, State) ->
 %%             Name = string()
 %%             Definition = true |false
 %% Result    : {Rest, State}
-%% Description: Gets the DTD name as a parameter and contine parse the DOCTYPE
+%% Description: Gets the DTD name as a parameter and continue parse the DOCTYPE
 %%              directive
 %%----------------------------------------------------------------------
 parse_doctype_1(?STRING_EMPTY, State, Name, Definition) ->
@@ -3829,7 +3829,7 @@ parse_notation_decl_1(Bytes, State) ->
 %%             PubId = string()
 %%             SysId = string()
 %% Description: Parse a NOTATION identity. The public id case is a special 
-%%              variant of extenal id where just the public part is allowed.
+%%              variant of external id where just the public part is allowed.
 %%              This is allowed if the third parameter in parse_external_id/3 
 %%              is true.
 %%              [83] PublicID ::= 'PUBLIC' S PubidLiteral 
diff --git a/lib/xmerl/src/xmerl_sax_parser_list.erlsrc b/lib/xmerl/src/xmerl_sax_parser_list.erlsrc
index ac89896215..73afadf34b 100644
--- a/lib/xmerl/src/xmerl_sax_parser_list.erlsrc
+++ b/lib/xmerl/src/xmerl_sax_parser_list.erlsrc
@@ -34,7 +34,7 @@
 -define(APPEND_STRING(Rest, New), Rest ++ New).
 -define(TO_INPUT_FORMAT(Val), Val).
 
-%%  In the list case we can't use a '++' when matchin against an unbound variable 
+%%  In the list case we can't use a '++' when matching against an unbound variable 
 -define(STRING_UNBOUND_REST(MatchChar, Rest), [MatchChar | Rest]).
 
 -define(PARSE_BYTE_ORDER_MARK(Bytes, State),
diff --git a/lib/xmerl/src/xmerl_scan.erl b/lib/xmerl/src/xmerl_scan.erl
index 270d5b4962..d6edab1a17 100644
--- a/lib/xmerl/src/xmerl_scan.erl
+++ b/lib/xmerl/src/xmerl_scan.erl
@@ -3637,7 +3637,7 @@ scan_entity_value("%" ++ T, S0, Delim, Acc, PEName,Namespace,PENesting) ->
 		     ExpRef ->
 			{string_to_char_set(S1#xmerl_scanner.encoding, ExpRef) ,S1}
 		end,
-	    %% single or duoble qoutes are not treated as delimeters
+	    %% single or duoble quotes are not treated as delimiters
 	    %% in passages "included in literal"
 	    S3 = S2#xmerl_scanner{col=S2#xmerl_scanner.col+1},
 	    {Acc2,_,S4} = scan_entity_value(ExpandedRef,S3,no_delim,Acc,
@@ -3678,32 +3678,32 @@ scan_entity_value("&" ++ T, S0, Delim, Acc, PEName,Namespace,PENesting) ->
 	    scan_entity_value(T2,S2,Delim,[";",atom_to_list(Name),"&"|Acc],PEName,Namespace,PENesting)
     end;
 %% The following clauses is for PE Nesting VC constraint
-%% Start delimeter for ConditionalSection
+%% Start delimiter for ConditionalSection
 scan_entity_value("<!["++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(3),
     scan_entity_value(T,S,Delim,["<!["|Acc],PEName,NS,
 		      pe_push("<![",PENesting,S));
-%% Start delimeter for ConditionalSection (2)
+%% Start delimiter for ConditionalSection (2)
 scan_entity_value("["++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(1),
     scan_entity_value(T,S,Delim,["["|Acc],PEName,NS,
 		      pe_push("[",PENesting,S));
-%% Start delimeter for comment
+%% Start delimiter for comment
 scan_entity_value("<!--"++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(4),
     scan_entity_value(T,S,Delim,["<!--"|Acc],PEName,NS,
 		      pe_push("<!--",PENesting,S));
-%% Start delimeter for ElementDecl, AttListDecl,EntityDecl,NotationDecl
+%% Start delimiter for ElementDecl, AttListDecl,EntityDecl,NotationDecl
 scan_entity_value("<!"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(2),
     scan_entity_value(T,S,Delim,["<!"|Acc],PEName,NS,
 		      pe_push("<!",PENesting,S));
-%% Start delimeter for PI
+%% Start delimiter for PI
 scan_entity_value("<?"++T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(2),
     scan_entity_value(T,S,Delim,["<?"|Acc],PEName,NS,
 		      pe_push("<?",PENesting,S));
-%% Start delimeter for elements that matches the proper stop delimeter
+%% Start delimiter for elements that matches the proper stop delimiter
 %% for a markupdecl
 scan_entity_value("</"++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(2),
@@ -3713,32 +3713,32 @@ scan_entity_value("<"++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(1),
     scan_entity_value(T,S,Delim,["<"|Acc],PEName,NS,
 		      pe_push("<",PENesting,S));
-%% Delimeter for contentspecs
+%% Delimiter for contentspecs
 scan_entity_value("("++T,S0,Delim,Acc,PEName,parameter=NS,PENesting)->
     ?bump_col(1),
     scan_entity_value(T,S,Delim,["("|Acc],PEName,NS,
 		      pe_push("(",PENesting,S));
-%% Stop delimeter for ElementDecl, AttListDecl,EntityDecl,NotationDecl
+%% Stop delimiter for ElementDecl, AttListDecl,EntityDecl,NotationDecl
 scan_entity_value(">"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(1),
     scan_entity_value(T,S,Delim,[">"|Acc],PEName,NS,
 		      pe_pop(">",PENesting,S));
-%% Stop delimeter for PI
+%% Stop delimiter for PI
 scan_entity_value("?>"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(2),
     scan_entity_value(T,S,Delim,["?>"|Acc],PEName,NS,
 		      pe_pop("?>",PENesting,S));
-%% Stop delimeter for comment
+%% Stop delimiter for comment
 scan_entity_value("-->"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(3),
     scan_entity_value(T,S,Delim,["-->"|Acc],PEName,NS,
 		      pe_pop("-->",PENesting,S));
-%% Stop delimeter for ConditionalSection
+%% Stop delimiter for ConditionalSection
 scan_entity_value("]]>"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(3),
     scan_entity_value(T,S,Delim,["]]>"|Acc],PEName,NS,
 		      pe_pop("]]>",PENesting,S));
-%% Stop delimeter added to match a content start delimeter included
+%% Stop delimiter added to match a content start delimiter included
 scan_entity_value("/>"++ T,S0,Delim,Acc,PEName, parameter=NS,PENesting) ->
     ?bump_col(2),
     scan_entity_value(T,S,Delim,["/>"|Acc],PEName,NS,
diff --git a/lib/xmerl/src/xmerl_ucs.erl b/lib/xmerl/src/xmerl_ucs.erl
index 4b1fc30089..348d30a6c9 100644
--- a/lib/xmerl/src/xmerl_ucs.erl
+++ b/lib/xmerl/src/xmerl_ucs.erl
@@ -423,7 +423,7 @@ char_to_utf8(Ch) when is_integer(Ch), Ch >= 0 ->
 
 %% expand_utf8([Byte]) -> {[UnicodeChar],NumberOfBadBytes}
 %%  Expand UTF8 byte sequences to ISO 10646/Unicode
-%%  charactes. Any illegal bytes are removed and the number of
+%%  characters. Any illegal bytes are removed and the number of
 %%  bad bytes are returned.
 %%
 %%  Reference:
diff --git a/lib/xmerl/src/xmerl_validate.erl b/lib/xmerl/src/xmerl_validate.erl
index 8b4f5b91a2..f2b427639f 100644
--- a/lib/xmerl/src/xmerl_validate.erl
+++ b/lib/xmerl/src/xmerl_validate.erl
@@ -509,7 +509,7 @@ choice([CH|CHS],[_XML|_T]=XMLS,Rules,WSaction,S)->
 	{[],XMLS1} -> %% Maybe a sequence with * or ? elements that
                       %% didn't match
  	    case CHS of
- 		[] -> % choice has succeded but without matching XMLS1
+ 		[] -> % choice has succeeded but without matching XMLS1
  		    {[],XMLS1};
  		_ -> % there are more choice alternatives to try with
  		    choice(CHS,XMLS1,Rules,WSaction,S)
diff --git a/lib/xmerl/src/xmerl_xpath.erl b/lib/xmerl/src/xmerl_xpath.erl
index 6146feba49..da8449cc5e 100644
--- a/lib/xmerl/src/xmerl_xpath.erl
+++ b/lib/xmerl/src/xmerl_xpath.erl
@@ -601,7 +601,7 @@ match_preceding_sibling(Tok, N, Acc, Context) ->
 
 
 %% "The 'preceding' axis contains all nodes in the same document as the context
-%% node that are before the context node in document order, exluding any
+%% node that are before the context node in document order, excluding any
 %% ancestors and excluding attribute nodes and namespace nodes."
 match_preceding(Tok, N, Acc, Context) ->
     #xmlNode{parents = Ps, node = Node} = N,
diff --git a/lib/xmerl/src/xmerl_xsd.erl b/lib/xmerl/src/xmerl_xsd.erl
index 2836bb0e5b..967e61da89 100644
--- a/lib/xmerl/src/xmerl_xsd.erl
+++ b/lib/xmerl/src/xmerl_xsd.erl
@@ -25,7 +25,7 @@
 %% 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 
-%% representated by the <code>#xsd_state{}</code> record.
+%% represented by the <code>#xsd_state{}</code> record.
 %% </p>
 %% @type option_list(). <p>Options allow to customize the behaviour of the 
 %% validation.
@@ -400,7 +400,7 @@ new_state(Opts) ->
 %% information as defined elements and types.
 validate_schema(E=#xmlElement{},
 		    S) ->
-    %% namespace is always a xmlNamespace record, attributs a list of
+    %% namespace is always a xmlNamespace record, attributes a list of
     %% #xmlAttributes and content a list of #xmlElements|#xmlText|...
 
     %% Have to save namespace nodes. Use of namespace in paths for
@@ -563,7 +563,7 @@ element_content({element,S},El,Env) ->
     case qualify_NCName(El,S) of
 	no_name ->
 	    Ref = particle_ref(El),
-	    {Occ,S2} = occurance(El,{1,1},S),
+	    {Occ,S2} = occurrence(El,{1,1},S),
 	    %% 3.3.3 bullet 2.2
 	    S3 = element_forbidden_properties(El,S2),
 	    S4 = element_forbidden_content(El#xmlElement.content,S3),
@@ -578,7 +578,7 @@ element_content({element,S},El,Env) ->
 	    Type2 = remove_annotation(Type),
 	    Unique = [X||X={unique,_} <- Type2],
 	    Key = [X||X={K,_} <- Type2,K == key orelse K==keyref],
-	    {Occur,S4} = occurance(El,{1,1},S3),
+	    {Occur,S4} = occurrence(El,{1,1},S3),
 	    {SE,S5} = element_properties(El#xmlElement.attributes,
 					 #schema_element{},El,S4),
 	    CM = remove_attributes([X||X={Y,_}<-Type2,
@@ -586,14 +586,14 @@ element_content({element,S},El,Env) ->
 				       keyref=/=Y,annotation=/=Y]),
 	    %% take care of key/keyref later
 	    SE2 = SE#schema_element{name=Name,type=CM,uniqueness=Unique,
-				    key=Key, occurance=Occur,
+				    key=Key, occurrence=Occur,
 				    scope=S5#xsd_state.scope},
 	    S6 = insert_substitutionGroup(SE2,S5),
 	    S7 = save_object({element,SE2},S6),
 	    {{element,{Name,Occur}},S7}
     end;
 element_content({complexType,S},CT,Env) ->
-    %% complex type definition without a name is returnd and added to
+    %% complex type definition without a name is returned and added to
     %% the content model at this level. A complex type may also contain
     %% attributes or attribute group references in the end of its content.
     %%?debug("complexType content: ~p~nenv: ~p~n",[CT,Env]),
@@ -677,7 +677,7 @@ element_content({group,S},G,Env) ->
 	    %% "Schema Representation Constraint: Individual Component
 	    %% Redefinition"
 	    Ref = particle_ref(G),
-	    {Occur,S2} = occurance(G,{1,1},S),
+	    {Occur,S2} = occurrence(G,{1,1},S),
 	    GRef =
 		{group,
 	      {get_QName(Ref,G#xmlElement.namespace,reset_scope(S2)),%%QQQ
@@ -694,16 +694,16 @@ element_content({group,S},G,Env) ->
     end;
 element_content({all,S},All,Env) ->
     %% each element occurs 0 or 1 times in any order
-    %% {all,[{element_name,occurance}]}
+    %% {all,[{element_name,occurrence}]}
 %%    CM = content_model(Seq#xmlElement.content,S,[all|Env]),
-    {Occur,S1} = occurance(All,{1,1},S),
+    {Occur,S1} = occurrence(All,{1,1},S),
     {CM,S2} = type(All#xmlElement.content,S1,[all|Env]),
     S3 = check_cm(all,allowed_content(all,Env),CM,S2),
     {{all,{[X||X = {element,_} <- CM],Occur}},S3};
 element_content({sequence,S},Seq,Env) ->
-    %% {sequence,[{element_name,occurance}]}
+    %% {sequence,[{element_name,occurrence}]}
 %%    CM = content_model(Seq#xmlElement.content,S,[sequence|Env]),
-    {Occur,S1} = occurance(Seq,{1,1},S),
+    {Occur,S1} = occurrence(Seq,{1,1},S),
     {CM,S2} = type(Seq#xmlElement.content,S1,[sequence|Env]),
     S3 = check_cm(sequence,allowed_content(sequence,Env),CM,S2),
     {{sequence,{remove_annotation(CM),Occur}},S3};
@@ -712,12 +712,12 @@ element_content({choice,S},Choice,Env) ->
     %%                   (element | group | choice | sequence | any)*)
     %% returns: {choice,[element_name]}
 %%    CM = content_model(Choice#xmlElement.content,S,[choice|Env]),
-    {Occur,S1} = occurance(Choice,{1,1},S),
+    {Occur,S1} = occurrence(Choice,{1,1},S),
     {CM,S2} = type(Choice#xmlElement.content,S1,[choice|Env]),
     S3 = check_cm(choice,allowed_content(choice,Env),CM,S2),
     {{choice,{remove_annotation(CM),Occur}},S3};
 element_content({any,S},Any,_Env) ->
-    {Occur,S1} = occurance(Any,{1,1},S),
+    {Occur,S1} = occurrence(Any,{1,1},S),
     NameSpace = wildcard_namespace(Any,S1),
     PC = processor_contents(Any),
     ?debug("element_content, any: Any content:~p~n",[Any#xmlElement.content]),
@@ -1426,7 +1426,7 @@ check_cm(Kind,S4SCM,ContentModel,S) ->
 	    exit({error,{[],?MODULE,{internal_error,Err}}})
     end.
 
-check_cm2(Kind,#chain{content=S4SCM,occurance=Occ},
+check_cm2(Kind,#chain{content=S4SCM,occurrence=Occ},
 	 ContentModel,S) ->
     case occurance_loop(Occ,fun check_chain/1,
 			[S4SCM,ContentModel,Kind,S],0) of
@@ -1445,7 +1445,7 @@ check_cm2(Kind,#chain{content=S4SCM,occurance=Occ},
 	    Err = {[],?MODULE,{illegal_content,Reason,Kind}},
 	    {ContentModel,acc_errs(S,Err)}
     end;
-check_cm2(Kind,#alternative{content=S4SCM,occurance=Occ},
+check_cm2(Kind,#alternative{content=S4SCM,occurrence=Occ},
 	 ContentModel,S) ->
     case occurance_loop(Occ,fun check_alternative/1,
 			[S4SCM,ContentModel,Kind,S],0) of
@@ -1621,9 +1621,9 @@ optional({_,{_,{0,_}}}) ->
     true; %% sequence, all or choice
 optional({any,{_,{0,_},_}}) ->
     true;
-optional(#chain{occurance={0,_}}) ->
+optional(#chain{occurrence={0,_}}) ->
     true;
-optional(#alternative{occurance={0,_}}) ->
+optional(#alternative{occurrence={0,_}}) ->
     true;
 optional(#chain{content=Content}) ->
     catch is_optional_content(Content);
@@ -1671,10 +1671,10 @@ allowed_content(element,_Parents) ->
 	       #chain{content=
 			 [#alternative{content=
 				  [{simpleType,{1,1}},{complexType,{1,1}}],
-				  occurance={0,1}},
+				  occurrence={0,1}},
 			  #alternative{content=
 				  [{unique,{1,1}},{key,{1,1}},{keyref,{1,1}}],
-				  occurance={0,unbounded}}]
+				  occurrence={0,unbounded}}]
 			}]
 	     };
 allowed_content(attribute,_Parents) ->
@@ -1689,12 +1689,12 @@ allowed_content(complexType,Parents) ->
 		    [#alternative{content=
 				  [{group,{1,1}},{all,{1,1}},
 				   {choice,{1,1}},{sequence,{1,1}}],
-				  occurance={0,1}},
+				  occurrence={0,1}},
 		     #chain{content=
 			    [#alternative{content=
 					  [{attribute,{1,1}},
 					   {attributeGroup,{1,1}}],
-					  occurance={0,unbounded}},
+					  occurrence={0,unbounded}},
 			     {anyAttribute,{0,1}}]
 			   }
 		    ]
@@ -1714,7 +1714,7 @@ allowed_content(attributeGroup,Parents) ->
 				 [#alternative{content=
 					  [{attribute,{1,1}},
 					   {attributeGroup,{1,1}}],
-					  occurance={0,unbounded}},
+					  occurrence={0,unbounded}},
 				  {anyAttribute,{0,1}}]}]}
     end;
 allowed_content(group,_Parents) ->
@@ -1722,7 +1722,7 @@ allowed_content(group,_Parents) ->
 	      [{annotation,{0,1}},
 	       #alternative{content=
 		       [{all,{1,1}},{choice,{1,1}},{sequence,{1,1}}],
-		       occurance={0,1}}]};
+		       occurrence={0,1}}]};
 allowed_content(all,_Parents) ->
     #chain{content=[{annotation,{0,1}},{element,{0,unbounded}}]};
 allowed_content(SorC,_Parents) when SorC==sequence;SorC==choice ->
@@ -1732,7 +1732,7 @@ allowed_content(SorC,_Parents) when SorC==sequence;SorC==choice ->
 		       [{element,{1,1}},{group,{1,1}},
 			{choice,{1,1}},{sequence,{1,1}},
 			{any,{1,1}}],
-		       occurance={0,unbounded}}]};
+		       occurrence={0,unbounded}}]};
 %% allowed_content(E,_Parents)
 %%   when E==any;E==selector;E==field;E==notation;E==include;E==import;
 %%        E==anyAttribute ->
@@ -1744,7 +1744,7 @@ allowed_content(SorC,_Parents) when SorC==sequence;SorC==choice ->
 %% 			 [{selector,{1,1}},{selector,{1,unbounded}}]}]};
 %% allowed_content(annotation,_Parents) ->
 %%     #alternative{content=[{appinfo,{1,1}},{documentation,{1,1}}],
-%% 	    occurance={0,unbounded}};
+%% 	    occurrence={0,unbounded}};
 %% allowed_content(E,_Parents) when E==appinfo;E==documentation ->
 %%     {any,{0,unbounded}};
 allowed_content(simpleType,_Parents) ->
@@ -1771,7 +1771,7 @@ allowed_content(LU,_Parent) when LU==list;LU==union ->
 %% 	      [#alternative{content=
 %% 		       [{include,{1,1}},{import,{1,1}},
 %% 			{redefine,{1,1}},{annotation,{1,1}}],
-%% 		       occurance={0,1}},
+%% 		       occurrence={0,1}},
 %% 	       #chain{content=
 %% 			 [#alternative{content=
 %% 				  [#alternative{content=
@@ -1781,14 +1781,14 @@ allowed_content(LU,_Parent) when LU==list;LU==union ->
 %% 				   {attribute,{1,1}},
 %% 				   {notation,{1,1}}]},
 %% 			  {annotation,{0,unbounded}}],
-%% 			 occurance={0,unbounded}}]};
+%% 			 occurrence={0,unbounded}}]};
 allowed_content(redefine,_Parents) ->
     #alternative{content=
 	    [{annotation,{1,1}},
 	     #alternative{content=
 		     [{simpleType,{1,1}},{complexType,{1,1}},
 		      {group,{1,1}},{attributeGroup,{1,1}}]}],
-	    occurance={0,unbounded}};
+	    occurrence={0,unbounded}};
 allowed_content(E,_Parents) when E==simpleContent;
 				 E==complexContent ->
     #chain{content=
@@ -1842,7 +1842,7 @@ allowed_content2(restriction,simpleType) ->
 				   {length,{1,1}},{minLength,{1,1}},
 				   {maxLength,{1,1}},{enumeration,{1,1}},
 				   {whiteSpace,{1,1}},{pattern,{1,1}}],
-				  occurance={0,unbounded}}]}]};
+				  occurrence={0,unbounded}}]}]};
 allowed_content2(restriction,simpleContent) ->
     #chain{content=
 	      [{annotation,{0,1}},
@@ -1855,12 +1855,12 @@ allowed_content2(restriction,simpleContent) ->
 				  {length,{1,1}},{minLength,{1,1}},
 				  {maxLength,{1,1}},{enumeration,{1,1}},
 				  {whiteSpace,{1,1}},{pattern,{1,1}}],
-				 occurance={0,unbounded}}],
-			 occurance={0,1}},
+				 occurrence={0,unbounded}}],
+			 occurrence={0,1}},
 	       #chain{content=
 			 [#alternative{content=
 				 [{attribute,{1,1}},{attributeGroup,{1,1}}],
-				  occurance={0,unbounded}},
+				  occurrence={0,unbounded}},
 			  {anyAttribute,{0,1}}]}]};
 allowed_content2(restriction,complexContent) ->
     #chain{content=
@@ -1868,11 +1868,11 @@ allowed_content2(restriction,complexContent) ->
 	       #alternative{content=
 		       [{group,{1,1}},{all,{1,1}},{choice,{1,1}},
 			{sequence,{1,1}}],
-		       occurance={0,1}},
+		       occurrence={0,1}},
 	       #chain{content=
 			 [#alternative{content=
 				  [{attribute,{1,1}},{attributeGroup,{1,1}}],
-				  occurance={0,unbounded}},
+				  occurrence={0,unbounded}},
 			  {anyAttribute,{0,1}}]}]};
 allowed_content2(extension,simpleContent) ->
     #chain{content=
@@ -1880,7 +1880,7 @@ allowed_content2(extension,simpleContent) ->
 	       #chain{content=
 			 [#alternative{content=
 				  [{attribute,{1,1}},{attributeGroup,{1,1}}],
-				  occurance={0,unbounded}},
+				  occurrence={0,unbounded}},
 			  {anyAttribute,{0,1}}]}]};
 allowed_content2(extension,complexContent) ->
     #chain{content=
@@ -1889,19 +1889,19 @@ allowed_content2(extension,complexContent) ->
 			 [#alternative{content=
 				  [{group,{1,1}},{all,{1,1}},{choice,{1,1}},
 				   {sequence,{1,1}}],
-				  occurance={0,1}},
+				  occurrence={0,1}},
 			  #chain{content=
 				    [#alternative{content=
 					     [{attribute,{1,1}},
 					      {attributeGroup,{1,1}}],
-					     occurance={0,1}},
+					     occurrence={0,1}},
 				     {anyAttribute,{0,1}}]}]}]}.
 						  
 
 set_occurance(Ch = #chain{},Occ) ->
-    Ch#chain{occurance=Occ};
+    Ch#chain{occurrence=Occ};
 set_occurance(Alt = #alternative{},Occ) ->
-    Alt#alternative{occurance=Occ};
+    Alt#alternative{occurrence=Occ};
 set_occurance({Name,_},Occ) when is_atom(Name) ->
     {Name,Occ}.
 %% set_occurance(CM,_) ->
@@ -1992,7 +1992,7 @@ save_namespace_definition(NameSpace,
 				       checked_namespace_nodes=CNS}) ->
     %% 1) Have to find a matching namespace in the global list for
     %% this schema, and get the associated prefix. 2) Then check
-    %% whether a schema with this prefix - namespace combinaton
+    %% whether a schema with this prefix - namespace combination
     %% already is checked, if so do nothing. 3a) If this namespace is
     %% checked but with another prefix only add the prefix - namespace
     %% pair to the checked namespace list. 3b) Otherwise add the
@@ -2275,7 +2275,7 @@ set_num_el(S=#xsd_state{},#xsd_state{num_el=I}) ->
     S#xsd_state{num_el=I}.
 
 
-occurance(El=#xmlElement{attributes=Atts},{Min,Max},S) ->
+occurrence(El=#xmlElement{attributes=Atts},{Min,Max},S) ->
     AttVal=fun(#xmlAttribute{value=V},Sin) -> 
 		   case catch mk_int_or_atom(V) of
 		       {'EXIT',_} ->
@@ -2470,7 +2470,7 @@ check_element_type(XML=[#xmlElement{}|_],[{all,{CM,Occ}}|_CMRest],
 %% 3 often. CMEL may be ((simpleType | complexType)?, (unique | key | keyref)*))
 check_element_type(XML=[XMLEl=#xmlElement{}|_],[CMEl|CMRest],Env,
 		   Block,S,Checked) ->
-    %% Three possible releations between XMLEl - CMEl:
+    %% Three possible relations between XMLEl - CMEl:
     %% (1) XMLEl matches CMEl.
     %% (2) XMLEl don't matches CMEl and CMEl is optional.
     %% (3) XMLEl don't matches CMEl, CMEl mandatory, - error.
@@ -2563,12 +2563,12 @@ check_element_type(XML=[XMLEl=#xmlElement{name=Name}|RestXML],
 		   CMEl=#schema_element{name=CMName,type=Type},
 		   Env,Block,S,Checked) ->
     ElName = mk_EII_QName(Name,XMLEl,S#xsd_state{scope=element(2,CMName)}),
-    {Min,Max} = CMEl#schema_element.occurance,
+    {Min,Max} = CMEl#schema_element.occurrence,
     case cmp_name(ElName,CMName,S) of %% substitutionGroup
 	true when S#xsd_state.num_el =< Max ->
 	    S1 = id_constraints(CMEl,XMLEl,S),
 	    %% If CMEl element has a substitutionGroup we have to
-	    %% switch to the rigth element and type here.
+	    %% switch to the right element and type here.
 	    {CMEl2,Type2,S2} =
 		if 
 		    ElName =:= CMName ->
@@ -2705,7 +2705,7 @@ check_element_type(XML=[E=#xmlElement{name=Name}|Rest],
     end;
 check_element_type([],CM,_Env,_Block,S,Checked) ->
     %% #schema_complex_type, any, #schema_group, anyType and lists are
-    %% catched above.
+    %% caught above.
     case CM of
 	#schema_simple_type{} ->
 	    {NewVal,S2} = check_type(CM,[],unapplied,S),
@@ -2777,7 +2777,7 @@ check_sequence(Seq=[_InstEl=#xmlElement{}|_],[El|Els],Occ={_Min,_Max},Env,S,Chec
 %%	    Err;
 	{Ret,UnValRest,S3} ->
 	    %% must also take care of more elements of same name
-	    %% decrease occurance in El for the optional measurements
+	    %% decrease occurrence in El for the optional measurements
 	    %% when Seq is empty.
 	    check_sequence(UnValRest,[decrease_occurance(El)|Els],Occ,Env,
 			   count_num_el(set_num_el(S3,S2)),
@@ -2835,7 +2835,7 @@ check_choice(XML,[],{0,_},_,S,Checked) ->
     %% Choice is optional
     {Checked,XML,set_num_el(S,0)};
 check_choice(XML,[],_,_,S,Checked) ->
-    %% Choice has already matched something, the rest is for somthing
+    %% Choice has already matched something, the rest is for something
     %% else to match.
     case S#xsd_state.num_el > 0 of
 	true ->
@@ -3965,7 +3965,7 @@ resolve(E,S) ->
     load_object(E,S).
 
 %% explicit_type checks whether the instance element is of an explicit
-%% type pointed out by xsi:type. A type refernced by xsi:type must be
+%% type pointed out by xsi:type. A type referenced by xsi:type must be
 %% the same as, or derived from the instance element's type. Concluded
 %% from 3.4.6 section "Schema Component Constraint: Type Derivation OK
 %% (Complex)".
@@ -5080,7 +5080,7 @@ load_redefine_object({Kind,Name},S) ->
 
 load_object({element,{QN,Occ={Min,_}}},S) when is_integer(Min) ->
     case load_object({element,QN},S) of
-	{SE=#schema_element{},S1} -> {SE#schema_element{occurance=Occ},S1};
+	{SE=#schema_element{},S1} -> {SE#schema_element{occurrence=Occ},S1};
 	Other -> Other
     end;
 load_object({group,{QN,_Occ={Min,_}}},S) when is_integer(Min) ->
@@ -5439,11 +5439,11 @@ format_error({unvalidated_rest,UR}) ->
 format_error({no_schemas_provided}) ->
     "Schema: Validator found no schema. A schema must be provided for validation.";
 format_error({internal_error,Reason}) ->
-    io_lib:format("An error occured that was unforeseen, due to ~p.",[Reason]);
+    io_lib:format("An error occurred that was unforeseen, due to ~p.",[Reason]);
 format_error({internal_error,Reason,Info}) ->
-    io_lib:format("An error occured that was unforeseen, due to ~p: ~p.",[Reason,Info]);
+    io_lib:format("An error occurred that was unforeseen, due to ~p: ~p.",[Reason,Info]);
 format_error({internal_error,Function,Info1,Info2}) ->
-    io_lib:format("An internal error occured in function ~p with args: ~p,~p.",[Function,Info1,Info2]);
+    io_lib:format("An internal error occurred in function ~p with args: ~p,~p.",[Function,Info1,Info2]);
 format_error({illegal_content,Reason,Kind}) ->
     io_lib:format("Schema: The schema violates the content model allowed for schemas.~nReason: ~p,~nkind of schema element: ~p.",[Reason,Kind]);
 format_error({no_match,Kind}) ->
@@ -5473,7 +5473,7 @@ format_error({no_element_expected_in_group,XML}) ->
 format_error({element_bad_match,E,Any,_Env}) ->
     io_lib:format("XML: XML element ~p didn't match into the namespace of schema type any ~p.",[E,Any]);
 format_error({match_failure,_XML,_CM,_S}) ->
-    "XML: A combination of XML element(s) and schema definitions that is not known has occured. The implementation doesn't support this structure.";
+    "XML: A combination of XML element(s) and schema definitions that is not known has occurred. The implementation doesn't support this structure.";
 format_error({cannot_contain_text,_XMLTxt,CMEl}) ->
     io_lib:format("XML: The schema structure: ~p doesn't allow text",[CMEl]);
 format_error({missing_mandatory_elements,MandatoryEls}) ->
@@ -5489,7 +5489,7 @@ format_error({element_not_in_all,ElName,E,_CM}) ->
 format_error({missing_mandatory_elements_in_all,MandatoryEls}) ->
     io_lib:format("XML: The schema elements ~p were missed in the XML file.",[MandatoryEls]);
 format_error({failed_validating,E,Any}) ->
-    io_lib:format("XML: The element ~p at location ~p failed validation. It should hav been matched by an any schema element ~p",[E#xmlElement.name,error_path(E,undefined),Any]);
+    io_lib:format("XML: The element ~p at location ~p failed validation. It should have been matched by an any schema element ~p",[E#xmlElement.name,error_path(E,undefined),Any]);
 format_error({schemaLocation_list_failure,Paths}) ->
     io_lib:format("XML: schemaLocation values consists of one or more pairs of URI references, separated by white space. The first is a namespace name the second a reference to a schema: ~p.",[Paths]);
 format_error({element_content_not_nil,XMLEl}) ->
@@ -5502,7 +5502,7 @@ format_error({default_and_fixed_attributes_mutual_exclusive,
 	      Name,Default,Fix}) ->
     io_lib:format("Schema: It is an error in the schema to assign values for both default and fix for an attribute. Attribute: ~p, default: ~p, fix: ~p.",[Name,Default,Fix]);
 format_error({schema_error,unexpected_object,_SA,_Err}) ->
-    "Schema: An unforeseen error case occured, maybee due to an unimplemented feature.";
+    "Schema: An unforeseen error case occurred, maybe due to an unimplemented feature.";
 format_error({attribute_not_defined_in_schema,Name}) ->
     io_lib:format("XML: The attribute ~p is not defined in the provided schema.",[Name]);
 format_error({disallowed_namespace,Namespace,NS,Name}) ->
@@ -5530,9 +5530,9 @@ format_error({key_value_not_unique,KS}) ->
 format_error({keyref_missed_matching_key,Refer}) ->
     io_lib:format("Schema: This keyref had no matching key ~p.",[Refer]);
 format_error({keyref_unexpected_object,_Other}) ->
-    "Schema: An unforeseen error case occured, unknown failure cause.";
+    "Schema: An unforeseen error case occurred, unknown failure cause.";
 format_error({cardinality_of_fields_not_equal,KR,K}) ->
-    io_lib:format("Schema: keyref and the corresponding key must have same cardinality of their fields. Missmatch in this case keyref: ~p, key: ~p.",[KR,K]);
+    io_lib:format("Schema: keyref and the corresponding key must have same cardinality of their fields. Mismatch in this case keyref: ~p, key: ~p.",[KR,K]);
 format_error({could_not_load_keyref,Name}) ->
     io_lib:format("Schema: The schema didn't define a keyref with the name ~p.",[Name]);
 format_error({reference_undeclared,Kind,Ref}) ->
@@ -5542,7 +5542,7 @@ format_error({cyclic_substitutionGroup,SGs}) ->
 format_error({substitutionGroup_error,Head,SG}) ->
     io_lib:format("Schema: Either of substitutionGroup members ~p or ~p is not defined in the provided schema.",[Head,SG]);
 format_error({cyclic_definition,CA}) ->
-    io_lib:format("Schema: A forbidden cicular definition was detected ~p.",[CA]);
+    io_lib:format("Schema: A forbidden circular definition was detected ~p.",[CA]);
 format_error({type_of_element_not_derived,MemT,HeadT}) ->
     io_lib:format("Schema: Type in substitutionGroup members should be simpleType or complexType. In this case ~p and ~p were found.",[MemT, HeadT]);
 format_error({derivation_blocked,BlockTag,Derivation}) ->
diff --git a/lib/xmerl/src/xmerl_xsd_type.erl b/lib/xmerl/src/xmerl_xsd_type.erl
index 8b73c3af3b..433f9776eb 100644
--- a/lib/xmerl/src/xmerl_xsd_type.erl
+++ b/lib/xmerl/src/xmerl_xsd_type.erl
@@ -1499,7 +1499,7 @@ get_digit([],_,[],_Str) ->
 get_digit([],_,_,Str) ->
     {"0",Str};
 get_digit(_,_,_,Str) ->
-    %% this matches both the case when reaching another delimeter and
+    %% this matches both the case when reaching another delimiter and
     %% when the string already are emptied.
     {"0",Str}.
 
diff --git a/lib/xmerl/test/xmerl_SUITE.erl b/lib/xmerl/test/xmerl_SUITE.erl
index bc133558d6..e54603e769 100644
--- a/lib/xmerl/test/xmerl_SUITE.erl
+++ b/lib/xmerl/test/xmerl_SUITE.erl
@@ -445,7 +445,7 @@ generate_heading_col(N) ->
 %% ticket_5998
 %%
 %% A Kleene Closure child in a sequence consumed all following
-%% childs. This problem has been fixed.
+%% child's. This problem has been fixed.
 %%
 ticket_5998(Config) ->
     DataDir = datadir(Config),
@@ -477,7 +477,7 @@ ticket_5998(Config) ->
 %% ticket_7211
 %%
 %% A Kleene Closure child in a sequence consumed all following
-%% childs. This problem has been fixed.
+%% child's. This problem has been fixed.
 %%
 ticket_7211(Config) ->
     DataDir = datadir(Config),
@@ -507,7 +507,7 @@ ticket_7211(Config) ->
 %% ticket_7214
 %%
 %% Now validating xhtml1-transitional.dtd.
-%% A certain contentspec with a succeding choice, that didn't match
+%% A certain contentspec with a succeeding choice, that didn't match
 %% all content, followed by other child elements caused a
 %% failure. This is now corrected.
 %%
@@ -607,7 +607,7 @@ ticket_9457_cont(Continue, Exception, GlobalState) ->
     end.
 
 
-%% Test that comments are handled correct whith
+%% Test that comments are handled correct with
 ticket_9664_schema(Config) ->
     {E, _} = xmerl_scan:file(datadir_join(Config,[misc,"ticket_9664_schema.xml"]),[]),
     {ok, S} = xmerl_xsd:process_schema(datadir_join(Config,[misc,"motorcycles.xsd"])),
@@ -620,7 +620,7 @@ ticket_9664_schema(Config) ->
                               {validation, schema}]),
     ok.
 
-%% Test that comments are handled correct whith
+%% Test that comments are handled correct with
 ticket_9664_dtd(Config) ->
     {E, _} = xmerl_scan:file(datadir_join(Config,[misc,"ticket_9664_dtd.xml"]),[]),
     {E, _} = xmerl_scan:file(datadir_join(Config,[misc,"ticket_9664_dtd.xml"]),[{validation, true}]),
-- 
2.31.1

openSUSE Build Service is sponsored by