docs and strings

This commit is contained in:
Vítor Santos Costa 2016-01-06 12:43:51 +00:00
parent e315217f0e
commit f6c5a2eea1
7 changed files with 2420 additions and 2372 deletions

View File

@ -17,10 +17,13 @@
xml_parse/2, xml_parse/2,
xml_parse/3, xml_parse/3,
xml_subterm/2, xml_subterm/2,
xml_pp/1 xml_pp/1,
load_xml/3,
load_xml/2
] ). ] ).
/* xml is intended to be a rather modular module: it should be easy to /* @section xml Prolog XML module
* xml is intended to be a rather modular module: it should be easy to
* build a program that can output XML, but not read it, or vice versa. * build a program that can output XML, but not read it, or vice versa.
* Similarly, you may be happy to dispense with diagnosis once you are * Similarly, you may be happy to dispense with diagnosis once you are
* sure that your code will only try to make valid calls to xml_parse/2. * sure that your code will only try to make valid calls to xml_parse/2.
@ -32,6 +35,7 @@
*/ */
:- use_module( library(lists), [append/3] ). :- use_module( library(lists), [append/3] ).
:- use_module( library(readutil) ).
:- ensure_loaded( xml/xml_driver ). :- ensure_loaded( xml/xml_driver ).
@ -47,7 +51,8 @@
%number_codes( Number, Codes ) :- %number_codes( Number, Codes ) :-
% number_chars( Number, Codes ). % number_chars( Number, Codes ).
/* xml_exception( +Message, +Document, +Culprit, +Path ) is a hook to /** @pred xml_exception( +Message, +Document, +Culprit, +Path )
* a hook to
* raise an exception to be raised in respect of a fault in the XML Term: * raise an exception to be raised in respect of a fault in the XML Term:
* Document. * Document.
* - Culprit is a sub-term of Document which cannot be serialized; * - Culprit is a sub-term of Document which cannot be serialized;
@ -62,6 +67,19 @@ xml_exception( Message, Document, Culprit, Path ) :-
[Message,Document,Culprit,Path] ) [Message,Document,Culprit,Path] )
). ).
load_xml(File, XML, []) :-
open( File, read, S),
read_stream_to_codes(S, Doc),
close(S),
xml_parse(Doc, XML).
load_xml(File, XML) :-
open( File, read, S),
read_stream_to_codes(S, Doc),
close(S),
xml_parse(Doc, XML).
/* member( ?Element, ?List ) holds when Element is a member of List. /* member( ?Element, ?List ) holds when Element is a member of List.
*/ */
member( H, [H|_] ). member( H, [H|_] ).

View File

@ -18,7 +18,8 @@
:- use_module(library(lists)). :- use_module(library(lists)).
/* xml_to_document( +Controls, +XML, ?Document ) translates the list of /** @pred xml_to_document( +Controls, +XML, ?Document )
* translates the list of
* character codes XML into the Prolog term Document. Controls is a list * character codes XML into the Prolog term Document. Controls is a list
* of terms controlling the treatment of layout characters and character * of terms controlling the treatment of layout characters and character
* entities. * entities.
@ -312,14 +313,15 @@ attributes( [Name=Value|Attributes], Seen, Namespaces ) -->
attributes( [], _Seen, _Namespaces ) --> "". attributes( [], _Seen, _Namespaces ) --> "".
xml_declaration_attributes( [] ) --> "". xml_declaration_attributes( [] ) --> "".
xml_declaration_attributes( [Name=Value|Attributes] ) --> xml_declaration_attributes( [Name=S|Attributes] ) -->
spaces, spaces,
nmtoken( Name ), nmtoken( Name ),
spaces, spaces,
"=", "=",
spaces, spaces,
xml_string( Value ), xml_string( Value ),
{xml_declaration_attribute_valid(Name, Value)}, {string_codes(S, Value), writeln(S),
xml_declaration_attribute_valid(Name, Value)},
xml_declaration_attributes( Attributes ), xml_declaration_attributes( Attributes ),
spaces. spaces.
@ -1119,3 +1121,4 @@ extender -->
range( Low, High ) --> range( Low, High ) -->
[Char], [Char],
{Char >= Low, Char =< High}. {Char >= Low, Char =< High}.

View File

@ -14,7 +14,9 @@
:- ensure_loaded( xml_generation ). :- ensure_loaded( xml_generation ).
/* xml_fault( +Term, +Indentation, ?SubTerm, ?Path, ?Message ) identifies SubTerm /* @pred xml_fault( +Term, +Indentation, ?SubTerm, ?Path, ?Message )
*
* identifies SubTerm
* as a sub-term of Term which cannot be serialized after Indentation. * as a sub-term of Term which cannot be serialized after Indentation.
* Message is an atom naming the type of error; Path is a string encoding a * Message is an atom naming the type of error; Path is a string encoding a
* list of SubTerm's ancestor elements in the form <tag>{(id)}* where <tag> is the * list of SubTerm's ancestor elements in the form <tag>{(id)}* where <tag> is the
@ -82,3 +84,4 @@ fault_id( Attributes ) -->
!, !,
"(", chars(Chars), ")". "(", chars(Chars), ")".
fault_id( _Attributes ) --> "". fault_id( _Attributes ) --> "".

View File

@ -11,11 +11,15 @@
* This program is offered free of charge, as unsupported source code. You may * This program is offered free of charge, as unsupported source code. You may
* use it, copy it, distribute it, modify it or sell it without restriction, * use it, copy it, distribute it, modify it or sell it without restriction,
* but entirely at your own risk. * but entirely at your own risk.
*/
/** @pred xml_parse( {+Controls}, +?Chars, ?+Document )
* *
* xml_parse( {+Controls}, +?Chars, ?+Document ) parses Chars to/from a data * parses Chars to/from a data
* structure of the form xml(<atts>, <content>). <atts> is a list of * structure of the form xml(<atts>, <content>). <atts> is a list of
* <atom>=<string> attributes from the (possibly implicit) XML signature of the * <atom>=<string> attributes from the (possibly implicit) XML signature of the
* document. <content> is a (possibly empty) list comprising occurrences of * ~~~ * document. <content> is a (possibly empty) list comprising occurrences of
* ~~~
* pcdata(<string>) : Text * pcdata(<string>) : Text
* comment(<string>) : An xml comment; * comment(<string>) : An xml comment;
* element(<tag>,<atts>,<content>) : <tag>..</tag> encloses <content> * element(<tag>,<atts>,<content>) : <tag>..</tag> encloses <content>
@ -75,7 +79,7 @@
* is not well-formed, diagnosis tries to identify the specific culprit term. * is not well-formed, diagnosis tries to identify the specific culprit term.
*/ */
:- module( xml, [xml_parse/2, :- module( xml_driver, [xml_parse/2,
xml_parse/3, xml_parse/3,
document_to_xml/3, document_to_xml/3,
xml_subterm/2 xml_subterm/2
@ -105,7 +109,8 @@ document_to_xml( Controls, Document, Chars ) :-
xml_exception( Message, Document, Culprit, Path ) xml_exception( Message, Document, Culprit, Path )
). ).
/** xml_subterm( +XMLTerm, ?Subterm ) /** @pred xml_subterm( +XMLTerm, ?Subterm )
*
* unifies Subterm with a sub-term of Term. * unifies Subterm with a sub-term of Term.
* Note that XMLTerm is a sub-term of itself. * Note that XMLTerm is a sub-term of itself.
*/ */

View File

@ -16,7 +16,9 @@
:- use_module(library(lists)). :- use_module(library(lists)).
/* document_generation( +Format, +Document ) is a DCG generating Document /* @pred document_generation( +Format, +Document )
*
* is a DCG generating Document
* as a list of character codes. Format is true|false defining whether layouts, * as a list of character codes. Format is true|false defining whether layouts,
* to provide indentation, should be added between the element content of * to provide indentation, should be added between the element content of
* the resultant "string". Note that formatting is disabled for elements that * the resultant "string". Note that formatting is disabled for elements that
@ -389,3 +391,4 @@ legal_xml_unicode( Code ) :-
legal_xml_unicode( Code ) :- legal_xml_unicode( Code ) :-
Code >= 65536, Code >= 65536,
Code =< 1114111. Code =< 1114111.

View File

@ -14,7 +14,9 @@
:- ensure_loaded( xml_utilities ). :- ensure_loaded( xml_utilities ).
/* xml_pp( +XMLDocument ) "pretty prints" XMLDocument on the current /** xml_pp( +XMLDocument )
*
* "pretty prints" XMLDocument on the current
* output stream. * output stream.
*/ */
xml_pp( xml(Attributes, Document) ) :- xml_pp( xml(Attributes, Document) ) :-
@ -196,3 +198,4 @@ pp_comma :-
pp_comma_sp :- pp_comma_sp :-
write( ', ' ). write( ', ' ).

View File

@ -19,11 +19,15 @@
% a linear list lookup is okay. They could be substituted by a logarithmic % a linear list lookup is okay. They could be substituted by a logarithmic
% data structure - in extremis. % data structure - in extremis.
/* empty_map( ?Map ) is true if Map is a null map. /** empty_map( ?Map )
*
* is true if Map is a null map.
*/ */
empty_map( [] ). empty_map( [] ).
/* map_member( +Key, +Map, ?Data ) is true if Map is a ordered map structure /* map_member( +Key, +Map, ?Data )
*
* is true if Map is a ordered map structure
* which records the pair Key-Data. Key must be ground. * which records the pair Key-Data. Key must be ground.
*/ */
map_member( Key0, [Key1-Data1|Rest], Data0 ) :- map_member( Key0, [Key1-Data1|Rest], Data0 ) :-
@ -33,7 +37,10 @@ map_member( Key0, [Key1-Data1|Rest], Data0 ) :-
map_member( Key0, Rest, Data0 ) map_member( Key0, Rest, Data0 )
). ).
/* map_store( +Map0, +Key, +Data, ?Map1 ) is true if Map0 is an ordered map /* map_store( +Map0, +Key, +Data, ?Map1 )
*
*
* is true if Map0 is an ordered map
* structure, Key must be ground, and Map1 is identical to Map0 except that * structure, Key must be ground, and Map1 is identical to Map0 except that
* the pair Key-Data is recorded by Map1. * the pair Key-Data is recorded by Map1.
*/ */
@ -48,7 +55,8 @@ map_store( [Key0-Data0|Map0], Key, Data, Map ) :-
map_store( Map0, Key, Data, Map1 ) map_store( Map0, Key, Data, Map1 )
). ).
/* context(?Element, ?PreserveSpace, ?CurrentNS, ?DefaultNS, ?Entities, ?Namespaces ) /** context(?Element, ?PreserveSpace, ?CurrentNS, ?DefaultNS, ?Entities, ?Namespaces )
*
* is an ADT hiding the "state" arguments for XML Acquisition * is an ADT hiding the "state" arguments for XML Acquisition
*/ */
initial_context( initial_context(
@ -158,7 +166,9 @@ allow_ampersand(
context(_Void,_Preserve,_Current,_Default,_Entities,_Names,_RPFA,true) context(_Void,_Preserve,_Current,_Default,_Entities,_Names,_RPFA,true)
). ).
/* pp_string( +String ) prints String onto the current output stream. /** pp_string( +String )
*
* prints String onto the current output stream.
* If String contains only 7-bit chars it is printed in shorthand quoted * If String contains only 7-bit chars it is printed in shorthand quoted
* format, otherwise it is written as a list. * format, otherwise it is written as a list.
* If your Prolog uses " to delimit a special string type, just use write/1. * If your Prolog uses " to delimit a special string type, just use write/1.
@ -485,7 +495,9 @@ extended_character_entities( [
"zwnj"-[8204] % zero width non-joiner, "zwnj"-[8204] % zero width non-joiner,
] ). ] ).
/* chars( ?Chars, ?Plus, ?Minus ) used as chars( ?Chars ) in a DCG to /* @pred chars( ?Chars, ?Plus, ?Minus )
*
* used as chars( ?Chars ) in a DCG to
* copy the list Chars inline. * copy the list Chars inline.
* *
* This is best expressed in terms of append/3 where append/3 is built-in. * This is best expressed in terms of append/3 where append/3 is built-in.
@ -500,3 +512,4 @@ extended_character_entities( [
chars( Chars, Plus, Minus ) :- chars( Chars, Plus, Minus ) :-
append( Chars, Minus, Plus ). append( Chars, Minus, Plus ).