File Coverage

blib/lib/XML/Generator.pm
Criterion Covered Total %
statement 437 460 95.0
branch 239 284 84.1
condition 79 99 79.8
subroutine 53 57 92.9
pod 6 7 85.7
total 814 907 89.7


line stmt bran cond sub pod time code
1             package XML::Generator;
2              
3 3     3   146049 use strict;
  3         32  
  3         85  
4 3     3   21 use warnings;
  3         6  
  3         84  
5 3     3   15 use Carp;
  3         6  
  3         212  
6 3     3   19 use vars qw/$VERSION $AUTOLOAD/;
  3         5  
  3         471  
7              
8             our $VERSION = '1.12';
9              
10             =head1 NAME
11              
12             XML::Generator - Perl extension for generating XML
13              
14             =head1 SYNOPSIS
15              
16             use XML::Generator ':pretty';
17              
18             print foo(bar({ baz => 3 }, bam()),
19             bar([ 'qux' => 'http://qux.com/' ],
20             "Hey there, world"));
21              
22             # OR
23              
24             require XML::Generator;
25              
26             my $X = XML::Generator->new(':pretty');
27              
28             print $X->foo($X->bar({ baz => 3 }, $X->bam()),
29             $X->bar([ 'qux' => 'http://qux.com/' ],
30             "Hey there, world"));
31              
32             Either of the above yield:
33              
34            
35            
36            
37            
38             Hey there, world
39            
40              
41             =head1 DESCRIPTION
42              
43             In general, once you have an XML::Generator object, you then simply call
44             methods on that object named for each XML tag you wish to generate.
45              
46             XML::Generator can also arrange for undefined subroutines in the caller's
47             package to generate the corresponding XML, by exporting an C
48             subroutine to your package. Just supply an ':import' argument to
49             your C call. If you already have an C
50             defined then XML::Generator can be configured to cooperate with it.
51             See L<"STACKABLE AUTOLOADs">.
52              
53             Say you want to generate this XML:
54              
55            
56             Bob
57             34
58             Accountant
59            
60              
61             Here's a snippet of code that does the job, complete with pretty printing:
62              
63             use XML::Generator;
64             my $gen = XML::Generator->new(':pretty');
65             print $gen->person(
66             $gen->name("Bob"),
67             $gen->age(34),
68             $gen->job("Accountant")
69             );
70              
71             The only problem with this is if you want to use a tag name that
72             Perl's lexer won't understand as a method name, such as "shoe-size".
73             Fortunately, since you can store the name of a method in a variable,
74             there's a simple work-around:
75              
76             my $shoe_size = "shoe-size";
77             $xml = $gen->$shoe_size("12 1/2");
78              
79             Which correctly generates:
80              
81             12 1/2
82              
83             You can use a hash ref as the first parameter if the tag should include
84             atributes. Normally this means that the order of the attributes will be
85             unpredictable, but if you have the L module, you can use it
86             to get the order you want, like this:
87              
88             use Tie::IxHash;
89             tie my %attr, 'Tie::IxHash';
90              
91             %attr = (name => 'Bob',
92             age => 34,
93             job => 'Accountant',
94             'shoe-size' => '12 1/2');
95              
96             print $gen->person(\%attr);
97              
98             This produces
99              
100            
101              
102             An array ref can also be supplied as the first argument to indicate
103             a namespace for the element and the attributes.
104              
105             If there is one element in the array, it is considered the URI of
106             the default namespace, and the tag will have an xmlns="URI" attribute
107             added automatically. If there are two elements, the first should be
108             the tag prefix to use for the namespace and the second element should
109             be the URI. In this case, the prefix will be used for the tag and an
110             xmlns:PREFIX attribute will be automatically added. Prior to version
111             0.99, this prefix was also automatically added to each attribute name.
112             Now, the default behavior is to leave the attributes alone (although you
113             may always explicitly add a prefix to an attribute name). If the prior
114             behavior is desired, use the constructor option C.
115              
116             If you specify more than two elements, then each pair should correspond
117             to a tag prefix and the corresponding URL. An xmlns:PREFIX attribute
118             will be added for each pair, and the prefix from the first such pair
119             will be used as the tag's namespace. If you wish to specify a default
120             namespace, use '#default' for the prefix. If the default namespace is
121             first, then the tag will use the default namespace itself.
122              
123             If you want to specify a namespace as well as attributes, you can make
124             the second argument a hash ref. If you do it the other way around,
125             the array ref will simply get stringified and included as part of the
126             content of the tag.
127              
128             Here's an example to show how the attribute and namespace parameters work:
129              
130             $xml = $gen->account(
131             $gen->open(['transaction'], 2000),
132             $gen->deposit(['transaction'], { date => '1999.04.03'}, 1500)
133             );
134              
135             This generates:
136              
137            
138             2000
139             1500
140            
141              
142             Because default namespaces inherit, XML::Generator takes care to output
143             the xmlns="URI" attribute as few times as strictly necessary. For example,
144              
145             $xml = $gen->account(
146             $gen->open(['transaction'], 2000),
147             $gen->deposit(['transaction'], { date => '1999.04.03'},
148             $gen->amount(['transaction'], 1500)
149             )
150             );
151              
152             This generates:
153              
154            
155             2000
156            
157             1500
158            
159            
160              
161             Notice how C was left out of the C<> tag.
162              
163             Here is an example that uses the two-argument form of the namespace:
164              
165             $xml = $gen->widget(['wru' => 'http://www.widgets-r-us.com/xml/'],
166             {'id' => 123}, $gen->contents());
167              
168            
169            
170            
171              
172             Here is an example that uses multiple namespaces. It generates the
173             first example from the RDF primer (L).
174              
175             my $contactNS = [contact => "http://www.w3.org/2000/10/swap/pim/contact#"];
176             $xml = $gen->xml(
177             $gen->RDF([ rdf => "http://www.w3.org/1999/02/22-rdf-syntax-ns#",
178             @$contactNS ],
179             $gen->Person($contactNS, { 'rdf:about' => "http://www.w3.org/People/EM/contact#me" },
180             $gen->fullName($contactNS, 'Eric Miller'),
181             $gen->mailbox($contactNS, {'rdf:resource' => "mailto:em@w3.org"}),
182             $gen->personalTitle($contactNS, 'Dr.'))));
183              
184            
185            
186             xmlns:contact="http://www.w3.org/2000/10/swap/pim/contact#">
187            
188             Eric Miller
189            
190             Dr.
191            
192            
193              
194             =head1 CONSTRUCTOR
195              
196             XML::Generator-Enew(':option', ...);
197              
198             XML::Generator-Enew(option => 'value', ...);
199              
200             (Both styles may be combined)
201              
202             The following options are available:
203              
204             =head2 :std, :standard
205              
206             Equivalent to
207              
208             escape => 'always',
209             conformance => 'strict',
210              
211             =head2 :strict
212              
213             Equivalent to
214              
215             conformance => 'strict',
216              
217             =head2 :pretty[=N]
218              
219             Equivalent to
220              
221             escape => 'always',
222             conformance => 'strict',
223             pretty => N # N defaults to 2
224              
225             =head2 namespace
226              
227             This value of this option must be an array reference containing one or
228             two values. If the array contains one value, it should be a URI and will
229             be the value of an 'xmlns' attribute in the top-level tag. If there are
230             two or more elements, the first of each pair should be the namespace
231             tag prefix and the second the URI of the namespace. This will enable
232             behavior similar to the namespace behavior in previous versions; the tag
233             prefix will be applied to each tag. In addition, an xmlns:NAME="URI"
234             attribute will be added to the top-level tag. Prior to version 0.99,
235             the tag prefix was also automatically added to each attribute name,
236             unless overridden with an explicit prefix. Now, the attribute names are
237             left alone, but if the prior behavior is desired, use the constructor
238             option C.
239              
240             The value of this option is used as the global default namespace.
241             For example,
242              
243             my $html = XML::Generator->new(
244             pretty => 2,
245             namespace => [HTML => "http://www.w3.org/TR/REC-html40"]);
246             print $html->html(
247             $html->body(
248             $html->font({ face => 'Arial' },
249             "Hello, there")));
250              
251             would yield
252              
253            
254            
255             Hello, there
256            
257            
258              
259             Here is the same example except without all the prefixes:
260              
261             my $html = XML::Generator->new(
262             pretty => 2,
263             namespace => ["http://www.w3.org/TR/REC-html40"]);
264             print $html->html(
265             $html->body(
266             $html->font({ 'face' => 'Arial' },
267             "Hello, there")));
268              
269             would yield
270              
271            
272            
273             Hello, there
274            
275            
276              
277             =head2 qualifiedAttributes, qualified_attributes
278              
279             Set this to a true value to emulate the attribute prefixing behavior of
280             XML::Generator prior to version 0.99. Here is an example:
281              
282             my $foo = XML::Generator->new(
283             namespace => [foo => "http://foo.com/"],
284             qualifiedAttributes => 1);
285             print $foo->bar({baz => 3});
286              
287             yields
288              
289            
290              
291             =head2 escape
292              
293             The contents and the values of each attribute have any illegal XML
294             characters escaped if this option is supplied. If the value is 'always',
295             then &, < and > (and " within attribute values) will be converted into
296             the corresponding XML entity, although & will not be converted if it looks
297             like it could be part of a valid entity (but see below). If the value is
298             'unescaped', then the escaping will be turned off character-by-character
299             if the character in question is preceded by a backslash, or for the
300             entire string if it is supplied as a scalar reference. So, for example,
301              
302             use XML::Generator escape => 'always';
303              
304             one('<'); # <
305             two('\&'); # \&
306             three(\''); # (scalar refs always allowed)
307             four('<'); # < (looks like an entity)
308             five('"'); # " (looks like an entity)
309              
310             but
311              
312             use XML::Generator escape => 'unescaped';
313              
314             one('<'); # <
315             two('\&'); # &
316             three(\'');# (scalar refs always allowed)
317             four('<'); # &lt; (no special case for entities)
318              
319             By default, high-bit data will be passed through unmodified, so that
320             UTF-8 data can be generated with pre-Unicode perls. If you know that
321             your data is ASCII, use the value 'high-bit' for the escape option
322             and bytes with the high bit set will be turned into numeric entities.
323             You can combine this functionality with the other escape options by
324             comma-separating the values:
325              
326             my $a = XML::Generator->new(escape => 'always,high-bit');
327             print $a->foo("<\242>");
328              
329             yields
330              
331             <¢>
332              
333             Because XML::Generator always uses double quotes ("") around attribute
334             values, it does not escape single quotes. If you want single quotes
335             inside attribute values to be escaped, use the value 'apos' along with
336             'always' or 'unescaped' for the escape option. For example:
337              
338             my $gen = XML::Generator->new(escape => 'always,apos');
339             print $gen->foo({'bar' => "It's all good"});
340              
341            
342              
343             If you actually want & to be converted to & even if it looks like it
344             could be part of a valid entity, use the value 'even-entities' along with
345             'always'. Supplying 'even-entities' to the 'unescaped' option is meaningless
346             as entities are already escaped with that option.
347              
348             =head2 pretty
349              
350             To have nice pretty printing of the output XML (great for config files
351             that you might also want to edit by hand), supply an integer for the
352             number of spaces per level of indenting, eg.
353              
354             my $gen = XML::Generator->new(pretty => 2);
355             print $gen->foo($gen->bar('baz'),
356             $gen->qux({ tricky => 'no'}, 'quux'));
357              
358             would yield
359              
360            
361             baz
362             quux
363            
364              
365             You may also supply a non-numeric string as the argument to 'pretty', in
366             which case the indents will consist of repetitions of that string. So if
367             you want tabbed indents, you would use:
368              
369             my $gen = XML::Generator->new(pretty => "\t");
370              
371             Pretty printing does not apply to CDATA sections or Processing Instructions.
372              
373             =head2 conformance
374              
375             If the value of this option is 'strict', a number of syntactic
376             checks are performed to ensure that generated XML conforms to the
377             formal XML specification. In addition, since entity names beginning
378             with 'xml' are reserved by the W3C, inclusion of this option enables
379             several special tag names: xmlpi, xmlcmnt, xmldecl, xmldtd, xmlcdata,
380             and xml to allow generation of processing instructions, comments, XML
381             declarations, DTD's, character data sections and "final" XML documents,
382             respectively.
383              
384             Invalid characters (http://www.w3.org/TR/xml11/#charsets) will be filtered
385             out. To disable this behavior, supply the 'filter_invalid_chars' option with
386             the value 0.
387              
388             See L<"XML CONFORMANCE"> and L<"SPECIAL TAGS"> for more information.
389              
390             =head2 filterInvalidChars, filter_invalid_chars
391              
392             Set this to a 1 to enable filtering of invalid characters, or to 0 to disable
393             the filtering. See http://www.w3.org/TR/xml11/#charsets for the set of valid
394             characters.
395              
396             =head2 allowedXMLTags, allowed_xml_tags
397              
398             If you have specified 'conformance' => 'strict' but need to use tags
399             that start with 'xml', you can supply a reference to an array containing
400             those tags and they will be accepted without error. It is not an error
401             to supply this option if 'conformance' => 'strict' is not supplied,
402             but it will have no effect.
403              
404             =head2 empty
405              
406             There are 5 possible values for this option:
407              
408             self - create empty tags as (default)
409             compact - create empty tags as
410             close - close empty tags as
411             ignore - don't do anything (non-compliant!)
412             args - use count of arguments to decide between and
413              
414             Many web browsers like the 'self' form, but any one of the forms besides
415             'ignore' is acceptable under the XML standard.
416              
417             'ignore' is intended for subclasses that deal with HTML and other
418             SGML subsets which allow atomic tags. It is an error to specify both
419             'conformance' => 'strict' and 'empty' => 'ignore'.
420              
421             'args' will produce if there are no arguments at all, or if there
422             is just a single undef argument, and otherwise.
423              
424             =head2 version
425              
426             Sets the default XML version for use in XML declarations.
427             See L<"xmldecl"> below.
428              
429             =head2 encoding
430              
431             Sets the default encoding for use in XML declarations.
432              
433             =head2 dtd
434              
435             Specify the dtd. The value should be an array reference with three
436             values; the type, the name and the uri.
437              
438             =head2 xml
439              
440             This is an hash ref value that should contain the version, encoding and dtd
441             values (same as above). This is used in case C is set to C,
442             but you still want to use the xml declaration or prolog.
443              
444             =head1 IMPORT ARGUMENTS
445              
446             use XML::Generator ':option';
447              
448             use XML::Generator option => 'value';
449              
450             (Both styles may be combined)
451              
452             =head2 :import
453              
454             Cause C to export an C to your package that
455             makes undefined subroutines generate XML tags corresponding to their name.
456             Note that if you already have an C defined, it will be overwritten.
457              
458             =head2 :stacked
459              
460             Implies :import, but if there is already an C defined, the
461             overriding C will still give it a chance to run. See L<"STACKABLE
462             AUTOLOADs">.
463              
464             =head2 ANYTHING ELSE
465              
466             If you supply any other options, :import is implied and the XML::Generator
467             object that is created to generate tags will be constructed with those options.
468              
469             =cut
470              
471             package XML::Generator;
472              
473 3     3   20 use strict;
  3         6  
  3         386  
474             require Carp;
475              
476             # If no value is provided for these options, they will be set to ''
477              
478             my @optionsToInit = qw(
479             allowed_xml_tags
480             conformance
481             dtd
482             escape
483             namespace
484             pretty
485             version
486             empty
487             qualified_attributes
488             filter_invalid_chars
489             );
490              
491             my %tag_factory;
492              
493             sub import {
494 15     15   2045 my $type = shift;
495              
496             # check for attempt to use tag 'import'
497 15 100 66     77 if (ref $type && defined $tag_factory{$type}) {
498 1         3 unshift @_, $type, 'import';
499 1         2 goto &{ $tag_factory{$type} };
  1         4  
500             }
501              
502 14         24 my $pkg = caller;
503              
504 3     3   21 no strict 'refs'; # Let's get serious
  3         5  
  3         115  
505              
506             # should we import an AUTOLOAD?
507 3     3   16 no warnings 'once';
  3         10  
  3         355  
508              
509 14 100       48 if (@_) {
510 10         50 my $STACKED;
511              
512             # are we supposed to call their AUTOLOAD first?
513 10 100       42 if (grep /^:stacked$/, @_) {
514 2         4 $STACKED = \&{"${pkg}::AUTOLOAD"};
  2         8  
515             }
516              
517 10         25 my $this = $type->new(@_);
518              
519 3     3   31 no warnings 'redefine'; # No, I mean SERIOUS
  3         6  
  3         7166  
520              
521 10         60 *{"${pkg}::AUTOLOAD"} =
522             sub {
523 20 100   20   290 if ($STACKED) {
524 7         11 ${"${pkg}::AUTOLOAD"} = our $AUTOLOAD;
  7         18  
525 7         17 my @ret = $STACKED->(@_);
526 7 100       70 return wantarray ? @ret : $ret[0] if @ret;
    100          
527             }
528              
529             # The tag is whatever our sub name is.
530 17         101 my($tag) = our $AUTOLOAD =~ /.*::(.*)/;
531              
532             # Special-case for xml... tags
533 17 50 33     50 if ($tag =~ /^xml/ && $this->{'conformance'} eq 'strict') {
534 0 0       0 if (my $func = $this->can($tag)) {
535 0         0 unshift @_, $this;
536 0         0 goto &$func;
537             }
538             }
539              
540 17         42 unshift @_, $this, $tag;
541              
542 17         27 goto &{ $tag_factory{$this} };
  17         103  
543 10         53 };
544              
545             # convenience feature for stacked autoloads; give them
546             # an import() that aliases AUTOLOAD.
547 10 100 66     1480 if ($STACKED && ! defined *{"${pkg}::import"}{CODE}) {
  2         12  
548 2         6 *{"${pkg}::import"} =
549             sub {
550 1     1   56 my $p = caller;
551 1         3 *{"${p}::AUTOLOAD"} = \&{"${pkg}::AUTOLOAD"};
  1         6  
  1         5  
552 2         7 };
553             }
554             }
555              
556 14         6927 return;
557             }
558              
559             # The constructor method
560              
561             sub new {
562 58     58 0 2920 my $class = shift;
563              
564             # If we already have a ref in $class, this means that the
565             # person wants to generate a tag!
566 58 100       137 return $class->XML::Generator::util::tag('new', @_) if ref $class;
567              
568             my %options =
569             map {
570 57         116 /^:(std|standard) $/x ? ( escape => 'always',
571             conformance => 'strict' )
572             : /^:strict $/x ? ( conformance => 'strict' )
573             : /^:pretty(?:=(.+))?$/x ? ( escape => 'always',
574             conformance => 'strict',
575             pretty => ( defined $1 ? $1 : 2 ) )
576             : /^:(import |
577 129 50       806 stacked )$/x ? ( do { Carp::carp("Useless use of $_")
  5 100       57  
    50          
    100          
    50          
    100          
    100          
    100          
    100          
578             unless (caller(1))[3] =~ /::import/;
579 5         134 () } )
580             : /^allowedXMLTags$/ ? 'allowed_xml_tags'
581             : /^qualifiedAttributes$/ ? 'qualified_attributes'
582             : /^filterInvalidChars$/ ? 'filter_invalid_chars'
583             : $_
584             } @_;
585              
586             # We used to only accept certain options, but unfortunately this
587             # means that subclasses can't extend the list. As such, we now
588             # just make sure our default options are defined.
589 57         143 for (@optionsToInit) {
590 570 100       1021 if (not defined $options{$_}) {
591 490         904 $options{$_} = '';
592             }
593             }
594              
595 57 100       107 if ($options{'dtd'}) {
596 1         9 $options{'dtdtree'} = $class->XML::Generator::util::parse_dtd($options{'dtd'});
597             }
598              
599 57 100 100     200 if ($options{'conformance'} eq 'strict' &&
600             $options{'empty'} eq 'ignore') {
601 1         106 Carp::croak "option 'empty' => 'ignore' not allowed while 'conformance' => 'strict'";
602             }
603              
604 56 100       105 if ($options{'escape'}) {
605 18         32 my $e = $options{'escape'};
606 18         35 $options{'escape'} = 0;
607 18         98 while ($e =~ /([-\w]+),?/g) {
608 22 100       106 if ($1 eq 'always') {
    100          
    100          
    100          
    50          
609 14         64 $options{'escape'} |= XML::Generator::util::ESCAPE_ALWAYS()
610             | XML::Generator::util::ESCAPE_GT();
611             } elsif ($1 eq 'high-bit') {
612 4         20 $options{'escape'} |= XML::Generator::util::ESCAPE_HIGH_BIT();
613             } elsif ($1 eq 'apos') {
614 1         4 $options{'escape'} |= XML::Generator::util::ESCAPE_APOS();
615             } elsif ($1 eq 'even-entities') {
616 1         4 $options{'escape'} |= XML::Generator::util::ESCAPE_EVEN_ENTITIES();
617             } elsif ($1) {
618 2 50       6 if ($1 ne 'unescaped') {
619 0         0 Carp::carp "option 'escape' => '$1' deprecated; use 'escape' => 'unescaped'";
620             }
621 2         14 $options{'escape'} |= XML::Generator::util::ESCAPE_TRUE()
622             | XML::Generator::util::ESCAPE_GT();
623             }
624             }
625             } else {
626 38         65 $options{'escape'} = 0;
627             }
628              
629 56 100 100     134 if ($options{'xml'} && ref $options{'xml'} ne 'HASH') {
630 1         139 Carp::croak("XML arguments must be a hash");
631             }
632              
633 55 100       145 if (ref $options{'namespace'} eq 'ARRAY') {
    50          
634 8 50 66     14 if (@{ $options{'namespace'} } > 2 && (@{ $options{'namespace'} } % 2) != 0) {
  8         22  
  1         9  
635 0         0 Carp::croak "odd number of arguments for namespace";
636             }
637             } elsif ($options{'namespace'}) {
638 0         0 Carp::croak "namespace must be an array reference";
639             }
640              
641 55 100 100     157 if ($options{'conformance'} eq 'strict' &&
642             $options{'filter_invalid_chars'} eq '') {
643 23         41 $options{'filter_invalid_chars'} = 1;
644             }
645              
646 55         113 my $this = bless \%options, $class;
647 55         125 $tag_factory{$this} = XML::Generator::util::c_tag($this);
648 55         226 return $this;
649             }
650              
651             # We use AUTOLOAD as a front-end to TAG so that we can
652             # create tags by name at will.
653              
654             sub AUTOLOAD {
655 131     131   2798 my $this = shift;
656              
657             # The tag is whatever our sub name is, or 'AUTOLOAD'
658 131 50       791 my ($tag) = defined our $AUTOLOAD ? $AUTOLOAD =~ /.*::(.*)/ : 'AUTOLOAD';
659              
660 131         241 undef $AUTOLOAD; # this ensures that future attempts to use tag 'AUTOLOAD' work.
661              
662 131         309 unshift @_, $this, $tag;
663              
664 131         171 goto &{ $tag_factory{$this} };
  131         462  
665             }
666              
667             # I wish there were a way to allow people to use tag 'DESTROY!'
668             # hmm, maybe xmlDESTROY?
669 39     39   1269 sub DESTROY { delete $tag_factory{$_[0]} }
670              
671             =head1 XML CONFORMANCE
672              
673             When the 'conformance' => 'strict' option is supplied, a number of
674             syntactic checks are enabled. All entity and attribute names are
675             checked to conform to the XML specification, which states that they must
676             begin with either an alphabetic character or an underscore and may then
677             consist of any number of alphanumerics, underscores, periods or hyphens.
678             Alphabetic and alphanumeric are interpreted according to the current
679             locale if 'use locale' is in effect and according to the Unicode standard
680             for Perl versions >= 5.6. Furthermore, entity or attribute names are not
681             allowed to begin with 'xml' (in any case), although a number of special
682             tags beginning with 'xml' are allowed (see L<"SPECIAL TAGS">). Note
683             that you can also supply an explicit list of allowed tags with the
684             'allowed_xml_tags' option.
685              
686             Also, the filter_invalid_chars option is automatically set to 1 unless it
687             is explicitly set to 0.
688              
689             =head1 SPECIAL TAGS
690              
691             The following special tags are available when running under strict
692             conformance (otherwise they don't act special):
693              
694             =head2 xmlpi
695              
696             Processing instruction; first argument is target, remaining arguments
697             are attribute, value pairs. Attribute names are syntax checked, values
698             are escaped.
699              
700             =cut
701              
702             # We handle a few special tags, but only if the conformance
703             # is 'strict'. If not, we just fall back to XML::Generator::util::tag.
704              
705             sub xmlpi {
706 5     5 1 148 my $this = shift;
707              
708             return $this->XML::Generator::util::tag('xmlpi', @_)
709 5 50       15 unless $this->{conformance} eq 'strict';
710              
711 5         8 my $xml;
712 5         17 my $tgt = shift;
713              
714 5         16 $this->XML::Generator::util::ck_syntax($tgt);
715              
716 5         11 $xml = "
717 5 100       11 if (@_) {
718 1         4 my %atts = @_;
719 1         19 while (my($k, $v) = each %atts) {
720 1         6 $this->XML::Generator::util::ck_syntax($k);
721             XML::Generator::util::escape($v,
722             XML::Generator::util::ESCAPE_ATTR() |
723 1         9 $this->{'escape'});
724 1         4 XML::Generator::util::filter($v);
725 1         9 $xml .= qq{ $k="$v"};
726             }
727             }
728 5         9 $xml .= "?>";
729              
730 5         17 return XML::Generator::pi->new([$xml]);
731             }
732              
733             =head2 xmlcmnt
734              
735             Comment. Arguments are concatenated and placed inside
736             comment delimiters. Any occurences of '--' in the concatenated arguments
737             are converted to '--'
738              
739             =cut
740              
741             sub xmlcmnt {
742 5     5 1 192 my $this = shift;
743              
744             return $this->XML::Generator::util::tag('xmlcmnt', @_)
745 5 50       20 unless $this->{conformance} eq 'strict';
746              
747 5         13 my $xml = join '', @_;
748              
749             # double dashes are illegal; change them to '--'
750 5         12 $xml =~ s/--/--/g;
751 5         14 XML::Generator::util::filter($xml);
752 5         11 $xml = "";
753              
754 5         22 return XML::Generator::comment->new([$xml]);
755             }
756              
757             =head2 xmldecl (@args)
758              
759             Declaration. This can be used to specify the version, encoding, and
760             other XML-related declarations (i.e., anything inside the tag).
761             @args can be used to control what is output, as keyword-value pairs.
762              
763             By default, the version is set to the value specified in the constructor,
764             or to 1.0 if it was not specified. This can be overridden by providing a
765             'version' key in @args. If you do not want the version at all, explicitly
766             provide undef as the value in @args.
767              
768             By default, the encoding is set to the value specified in the constructor;
769             if no value was specified, the encoding will be left out altogether.
770             Provide an 'encoding' key in @args to override this.
771              
772             If a dtd was set in the constructor, the standalone attribute of the
773             declaration will be set to 'no' and the doctype declaration will be
774             appended to the XML declartion, otherwise the standalone attribute will
775             be set to 'yes'. This can be overridden by providing a 'standalone'
776             key in @args. If you do not want the standalone attribute to show up,
777             explicitly provide undef as the value.
778              
779             =cut
780              
781             sub _allow_xml_cmd {
782 19     19   23 my $this = shift;
783 19 100       53 return 1 if $this->{conformance} eq 'strict';
784 5 100       17 return 1 if defined $this->{xml};
785 1         5 return 0;
786             }
787              
788              
789             sub xmldecl {
790 6     6 1 235 my $this = shift;
791              
792 6 50       19 return $this->XML::Generator::util::tag('xmldecl', @_) unless $this->{conformance} eq 'strict';
793 6         17 return $this->_xmldecl(@_);
794             }
795              
796             sub _xmldecl {
797 11     11   16 my $this = shift;
798 11         24 my @args = @_;
799              
800 11 50       21 return unless $this->_allow_xml_cmd;
801              
802 11   100     52 my $version = $this->{xml}{version} // $this->{'version'} || '1.0';
803              
804             # there's no explicit support for encodings yet, but at the
805             # least we can know to put it in the declaration
806 11   100     29 my $encoding = $this->{xml}{encoding} // $this->{'encoding'};
807              
808             # similarly, although we don't do anything with DTDs yet, we
809             # recognize a 'dtd' => [ ... ] option to the constructor, and
810             # use it to create a and to indicate that this
811             # document can't stand alone.
812 11   100     38 my $doctype = $this->xmldtd($this->{xml}{dtd} // $this->{dtd});
813 11         16 my $standalone;
814              
815 11         28 for (my $i = 0; $i < $#args; $i += 2) {
816 9 100       23 if ($args[$i] eq 'version' ) {
    100          
    50          
817 3         9 $version = $args[$i + 1];
818             } elsif ($args[$i] eq 'encoding' ) {
819 3         7 $encoding = $args[$i + 1];
820             } elsif ($args[$i] eq 'standalone') {
821 3         7 $standalone = $args[$i + 1];
822             } else {
823 0         0 Carp::croak("Unrecognized argument '$args[$i]'");
824             }
825             }
826              
827 11 100       21 $standalone = "no" if $doctype;;
828 11 100       30 $version = qq{ version="$version"} if defined $version;
829 11 100       39 $encoding = qq{ encoding="$encoding"} if defined $encoding;
830 11 100       20 $standalone = qq{ standalone="$standalone"} if defined $standalone;
831              
832 11   100     32 $encoding ||= '';
833 11   100     19 $version ||= '';
834 11   100     33 $standalone ||= '';
835              
836 11         34 my @xml = ("");
837 11 100       30 push(@xml, $doctype) if $doctype;
838 11         61 return join("\n", @xml, "");
839             }
840              
841             =head2 xmldtd
842              
843             DTD tag creation. The format of this method is different from
844             others. Since DTD's are global and cannot contain namespace information,
845             the first argument should be a reference to an array; the elements are
846             concatenated together to form the DTD:
847              
848             print $xml->xmldtd([ 'html', 'PUBLIC', $xhtml_w3c, $xhtml_dtd ])
849              
850             This would produce the following declaration:
851              
852            
853             "DTD/xhtml1-transitional.dtd">
854              
855             Assuming that $xhtml_w3c and $xhtml_dtd had the correct values.
856              
857             Note that you can also specify a DTD on creation using the new() method's
858             dtd option.
859              
860             =cut
861              
862             sub xmldtd {
863 11     11 1 15 my $this = shift;
864 11   100     24 my $dtd = shift || return undef;
865              
866             # return the appropriate thingy
867 2 50       9 $dtd ? return(qq{})
  2         10  
868             : return('');
869             }
870              
871             =head2 xmlcdata
872              
873             Character data section; arguments are concatenated and placed inside
874             character data section delimiters. Any occurences of
875             ']]>' in the concatenated arguments are converted to ']]>'.
876              
877             =cut
878              
879             sub xmlcdata {
880 3     3 1 207 my $this = shift;
881              
882             $this->XML::Generator::util::tag('xmlcdata', @_)
883 3 50       20 unless $this->{conformance} eq 'strict';
884              
885 3         11 my $xml = join '', @_;
886              
887             # ]]> is not allowed; change it to ]]>
888 3         9 $xml =~ s/]]>/]]>/g;
889 3         8 XML::Generator::util::filter($xml);
890 3         8 $xml = "";
891              
892 3         12 return XML::Generator::cdata->new([$xml]);
893             }
894              
895             =head2 xml
896              
897             "Final" XML document. Must be called with one and exactly one
898             XML::Generator-produced XML document. Any combination of
899             XML::Generator-produced XML comments or processing instructions may
900             also be supplied as arguments. Prepends an XML declaration, and
901             re-blesses the argument into a "final" class that can't be embedded.
902              
903             =cut
904              
905             sub xml {
906 8     8 1 183 my $this = shift;
907              
908 8 100       23 return $this->XML::Generator::util::tag('xml', @_)
909             unless $this->_allow_xml_cmd;
910              
911 7 100       18 unless (@_) {
912 1         92 Carp::croak "usage: object->xml( (COMMENT | PI)* XML (COMMENT | PI)* )";
913             }
914              
915 6         11 my $got_root = 0;
916 6         13 foreach my $arg (@_) {
917 8 100 100     43 next if UNIVERSAL::isa($arg, 'XML::Generator::comment') ||
918             UNIVERSAL::isa($arg, 'XML::Generator::pi');
919 6 100       16 if (UNIVERSAL::isa($arg, 'XML::Generator::overload')) {
920 5 50       10 if ($got_root) {
921 0         0 Carp::croak "arguments to xml() can contain only one XML document";
922             }
923 5         7 $got_root = 1;
924             } else {
925 1         72 Carp::croak "arguments to xml() must be comments, processing instructions or XML documents";
926             }
927             }
928              
929 5         12 return XML::Generator::final->new([$this->_xmldecl(), @_]);
930             }
931              
932             =head1 CREATING A SUBCLASS
933              
934             For a simpler way to implement subclass-like behavior, see L<"STACKABLE
935             AUTOLOADs">.
936              
937             At times, you may find it desireable to subclass XML::Generator. For
938             example, you might want to provide a more application-specific interface
939             to the XML generation routines provided. Perhaps you have a custom
940             database application and would really like to say:
941              
942             my $dbxml = new XML::Generator::MyDatabaseApp;
943             print $dbxml->xml($dbxml->custom_tag_handler(@data));
944              
945             Here, custom_tag_handler() may be a method that builds a recursive XML
946             structure based on the contents of @data. In fact, it may even be named
947             for a tag you want generated, such as authors(), whose behavior changes
948             based on the contents (perhaps creating recursive definitions in the
949             case of multiple elements).
950              
951             Creating a subclass of XML::Generator is actually relatively
952             straightforward, there are just three things you have to remember:
953              
954             1. All of the useful utilities are in XML::Generator::util.
955              
956             2. To construct a tag you simply have to call SUPER::tagname,
957             where "tagname" is the name of your tag.
958              
959             3. You must fully-qualify the methods in XML::Generator::util.
960              
961             So, let's assume that we want to provide a custom HTML table() method:
962              
963             package XML::Generator::CustomHTML;
964             use base 'XML::Generator';
965              
966             sub table {
967             my $self = shift;
968              
969             # parse our args to get namespace and attribute info
970             my($namespace, $attr, @content) =
971             $self->XML::Generator::util::parse_args(@_)
972              
973             # check for strict conformance
974             if ( $self->XML::Generator::util::config('conformance') eq 'strict' ) {
975             # ... special checks ...
976             }
977              
978             # ... special formatting magic happens ...
979              
980             # construct our custom tags
981             return $self->SUPER::table($attr, $self->tr($self->td(@content)));
982             }
983              
984             That's pretty much all there is to it. We have to explicitly call
985             SUPER::table() since we're inside the class's table() method. The others
986             can simply be called directly, assuming that we don't have a tr() in the
987             current package.
988              
989             If you want to explicitly create a specific tag by name, or just want a
990             faster approach than AUTOLOAD provides, you can use the tag() method
991             directly. So, we could replace that last line above with:
992              
993             # construct our custom tags
994             return $self->XML::Generator::util::tag('table', $attr, ...);
995              
996             Here, we must explicitly call tag() with the tag name itself as its first
997             argument so it knows what to generate. These are the methods that you might
998             find useful:
999              
1000             =over 4
1001              
1002             =item XML::Generator::util::parse_args()
1003              
1004             This parses the argument list and returns the namespace (arrayref), attributes
1005             (hashref), and remaining content (array), in that order.
1006              
1007             =item XML::Generator::util::tag()
1008              
1009             This does the work of generating the appropriate tag. The first argument must
1010             be the name of the tag to generate.
1011              
1012             =item XML::Generator::util::config()
1013              
1014             This retrieves options as set via the new() method.
1015              
1016             =item XML::Generator::util::escape()
1017              
1018             This escapes any illegal XML characters.
1019              
1020             =back
1021              
1022             Remember that all of these methods must be fully-qualified with the
1023             XML::Generator::util package name. This is because AUTOLOAD is used by
1024             the main XML::Generator package to create tags. Simply calling parse_args()
1025             will result in a set of XML tags called .
1026              
1027             Finally, remember that since you are subclassing XML::Generator, you do
1028             not need to provide your own new() method. The one from XML::Generator
1029             is designed to allow you to properly subclass it.
1030              
1031             =head1 STACKABLE AUTOLOADs
1032              
1033             As a simpler alternative to traditional subclassing, the C
1034             that C exports can be configured to work with a
1035             pre-defined C with the ':stacked' option. Simply ensure that
1036             your C is defined before C
1037             executes. The C will get a chance to run first; the subroutine
1038             name will be in your C<$AUTOLOAD> as normal. Return an empty list to let
1039             the default XML::Generator C run or any other value to abort it.
1040             This value will be returned as the result of the original method call.
1041              
1042             If there is no C defined, XML::Generator will create one.
1043             All that this C does is export AUTOLOAD, but that lets your
1044             package be used as if it were a subclass of XML::Generator.
1045              
1046             An example will help:
1047              
1048             package MyGenerator;
1049              
1050             my %entities = ( copy => '©',
1051             nbsp => ' ', ... );
1052              
1053             sub AUTOLOAD {
1054             my($tag) = our $AUTOLOAD =~ /.*::(.*)/;
1055              
1056             return $entities{$tag} if defined $entities{$tag};
1057             return;
1058             }
1059              
1060             use XML::Generator qw(:pretty :stacked);
1061              
1062             This lets someone do:
1063              
1064             use MyGenerator;
1065              
1066             print html(head(title("My Title", copy())));
1067              
1068             Producing:
1069              
1070            
1071            
1072             My Title©
1073            
1074            
1075              
1076             =cut
1077              
1078             package XML::Generator::util;
1079              
1080             # The ::util package space actually has all the utilities
1081             # that do all the work. It must be separate from the
1082             # main XML::Generator package space since named subs will
1083             # interfere with the workings of AUTOLOAD otherwise.
1084              
1085 3     3   24 use strict;
  3         6  
  3         61  
1086 3     3   16 use Carp;
  3         4  
  3         204  
1087              
1088 3     3   19 use constant ESCAPE_TRUE => 1;
  3         6  
  3         442  
1089 3     3   20 use constant ESCAPE_ALWAYS => 1<<1;
  3         5  
  3         185  
1090 3     3   17 use constant ESCAPE_HIGH_BIT => 1<<2;
  3         17  
  3         179  
1091 3     3   17 use constant ESCAPE_APOS => 1<<3;
  3         7  
  3         169  
1092 3     3   17 use constant ESCAPE_ATTR => 1<<4;
  3         15  
  3         193  
1093 3     3   18 use constant ESCAPE_GT => 1<<5;
  3         6  
  3         190  
1094 3     3   17 use constant ESCAPE_EVEN_ENTITIES => 1<<6;
  3         6  
  3         166  
1095 3     3   22 use constant ESCAPE_FILTER_INVALID_CHARS => 1<<7;
  3         5  
  3         8859  
1096              
1097             sub parse_args {
1098             # this parses the args and returns a namespace and attr
1099             # if either were specified, with the remainer of the
1100             # arguments (the content of the tag) in @args. call as:
1101             #
1102             # ($namespace, $attr, @args) = parse_args(@args);
1103            
1104 151     151   337 my($this, @args) = @_;
1105              
1106 151         194 my($namespace);
1107 151         237 my($attr) = ('');
1108              
1109             # check for supplied namespace
1110 151 100       341 if (ref $args[0] eq 'ARRAY') {
1111 30 100 100     42 $namespace = [ map { defined $_ && $_ eq '#default' ? undef : $_ } @{shift @args} ];
  52         216  
  30         65  
1112 30 50 66     84 if (@$namespace > 2 && (@$namespace % 2) != 0) {
1113 0         0 croak "odd number of arguments for namespace";
1114             }
1115             }
1116              
1117             # get globally-set namespace (from new)
1118 151 100       287 unless ($namespace) {
1119 121 50 66     154 $namespace = [ map { defined $_ && $_ eq '#default' ? undef : $_ } @{ $this->{'namespace'} || [] } ];
  35 100       152  
  121         491  
1120             }
1121              
1122 151 100       330 if (@$namespace == 1) { unshift @$namespace, undef }
  25         46  
1123              
1124             # check for supplied attributes
1125 151 100       310 if (ref $args[0] eq 'HASH') {
1126 40         69 $attr = shift @args;
1127 40 100       94 if ($this->{conformance} eq 'strict') {
1128             $this->XML::Generator::util::ck_syntax($_)
1129 23         157 for map split(/:/), keys %$attr;
1130             }
1131             }
1132              
1133 149         461 return ($namespace, $attr, @args);
1134             }
1135              
1136             # This routine is what handles all the automatic tag creation.
1137             # We maintain it as a separate method so that subclasses can
1138             # override individual tags and then call SUPER::tag() to create
1139             # the tag automatically. This is not possible if only AUTOLOAD
1140             # is used, since there is no way to then pass in the name of
1141             # the tag.
1142              
1143             sub tag {
1144 2     2   9 my $sub = XML::Generator::util::c_tag($_[0]);
1145 2 50       17 goto &{ $sub } if $sub;
  2         7  
1146             }
1147            
1148             # Generate a closure that encapsulates all the behavior to generate a tag
1149             sub c_tag {
1150 57     57   89 my $arg = shift;
1151              
1152 57         138 my $strict = $arg->{'conformance'} eq 'strict';
1153 57         84 my $escape = $arg->{'escape'};
1154 57         109 my $empty = $arg->{'empty'};
1155             my $indent = $arg->{'pretty'} =~ /^[^0-9]/
1156             ? $arg->{'pretty'}
1157             : $arg->{'pretty'}
1158 57 100       169 ? " " x $arg->{'pretty'}
    50          
1159             : "";
1160 57         90 my $filter = $arg->{'filter_invalid_chars'};
1161              
1162 57 100       99 my $blessClass = $indent ? 'XML::Generator::pretty' : 'XML::Generator::overload';
1163              
1164             return sub {
1165 151     151   252 my $this = shift;
1166 151   50     337 my $tag = shift || return undef; # catch for bad usage
1167              
1168             # parse our argument list to check for hashref/arrayref properties
1169 151         376 my($namespace, $attr, @args) = $this->XML::Generator::util::parse_args(@_);
1170              
1171 149 100       404 $this->XML::Generator::util::ck_syntax($tag) if $strict;
1172              
1173             # check for attempt to embed "final" document
1174 146         272 for (@args) {
1175 169 100       527 if (UNIVERSAL::isa($_, 'XML::Generator::final')) {
1176 1         79 croak("cannot embed XML document");
1177             }
1178             }
1179              
1180             # Deal with escaping if required
1181 145 100 100     406 if ($escape || $filter) {
1182 73 100       135 if ($attr) {
1183 24         35 foreach my $key (keys %{$attr}) {
  24         56  
1184 26 50       55 next unless defined($attr->{$key});
1185 26         76 XML::Generator::util::escape($attr->{$key}, ESCAPE_ATTR() | $escape);
1186 26 100       64 XML::Generator::util::filter($attr->{$key}) if ($filter);
1187             }
1188             }
1189 73         144 for (@args) {
1190 121 50       206 next unless defined($_);
1191              
1192             # perform escaping, except on sub-documents or simple scalar refs
1193 121 100       358 if (ref $_ eq "SCALAR") {
    100          
1194             # un-ref it
1195 2         5 $_ = $$_;
1196             } elsif (! UNIVERSAL::isa($_, 'XML::Generator::overload') ) {
1197 88 100       161 XML::Generator::util::escape($_, $escape) if $escape ;
1198 88 100       191 XML::Generator::util::filter($_) if $filter;
1199             }
1200             }
1201             } else {
1202             # un-ref simple scalar refs
1203 72         123 for (@args) {
1204 47 50       95 $_ = $$_ if ref $_ eq "SCALAR";
1205             }
1206             }
1207              
1208 145         242 my $prefix = '';
1209 145 100 66     510 $prefix = $namespace->[0] . ":" if $namespace && defined $namespace->[0];
1210 145         323 my $xml = "<$prefix$tag";
1211              
1212 145 100       248 if ($attr) {
1213 38         141 while (my($k, $v) = each %$attr) {
1214 40 50 33     124 next unless defined $k and defined $v;
1215 40 100       83 if ($strict) {
    100          
1216             # allow supplied namespace in attribute names
1217 23 100 66     82 if ($k =~ s/^([^:]+)://) {
    50          
1218 4         9 $this->XML::Generator::util::ck_syntax($k);
1219 4         11 $k = "$1:$k";
1220             } elsif ($prefix && $this->{'qualified_attributes'}) {
1221 0         0 $this->XML::Generator::util::ck_syntax($k);
1222 0         0 $k = "$prefix$k";
1223             } else {
1224 19         34 $this->XML::Generator::util::ck_syntax($k);
1225             }
1226             } elsif ($this->{'qualified_attributes'}) {
1227 2 100       13 if ($k !~ /^[^:]+:/) {
1228 1         3 $k = "$prefix$k";
1229             }
1230             }
1231 40         160 $xml .= qq{ $k="$v"};
1232             }
1233             }
1234              
1235 145         205 my @xml;
1236              
1237 145 100 100     415 if (@args || $empty eq 'close') {
    100          
    100          
1238 94 100 66     241 if ($empty eq 'args' && @args == 1 && ! defined $args[0]) {
      100        
1239 1         2 @xml = ($xml .= ' />');
1240             } else {
1241 93         148 $xml .= '>';
1242 93 100       170 if ($indent) {
1243 45         57 my $prettyend = '';
1244              
1245 45         76 foreach my $arg (@args) {
1246 57 50       103 next unless defined $arg;
1247 57 100       159 if ( UNIVERSAL::isa($arg, 'XML::Generator::cdata' ) ) {
1248 2         4 my $copy = $xml;
1249 2         4 push @xml, $copy, $arg;
1250 2         4 $xml = '';
1251             } else {
1252 55 100 100     196 if ( UNIVERSAL::isa($arg, 'XML::Generator::overload') &&
1253             ! UNIVERSAL::isa($arg, 'XML::Generator::pi') ) {
1254 33         60 $xml .= "\n$indent";
1255 33         54 $prettyend = "\n";
1256 33 100       156 XML::Generator::util::_fixupNS($namespace, $arg) if ref $arg->[0];
1257              
1258 33         53 my @cdata;
1259 33         68 for my $i (0..$#$arg) {
1260 64 100       202 if (UNIVERSAL::isa($arg->[$i], 'XML::Generator::cdata')) {
1261 1         3 push @cdata, $arg->[$i];
1262 1         2 $arg->[$i] = "\001";
1263             }
1264             }
1265              
1266 33         78 $arg =~ s/\n/\n$indent/gs;
1267              
1268 33 100       75 if (@cdata) {
1269 1         3 my @pieces = split "\001", $arg;
1270              
1271 1         2 my $copy = $xml;
1272 1         3 push @xml, $copy;
1273 1         1 $xml = '';
1274 1         2 $arg = '';
1275              
1276 1         2 for my $i (0..$#pieces) {
1277 2 100       5 if (defined $cdata[$i]) {
1278 1         3 push @xml, $pieces[$i], $cdata[$i];
1279             } else {
1280 1         2 push @xml, $pieces[$i];
1281             }
1282             }
1283             }
1284             }
1285 55         120 $xml .= "$arg";
1286             }
1287             }
1288 45         63 $xml .= $prettyend;
1289 45         141 push @xml, ($xml, "");
1290             } else {
1291 48         108 @xml = $xml;
1292 48         140 foreach my $arg (grep defined, @args) {
1293 110 100 66     334 if ( UNIVERSAL::isa($arg, 'XML::Generator::overload') &&
      100        
1294             (! ( UNIVERSAL::isa($arg, 'XML::Generator::cdata' ) ||
1295             UNIVERSAL::isa($arg, 'XML::Generator::pi' )))) {
1296 16 100       55 XML::Generator::util::_fixupNS($namespace, $arg) if ref $arg->[0];
1297             }
1298 110         202 push @xml, $arg;
1299             }
1300 48         124 push @xml, "";
1301             }
1302             }
1303             } elsif ($empty eq 'ignore') {
1304 1         3 @xml = ($xml .= '>');
1305             } elsif ($empty eq 'compact') {
1306 1         3 @xml = ($xml .= '/>');
1307             } else {
1308 49         116 @xml = ($xml .= ' />');
1309             }
1310              
1311 145 50       381 unshift @xml, $namespace if $namespace;
1312              
1313 145         367 return $blessClass->new(\@xml);
1314 57         898 };
1315             }
1316              
1317             sub _fixupNS {
1318             # remove namespaces
1319             # if prefix
1320             # if prefix and uri match one we have, remove them from child
1321             # if prefix does not match one we have, remove it and uri
1322             # from child and add them to us
1323             # no prefix
1324             # if we have an explicit default namespace and the child has the
1325             # same one, remove it from the child
1326             # if we have an explicit default namespace and the child has a
1327             # different one, leave it alone
1328             # if we have an explicit default namespace and the child has none,
1329             # add an empty default namespace to child
1330 47     47   90 my($namespace, $o) = @_;
1331 47         53 my @n = @{$o->[0]};
  47         91  
1332 47         73 my $sawDefault = 0;
1333 47         123 for (my $i = 0; $i < $#n; $i+=2) {
1334 33 100       75 if (defined $n[$i]) { # namespace w/ prefix
    100          
1335 19         56 my $flag = 0;
1336 19         45 for (my $j = 0; $j < $#$namespace; $j+=2) {
1337 18 100       42 next unless defined $namespace->[$j];
1338 8 100       27 if ($namespace->[$j] eq $n[$i]) {
1339 7         11 $flag = 1;
1340 7 50       32 if ($namespace->[$j+1] ne $n[$i+1]) {
1341 0         0 $flag = 2;
1342             }
1343 7         13 last;
1344             }
1345             }
1346 19 100       38 if (!$flag) {
    50          
1347 12         29 push @$namespace, splice @n, $i, 2;
1348 12         31 $i-=2;
1349             } elsif ($flag == 1) {
1350 7         13 splice @n, $i, 2;
1351 7         17 $i-=2;
1352             }
1353             } elsif (defined $n[$i+1]) { # default namespace
1354 11         14 $sawDefault = 1;
1355 11         26 for (my $j = 0; $j < $#$namespace; $j+=2) {
1356 7 100       16 next if defined $namespace->[$j];
1357 5 100       14 if ($namespace->[$j+1] eq $n[$i+1]) {
1358 4         10 splice @n, $i, 2;
1359 4         15 $i-=2;
1360             }
1361             }
1362             }
1363             }
1364              
1365             # check to see if we need to add explicit default namespace of "" to child
1366 47 50 66     62 if (! @{ $o->[0] } &&
      66        
1367             ! $sawDefault &&
1368 18 100       103 grep { defined $namespace->[$_ * 2 + 1] &&
1369             ! defined $namespace->[$_ * 2 ] } 0..($#$namespace/2)) {
1370 0         0 push @n, undef, "";
1371             }
1372              
1373 47 100       90 if (@n) {
1374 10         28 $o->[0] = [@n];
1375             } else {
1376 37         72 splice @$o, 0, 1;
1377             }
1378             }
1379              
1380             # Fetch and store config values (those set via new())
1381             # This is only here for subclasses
1382              
1383             sub config {
1384 0     0   0 my $this = shift;
1385 0   0     0 my $key = shift || return undef;
1386             @_ ? $this->{$key} = $_[0]
1387 0 0       0 : $this->{$key};
1388             }
1389              
1390             # Collect all escaping into one place
1391             sub escape {
1392             # $_[0] is the argument, $_[1] are the flags
1393 96 100   96   169 return unless defined $_[0];
1394              
1395 93         125 my $f = $_[1];
1396 93 100       175 if ($f & ESCAPE_ALWAYS) {
1397 77 100       173 if ($f & ESCAPE_EVEN_ENTITIES) {
1398 1         5 $_[0] =~ s/&/&/g;
1399             } else {
1400 76         159 $_[0] =~ s/&(?!(?:#[0-9]+|#x[0-9a-fA-F]+|\w+);)/&/g;
1401             }
1402              
1403 77         124 $_[0] =~ s/
1404 77 50       160 $_[0] =~ s/>/>/g if $f & ESCAPE_GT;
1405 77 100       174 $_[0] =~ s/"/"/g if $f & ESCAPE_ATTR;
1406 77 100 100     242 $_[0] =~ s/'/'/g if $f & ESCAPE_ATTR && $f & ESCAPE_APOS;
1407             } else {
1408 16         45 $_[0] =~ s/([^\\]|^)&/$1&/g;
1409 16         27 $_[0] =~ s/\\&/&/g;
1410 16         44 $_[0] =~ s/([^\\]|^)
1411 16         29 $_[0] =~ s/\\
1412 16 100       44 if ($f & ESCAPE_GT) {
1413 8         17 $_[0] =~ s/([^\\]|^)>/$1>/g;
1414 8         16 $_[0] =~ s/\\>/>/g;
1415             }
1416 16 100       29 if ($f & ESCAPE_ATTR) {
1417 12         49 $_[0] =~ s/(?
1418 12         28 $_[0] =~ s/\\"/"/g;
1419 12 50       33 if ($f & ESCAPE_APOS) {
1420 0         0 $_[0] =~ s/([^\\]|^)'/$1'/g;
1421 0         0 $_[0] =~ s/\\'/'/g;
1422             }
1423             }
1424             }
1425 93 100       181 if ($f & ESCAPE_HIGH_BIT) {
1426 5         24 $_[0] =~ s/([^\x00-\x7f])/'&#'.ord($1).';'/ge;
  15         49  
1427             }
1428             }
1429              
1430 116     116   247 sub filter { $_[0] =~ tr/\x00\x01\x02\x03\x04\x05\x06\x07\x08\x0B\x0C\x0E\x0F\x10\x11\x12\x13\x14\x15\x16\x17\x18\x19\x1A\x1B\x1C\x1D\x1E\x1F\x7F\x80\x81\x82\x83\x84\x86\x87\x88\x89\x8A\x8B\x8C\x8D\x8E\x8F\x90\x91\x92\x93\x94\x95\x96\x97\x98\x99\x9A\x9B\x9C\x9D\x9E\x9F//d }
1431              
1432             # verify syntax of supplied name; croak if it's not valid.
1433             # rules: 1. name must begin with a letter or an underscore
1434             # 2. name may contain any number of letters, numbers, hyphens,
1435             # periods or underscores
1436             # 3. name cannot begin with "xml" in any case
1437             sub ck_syntax {
1438 130     130   229 my($this, $name) = @_;
1439             # use \w and \d so that everything works under "use locale" and
1440             # "use utf8"
1441 130 100       511 if ($name =~ /^\w[\w\-\.]*$/) {
1442 129 100       292 if ($name =~ /^\d/) {
1443 2         172 croak "name [$name] may not begin with a number";
1444             }
1445             } else {
1446 1         91 croak "name [$name] contains illegal character(s)";
1447             }
1448 127 100       290 if ($name =~ /^xml/i) {
1449 3 100 66     14 if (!$this->{'allowed_xml_tags'} || ! grep { $_ eq $name } @{ $this->{'allowed_xml_tags'} }) {
1450 2         323 croak "names beginning with 'xml' are reserved by the W3C";
1451             }
1452             }
1453             }
1454              
1455             my %DTDs;
1456             my $DTD;
1457              
1458             sub parse_dtd {
1459 1     1   23 my $this = shift;
1460 1         4 my($dtd) = @_;
1461              
1462 1         2 my($root, $type, $name, $uri);
1463              
1464 1 50       18 croak "DTD must be supplied as an array ref" unless (ref $dtd eq 'ARRAY');
1465 1 50       2 croak "DTD must have at least 3 elements" unless (@{$dtd} >= 3);
  1         6  
1466              
1467 1         2 ($root, $type) = @{$dtd}[0,1];
  1         5  
1468 1 50       15 if ($type eq 'PUBLIC') {
    50          
1469 0         0 ($name, $uri) = @{$dtd}[2,3];
  0         0  
1470             } elsif ($type eq 'SYSTEM') {
1471 1         6 $uri = $dtd->[2];
1472             } else {
1473 0         0 croak "unknown dtd type [$type]";
1474             }
1475 1 50       7 return $DTDs{$uri} if $DTDs{$uri};
1476              
1477             # parse DTD into $DTD (not implemented yet)
1478 1         3 my $dtd_text = get_dtd($uri);
1479              
1480 1         4 return $DTDs{$uri} = $DTD;
1481             }
1482              
1483             sub get_dtd {
1484 1     1   3 my($uri) = @_;
1485 1         2 return;
1486             }
1487              
1488             # This package is needed so that embedded tags are correctly
1489             # interpreted as such and handled properly. Otherwise, you'd
1490             # get "<inner />"
1491              
1492             package XML::Generator::overload;
1493              
1494 98     98   244 use overload '""' => sub { $_[0]->stringify },
1495 0     0   0 '0+' => sub { $_[0]->stringify },
1496 0     0   0 'bool' => sub { $_[0]->stringify },
1497 100 50   100   3773 'eq' => sub { (ref $_[0] ? $_[0]->stringify : $_[0]) eq
    50          
1498 3     3   3656 (ref $_[1] ? $_[1]->stringify : $_[1])};
  3         3024  
  3         39  
1499              
1500             sub new {
1501 163     163   291 my($class, $xml) = @_;
1502 163         1056 return bless $xml, $class;
1503             }
1504              
1505             sub stringify {
1506 198 50   198   523 return $_[0] unless UNIVERSAL::isa($_[0], 'XML::Generator::overload');
1507 198 100       413 if (ref($_[0]->[0])) { # namespace
1508 108         148 my $n = shift @{$_[0]};
  108         247  
1509 108         342 for (my $i = ($#$n - 1); $i >= 0; $i-=2) {
1510 45         106 my($prefix, $uri) = @$n[$i,$i+1];
1511 45         102 XML::Generator::util::escape($uri, XML::Generator::util::ESCAPE_ATTR |
1512             XML::Generator::util::ESCAPE_ALWAYS|
1513             XML::Generator::util::ESCAPE_GT);
1514 45 100       89 if (defined $prefix) {
1515 21         201 $_[0]->[0] =~ s/^([^ \/>]+)/$1 xmlns:$prefix="$uri"/;
1516             } else {
1517 24   100     47 $uri ||= '';
1518 24         179 $_[0]->[0] =~ s/^([^ \/>]+)/$1 xmlns="$uri"/;
1519             }
1520             }
1521             }
1522              
1523 198   50     527 join $, || "", @{$_[0]}
  198         700  
1524             }
1525              
1526       0     sub DESTROY { }
1527              
1528             package XML::Generator::pretty;
1529              
1530 3     3   1196 use base 'XML::Generator::overload';
  3         7  
  3         2080  
1531              
1532             sub stringify {
1533 96     96   150 my $this = shift;
1534 96         159 my $string = $this->SUPER::stringify();
1535              
1536 96         201 $string =~ s{^((\s*<(?:\w+:)?\w[-.\w]* )[^ "]+"[^"]+")( .{40,})}
  1         17  
1537 1         5 { my($a,$b,$c) = ($1, $2, $3);
  1         7  
1538 1         11 $c =~ s{ ((?:\w+:)?\w+="[^\"]+")}{"\n" . (' 'x(length $b)) . $1}ge;
1539             "$a$c" }gem;
1540 96         407  
1541             return $string;
1542             }
1543              
1544             package XML::Generator::final;
1545 3     3   23  
  3         5  
  3         760  
1546             use base 'XML::Generator::overload';
1547              
1548             package XML::Generator::comment;
1549 3     3   23  
  3         11  
  3         750  
1550             use base 'XML::Generator::overload';
1551              
1552             package XML::Generator::pi;
1553 3     3   22  
  3         5  
  3         710  
1554             use base 'XML::Generator::overload';
1555              
1556             package XML::Generator::cdata;
1557 3     3   21  
  3         6  
  3         779  
1558             use base 'XML::Generator::overload';
1559              
1560             1;
1561             __END__