update to most recent sgml pl files.

This commit is contained in:
Vitor Santos Costa 2010-05-06 11:37:40 +01:00
parent 9301b67724
commit 515f7eafe2
6 changed files with 118 additions and 84 deletions

View File

@ -465,7 +465,7 @@ l3(uzb, 'Uzbek').
l3(vai, 'Vai').
l3(ven, 'Venda').
l3(vie, 'Vietnamese').
l3(vol, 'Volapük').
l3(vol, 'Volap\u00fck'). % Use \uxxxx for portability. (= \"u)
l3(vot, 'Votic').
l3(wak, 'Wakashan languages').
l3(wal, 'Walamo').

View File

@ -3,9 +3,9 @@
Part of SWI-Prolog
Author: Jan Wielemaker
E-mail: wielemak@science.uva.nl
E-mail: J.Wielemaker@cs.vu.nl
WWW: http://www.swi-prolog.org
Copyright (C): 1985-2005, University of Amsterdam
Copyright (C): 1985-2009, University of Amsterdam
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
@ -58,10 +58,13 @@
xml_quote_attribute/2, % +In, -Quoted
xml_quote_cdata/2, % +In, -Quoted
xml_name/1, % +In
xml_name/2, % +In, +Encoding
iri_xml_namespace/2, % +IRI, -Namespace
iri_xml_namespace/3, % +IRI, -Namespace, -LocalName
xml_is_dom/1 % +Term
]).
:- expects_dialect(swi).
:- assert(system:swi_io).
:- use_module(library(lists)).
:- use_module(library(option)).
@ -73,17 +76,15 @@ user:file_search_path(dtd, '.').
:- if(current_prolog_flag(version_data, swi(_,_,_,_))).
user:file_search_path(dtd, swi('library/DTD')).
:- else.
user:file_search_path(dtd, library('DTD')).
user:file_search_path(dtd, swi('DTD')).
:- endif.
sgml_register_catalog_file(File, Location) :-
prolog_to_os_filename(File, OsFile),
'_sgml_register_catalog_file'(OsFile, Location).
load_foreign :-
current_predicate(_, _:sgml_parse(_,_)), !.
load_foreign :-
load_foreign_library(foreign(sgml2pl)).
:- use_foreign_library(foreign(sgml2pl)).
register_catalog(Base) :-
absolute_file_name(dtd(Base),
@ -94,14 +95,8 @@ register_catalog(Base) :-
SocFile),
sgml_register_catalog_file(SocFile, end).
% make sure this is loaded in the current module, not user.
:- load_foreign.
init :-
ignore(register_catalog('HTML4')).
:- initialization
init.
ignore(register_catalog('HTML4')).
/*******************************
@ -160,10 +155,10 @@ load_dtd(DTD, DtdFile) :-
load_dtd(DTD, DtdFile, Options) :-
split_dtd_options(Options, DTDOptions, FileOptions),
open_dtd(DTD, DTDOptions, DtdOut),
system:swi_open(DtdFile, read, DtdIn, FileOptions),
system:swi_copy_stream_data(DtdIn, DtdOut),
system:swi_close(DtdIn),
system:swi_close(DtdOut).
open(DtdFile, read, DtdIn, FileOptions),
copy_stream_data(DtdIn, DtdOut),
close(DtdIn),
close(DtdOut).
split_dtd_options([], [], []).
split_dtd_options([H|T], [H|TD], S) :-
@ -270,7 +265,10 @@ set_parser_options(Parser, Options, RestOptions) :-
set_parser_options(_, Options, Options).
load_structure(stream(In), Term, Options) :- !,
:- meta_predicate
load_structure(+, -, :).
load_structure(stream(In), Term, M:Options) :- !,
( select_option(offset(Offset), Options, Options1)
-> seek(In, Offset, bof, _)
; Options1 = Options
@ -283,8 +281,8 @@ load_structure(stream(In), Term, Options) :- !,
new_sgml_parser(Parser,
[ dtd(DTD)
]),
def_entities(Options2, DTD, Options3),
call_cleanup(parse(Parser, Options3, TermRead, In),
def_entities(Options2, Parser, Options3),
call_cleanup(parse(Parser, M:Options3, TermRead, In),
free_sgml_parser(Parser)),
( ExplicitDTD == true
-> ( DTD = dtd(_, DocType),
@ -296,33 +294,47 @@ load_structure(stream(In), Term, Options) :- !,
),
Term = TermRead.
load_structure(Stream, Term, Options) :-
system:swi_is_stream(Stream), !,
is_stream(Stream), !,
load_structure(stream(Stream), Term, Options).
load_structure(File, Term, Options) :-
system:swi_open(File, read, In, [type(binary)]),
load_structure(stream(In), Term, [file(File)|Options]),
system:swi_close(In).
load_structure(File, Term, M:Options) :-
open(File, read, In, [type(binary)]),
load_structure(stream(In), Term, M:[file(File)|Options]),
close(In).
parse(Parser, Options, Document, In) :-
parse(Parser, M:Options, Document, In) :-
set_parser_options(Parser, Options, Options1),
parser_meta_options(Options1, M, Options2),
sgml_parse(Parser,
[ document(Document),
source(In)
| Options1
| Options2
]).
def_entities([], _, []).
def_entities([entity(Name, Value)|T], DTD, Opts) :- !,
def_entity(DTD, Name, Value),
def_entities(T, DTD, Opts).
def_entities([H|T0], DTD, [H|T]) :-
def_entities(T0, DTD, T).
parser_meta_options([], _, []).
parser_meta_options([call(When, Closure)|T0], M, [call(When, M:Closure)|T]) :- !,
parser_meta_options(T0, M, T).
parser_meta_options([H|T0], M, [H|T]) :-
parser_meta_options(T0, M, T).
def_entity(DTD, Name, Value) :-
open_dtd(DTD, [], Stream),
def_entities([], _, []).
def_entities([H|T], Parser, Opts) :-
def_entity(H, Parser), !,
def_entities(T, Parser, Opts).
def_entities([H|T0], Parser, [H|T]) :-
def_entities(T0, Parser, T).
def_entity(entity(Name, Value), Parser) :-
get_sgml_parser(Parser, dtd(DTD)),
xml_quote_attribute(Value, QValue),
system:swi_format(Stream, '<!ENTITY ~w "~w">~n', [Name, QValue]),
system:close(Stream).
setup_call_cleanup(open_dtd(DTD, [], Stream),
format(Stream, '<!ENTITY ~w "~w">~n',
[Name, QValue]),
close(Stream)).
def_entity(xmlns(URI), Parser) :-
set_sgml_parser(Parser, xmlns(URI)).
def_entity(xmlns(NS, URI), Parser) :-
set_sgml_parser(Parser, xmlns(NS, URI)).
/*******************************
@ -434,3 +446,5 @@ prolog:called_by(sgml_parse(_, Options), Called) :-
callable(G)
),
Called).
:- retract(system:swi_io).

View File

@ -1002,7 +1002,7 @@ feed(In, Len, Parser) :-
report_allowed(M) :-> % DEBUGGING
"Report allowed elements at point"::
get(M, allowed_elements, Allowed),
concat_atom(Allowed, ', ', Atom),
atomic_list_concat(Allowed, ', ', Atom),
send(M, report, status, 'Allowed: %s', Atom).
show_message(M, E) :-

View File

@ -238,7 +238,9 @@ emit_xml_encoding(Out, Options) :-
option(header(Hdr), Options, true),
Hdr == true, !,
stream_property(Out, encoding(Encoding)),
( Encoding == utf8
( ( Encoding == utf8
; Encoding == wchar_t
)
-> format(Out, '<?xml version="1.0" encoding="UTF-8"?>~n~n', [])
; Encoding == iso_latin_1
-> format(Out, '<?xml version="1.0" encoding="ISO-8859-1"?>~n~n', [])
@ -298,6 +300,9 @@ emit([], _, _) :- !.
emit([H|T], Out, State) :- !,
emit(H, Out, State),
emit(T, Out, State).
emit(CDATA, Out, State) :-
atom(CDATA), !,
sgml_write_content(Out, CDATA, State).
emit(Element, Out, State) :-
\+ \+ emit_element(Element, Out, State).
@ -571,6 +576,7 @@ generate_ns(_, NS) :-
rdf_db:ns/2.
default_ns('http://www.w3.org/2001/XMLSchema-instance', xsi).
default_ns('http://www.w3.org/1999/xhtml', xhtml).
default_ns(URI, NS) :-
rdf_db:ns(NS, URI).
@ -650,7 +656,8 @@ writeq([H|T], Out, Escape, EntityMap) :-
( memberchk(H, Escape)
-> write_entity(H, Out, EntityMap)
; H >= 256
-> ( stream_property(Out, encoding(utf8))
-> ( stream_property(Out, encoding(Enc)),
unicode_encoding(Enc)
-> put_code(Out, H)
; write_entity(H, Out, EntityMap)
)
@ -658,6 +665,10 @@ writeq([H|T], Out, Escape, EntityMap) :-
),
writeq(T, Out, Escape, EntityMap).
unicode_encoding(utf8).
unicode_encoding(wchar_t).
unicode_encoding(unicode_le).
unicode_encoding(unicode_be).
write_entity(Code, Out, EntityMap) :-
( get_assoc(Code, EntityMap, EntityName)

View File

@ -31,6 +31,7 @@
:- module(xsdp_type,
[ xsdp_type/1, % ?Type
xsdp_uri_type/2, % ?URI, ?Type
xsdp_numeric_uri/2, % ?URI, ?Primary
xsdp_subtype_of/2, % ?Type, ?Super
xsdp_convert/3 % +Type, +Content, -Value
@ -70,6 +71,14 @@ ns('http://www.w3.org/2001/XMLSchema#').
xsdp_type(Type) :-
subtype_of(Type, _).
%% xsdp_uri_type(?URI, ?Type)
%
% True if URI is the URI for the the XML-Schema primitive Type.
xsdp_uri_type(URI, Type) :-
xsd_local_id(URI, Type),
subtype_of(Type, _).
%% xsdp_subtype_of(?Type, ?Super)
%
% True if Type is a (transitive) subtype of Super.