File Coverage

blib/lib/Role/Markup/XML.pm
Criterion Covered Total %
statement 15 17 88.2
branch n/a
condition n/a
subroutine 6 6 100.0
pod n/a
total 21 23 91.3


line stmt bran cond sub pod time code
1             package Role::Markup::XML;
2              
3 1     1   13478 use 5.010;
  1         3  
4 1     1   3 use strict;
  1         2  
  1         17  
5 1     1   3 use warnings FATAL => 'all';
  1         3  
  1         35  
6              
7 1     1   474 use Moo::Role;
  1         13756  
  1         4  
8 1     1   665 use namespace::autoclean;
  1         10077  
  1         4  
9              
10 1     1   222 use XML::LibXML ();
  0            
  0            
11             use Scalar::Util ();
12             use Carp ();
13              
14             use constant XHTMLNS => 'http://www.w3.org/1999/xhtml';
15              
16             # XXX this is a shitty qname regex: no unicode but whatever
17             #use constant QNAME_RE =>
18             # qr/^(?:([A-Za-z][0-9A-Za-z_-]*):)?([A-Za-z][0-9A-Za-z_-]*)$/;
19              
20             use constant NCNAME_PAT => do {
21             my $ns = '_A-Za-z\N{U+C0}-\N{U+D6}\N{U+D8}-\N{U+F6}\N{U+F8}-\N{U+2FF}' .
22             '\N{U+370}-\N{U+37D}\N{U+37F}-\N{U+1FFF}\N{U+200C}-\N{U+200D}' .
23             '\N{U+2070}-\N{U+218F}\N{U+2C00}-\N{U+2FEF}\N{U+3001}-\N{U+D7FF}' .
24             '\N{U+F900}-\N{U+FDCF}\N{U+FDF0}-\N{U+FFFD}' .
25             '\N{U+10000}-\N{U+EFFFF}';
26             my $nc = '0-9\N{U+B7}\N{U+300}-\N{U+36F}\N{U+203F}-\N{U+2040}-';
27             sprintf '[%s][%s%s]*', $ns, $ns, $nc;
28             };
29              
30             use constant NCNAME_RE => do {
31             my $nc = NCNAME_PAT;
32             qr/^($nc)$/o;
33             };
34              
35             use constant QNAME_RE => do {
36             my $nc = NCNAME_PAT;
37             qr/^(?:($nc):)?($nc)$/o;
38             };
39              
40             #STDERR->binmode('utf8');
41             #warn NCNAME_RE;
42              
43              
44             has _ATTRS => (
45             is => 'ro',
46             isa => sub { Carp::croak('Input must be a HASH reference')
47             unless ref $_[0] eq 'HASH' },
48             default => sub { { } },
49             );
50              
51             =head1 NAME
52              
53             Role::Markup::XML - Moo(se) role for bolt-on lazy XML markup
54              
55             =head1 VERSION
56              
57             Version 0.04
58              
59             =cut
60              
61             our $VERSION = '0.04';
62              
63             =head1 SYNOPSIS
64              
65             package My::MarkupEnabled;
66              
67             use Moo; # or Moose, or something compatible
68             with 'Role::Markup::XML'; # ...and this of course
69              
70             # write some other code...
71              
72             sub something_useful {
73             my $self = shift;
74              
75             # put your XML-generating data structure here
76             my %spec = (
77             -name => 'my:foo', # element name
78             -content => { -name => 'my:bar' }, # element content
79             hurr => 'durr', # attribute
80             'my:derp' => 'lulz', # namespaced attribute
81             'xmlns:my' => 'urn:x-bogus:foo', # namespaces go inline
82             );
83              
84             # create a document object to hang on to
85             my $doc = $self->_DOC;
86              
87             # returns the last node generated, which is
88             my $stub = $self->_XML(
89             doc => $doc,
90             spec => \%spec,
91             );
92              
93             my @contents = (
94             # imagine a bunch of things in here
95             );
96              
97             # since these nodes will be appended to $stub, we aren't
98             # interested in the output this time
99             $self->_XML(
100             parent => $stub, # owner document is derived
101             spec => \@contents, # also accepts ARRAY refs
102             args => $self->cb_args, # some useful state data
103             );
104              
105             # the rest of the ops come from XML::LibXML
106             return $doc->toString(1);
107             }
108              
109             =head1 DESCRIPTION
110              
111             This is indeed yet another module for lazy XML markup generation. It
112             exists because it is different:
113              
114             =over 4
115              
116             =item
117              
118             It converses primarily in reusable, inspectable, and most importantly,
119             I Perl data structures,
120              
121             =item
122              
123             It also ingests existing L nodes,
124              
125             =item
126              
127             It enables you to generate markup I, rather than all at
128             once,
129              
130             =item
131              
132             It Does the Right ThingE<0x2122> around a bunch of otherwise tedious
133             boilerplate operations, such as namespaces, XHTML, or flattening
134             token lists in attributes,
135              
136             =item
137              
138             It has a callback infrastructure to help you create modular templates,
139             or otherwise override behaviour you don't like,
140              
141             =item
142              
143             It is implemented as a Role, to be more conducive to modern Perl
144             development.
145              
146             =back
147              
148             I began by using L. It is pretty good,
149             definitely preferable to typing out reams of L DOM-like
150             API any time I wanted to make some (guaranteed well-formed) XML. I
151             even submitted a patch to it to make it better. Nevertheless, I have
152             reservations about the general approach to terse markup-generating
153             libraries, in particular about the profligate use of anonymous
154             subroutines. (You also see this in
155             L for Python,
156             L
157             for Ruby, etc.)
158              
159             The main issue is that these languages aren't Lisp: it costs something
160             at runtime to gin up a stack of nested anonymous subroutines, run them
161             once, and then immediately throw them away. It likewise costs in
162             legibility to have to write a bunch of imperative code to do what is
163             essentially data declaration. It also costs in sanity to have to write
164             function-generating-function-generating functions just to get the mess
165             under control. What you get for your trouble is an interim product
166             that is impossible to inspect or manipulate. This ostensibly
167             time-saving pattern quickly hits a wall in both development, and at
168             runtime.
169              
170             The answer? Use (in this case) Perl's elementary data structures to
171             convey the requisite information: data structures which can be built
172             up from bits and pieces, referenced multiple times, sliced, diced,
173             spliced, frozen, thawed, inspected, and otherwise operated on by
174             ordinary Perl routines. Provide mix-and-match capability with vanilla
175             L, callbacks, and make the whole thing an unobtrusive
176             mix-in that you can bolt onto your existing code.
177              
178             =head1 METHODS
179              
180             Methods in this module are named such as to stay out of the way of
181             I module's interface.
182              
183             =head2 _DOC [$VERSION,] [$ENCODING]
184              
185             Generate a document node. Shorthand for L.
186              
187             =cut
188              
189             sub _DOC {
190             my (undef, $version, $encoding) = @_;
191             $version ||= '1.0';
192             $encoding ||= 'utf-8';
193              
194             XML::LibXML::Document->new($version, $encoding);
195             }
196              
197             =head2 _ELEM $TAG [, $DOC, \%NSMAP ]
198              
199             Generate a single XML element. Generates a new document unless C<$DOC>
200             is specified. Defaults to XHTML if no namespace map is provided.
201              
202             =cut
203              
204             sub _ELEM {
205             my ($self, $tag, $doc, $nsmap) = @_;
206             my ($prefix, $local) = ($tag =~ QNAME_RE);
207             $prefix ||= '';
208             $doc ||= $self->_DOC;
209              
210             my $ns = $nsmap && $nsmap->{$prefix} ? $nsmap->{$prefix} : XHTMLNS;
211              
212             my $elem = $doc->createElementNS($ns, $tag);
213             for my $k (sort keys %$nsmap) {
214             $elem->setNamespace($nsmap->{$k}, $k, $prefix eq $k);
215             }
216              
217             # add boilerplate attributes
218             if (my $a = $self->_ATTRS->{$tag}) {
219             map { $elem->setAttribute($_ => $a->{$_}) } keys %$a;
220             }
221              
222             $elem;
223             }
224              
225             =head2 _XML $SPEC [, $PARENT, $DOC, $ARGS | @ARGS ] | %PARAMS
226              
227             Generate an XML tree according to the L
228             format|/Specification Format>. Returns the I by
229             the process. Parameters are as follows:
230              
231             =over 4
232              
233             =item spec
234              
235             The node specification. Strictly speaking this is optional, but there
236             isn't much of a point of running this method if there is no spec to
237             run it over.
238              
239             =item doc
240              
241             The L object intended to own the
242             contents. Optional, however it is often desirable to supply a document
243             object along with the initial call to this method, so as not to have
244             to fish it out later.
245              
246             =item parent
247              
248             The L (or, redundantly, Document) object which
249             is intended to be the parent node of the spec. Optional.
250              
251             =item args
252              
253             An C reference of arguments to be passed into C
254             references embedded in the spec. Optional.
255              
256             =back
257              
258             =head3 Specification Format
259              
260             The building blocks of the spec are, unsurprisingly, C and
261             C references. The former correspond to elements and other
262             things, while the latter correspond to lists thereof. Literals become
263             text nodes, and blessed objects will be treated like strings, so it
264             helps if they have a string L. C references may be
265             used just about anywhere, and will be dereferenced recursively using
266             the supplied L until there is nothing left to dereference. It
267             is up to I to keep these data structures free of cycles.
268              
269             =over 4
270              
271             =item Elements
272              
273             Special keys designate the name and content of an element spec. These
274             are, unimaginitively, C<-name> and C<-content>. They work like so:
275              
276             { -name => 'body', -content => 'hurr' }
277              
278             # produces hurr
279              
280             Note that C<-content> can take any primitive: literal, C,
281             C or C reference, L object, etc.
282              
283             =item Attributes
284              
285             Any key is not C<-name> or C<-content> will be interpreted as an attribute.
286              
287             { -name => 'body', -content => 'hurr', class => 'lolwut' }
288              
289             # produces hurr
290              
291             When references are values of attributes, they are flattened into strings:
292              
293             { -name => 'body', -content => 'hurr', class => [qw(one two three)] }
294              
295             # produces hurr
296              
297             =item Namespaces
298              
299             If there is a colon in either the C<-name> key value or any of the
300             attribute keys, the processor will expect a namespace that corresponds
301             to that prefix. These are specified exactly as one would with ordinary
302             XML, with the use of an C attribute>. (Prefix-free C
303             attributes likewise work as expected.)
304              
305             { -name => 'svg',
306             xmlns => 'http://www.w3.org/2000/svg',
307             'xmlns:xlink' => 'http://www.w3.org/1999/xlink',
308             -content => [
309             { -name => 'a', 'xlink:href' => 'http://some.host/' },
310             ],
311             }
312              
313             # produces:
314             #
315             # xmlns:xlink="http://www.w3.org/1999/xlink">
316             #
317             #
318              
319             =item Other Nodes
320              
321             =over 4
322              
323             =item C<-pi>
324              
325             Processing instructions are designated by the special key C<-pi> and
326             accept arbitrary pseudo-attributes:
327              
328             { -pi => 'xml-stylesheet', type => 'text/xsl', href => '/my.xsl' }
329              
330             # produces
331              
332             =item C<-doctype>
333              
334             Document type declarations are designated by the special key
335             C<-doctype> and accept values for the keys C and C:
336              
337             { -doctype => 'html' }
338              
339             # produces
340              
341             =item C<-comment>
342              
343             Comments are designated by the special key C<-comment> and whatever is
344             in the value of that key:
345              
346             { -comment => 'hey you guyyyys' }
347              
348             # produces
349              
350             =back
351              
352             =item Callbacks
353              
354             Just about any part of a markup spec can be replaced by a C
355             reference, which can return any single value, including another
356             C reference. These are called in the context of C<$self>, i.e.,
357             as if they were a method of the object that does the role. The
358             L in the original method call form the subsequent input:
359              
360             sub callback {
361             my ($self, @args) = @_;
362              
363             my %node = (-name => 'section', id => $self->generate_id);
364              
365             # ...do things to %node, presumably involving @args...
366              
367             return \%node;
368             }
369              
370             sub make_xml {
371             my $self = shift;
372              
373             my $doc = $self->_DOC;
374             $self->_XML(
375             doc => $doc,
376             spec => { -name => 'p', -content => \&callback },
377             );
378              
379             return $doc;
380             }
381              
382             C references can appear in attribute values as well.
383              
384             =back
385              
386             =cut
387              
388             sub _flatten {
389             my ($self, $spec, $args) = @_;
390             if (my $ref = ref $spec) {
391             if ($ref eq 'ARRAY') {
392             return join ' ', grep { defined $_ }
393             map { $self->_flatten($_, $args) } @$spec;
394             }
395             elsif ($ref eq 'HASH') {
396             return join ' ',
397             map { join ': ', $_, $self->_flatten($spec->{$_}, $args) }
398             grep { defined $spec->{$_} } sort keys %$spec;
399             }
400             elsif ($ref eq 'CODE') {
401             return $self->_flatten($spec->($self, @$args), $args);
402             }
403             else {
404             return "$spec";
405             }
406             }
407             else {
408             return $spec;
409             }
410             }
411              
412             # figure out if the child should be some kind of table tag based on the parent
413             sub _table_tag {
414             my $parent = shift or return;
415              
416             my %is_tr = (thead => 1, tfoot => 1, tbody => 1);
417             my %is_th = (thead => 1, tfoot => 1);
418              
419             if ($parent->nodeType == 1) {
420             my $pln = $parent->localname;
421              
422             return 'tr' if $is_tr{$pln};
423              
424             if ($pln eq 'tr') {
425             my $gp = $parent->parentNode;
426             if ($gp and $gp->nodeType == 1) {
427             return $is_th{$gp->localname} ? 'th' : 'td';
428             }
429             }
430             }
431              
432             return;
433             }
434              
435             sub _attach {
436             my ($node, $parent) = @_;
437              
438             if ($node && $parent) {
439             if ($parent->nodeType == 9 and $node->nodeType == 1) {
440             $parent->setDocumentElement($node);
441             }
442             else {
443             $parent->appendChild($node);
444             }
445             }
446             $node;
447             }
448              
449             sub _XML {
450             my $self = shift;
451             my %p;
452             if (ref $_[0]) {
453             $p{spec} = $_[0];
454             @p{qw(parent doc)} = @_[1,2];
455             if (defined $_[3] and ref $_[3] eq 'ARRAY') {
456             $p{args} = $_[3];
457             }
458             else {
459             $p{args} = [@_[3..$#_]];
460             }
461             }
462             else {
463             %p = @_;
464             }
465              
466             $p{args} ||= [];
467             $p{doc} ||= $p{parent} && $p{parent}->ownerDocument
468             ? $p{parent}->ownerDocument : $self->_DOC;
469             $p{parent} ||= $p{doc}; # this might be problematic
470              
471             my $node;
472              
473             my $ref = ref($p{spec}) || '';
474             if ($ref eq 'ARRAY') {
475             my @out = map {
476             $self->_XML(spec => $_, parent => $p{parent},
477             doc => $p{doc}, args => $p{args}) } @{$p{spec}};
478             if (@out) {
479             return wantarray ? @out : $out[-1];
480             }
481             return $p{parent};
482             }
483             elsif ($ref eq 'CODE') {
484             return $self->_XML(spec => $p{spec}->($self, @{$p{args}}),
485             parent => $p{parent},
486             doc => $p{doc},
487             args => $p{args});
488             }
489             elsif ($ref eq 'HASH') {
490             # copy the spec so we don't screw it up
491             my %spec = %{$p{spec}};
492              
493             if (my $c = $spec{'-comment'}) {
494             $node = $p{doc}->createComment($self->_flatten($c, @{$p{args}}));
495             _attach($node, $p{parent});
496             return $node;
497             }
498             if (my $target = delete $spec{'-pi'}) {
499             # take -content over content
500             my $content = defined $spec{'-content'} ?
501             delete $spec{'-content'} : delete $spec{content};
502             my $data = join ' ', map {
503             sprintf q{%s="%s"}, $_, $self->_flatten($spec{$_}, @{$p{args}})
504             } sort keys %spec;
505              
506             $data .= ' ' .
507             $self->_flatten($content, @{$p{args}}) if defined $content;
508              
509             $node = $p{doc}->createProcessingInstruction($target, $data);
510             _attach($node, $p{parent});
511             return $node;
512             }
513             elsif (my $dtd = $spec{'-doctype'}) {
514             # in XML::LibXML::LazyBuilder i wrote that there is some
515             # XS issue and these values have to be explicitly passed
516             # in as undef.
517             my $public = $spec{public};
518             my $system = $spec{system};
519             $node = $p{doc}->createExternalSubset
520             ($dtd, $public || undef, $system || undef);
521             _attach($node, $p{doc});
522             return $node;
523             }
524             else {
525             # check for specified tag
526             my $tag = delete $spec{'-name'};
527              
528             my ($prefix, $local);
529             if (defined $tag) {
530             ($prefix, $local) = ($tag =~ QNAME_RE);
531             Carp::croak("Cannot make use of tag $tag")
532             unless defined $local;
533             }
534             $prefix ||= '';
535              
536             # detect appropriate table tag
537             unless ($tag ||= _table_tag($p{parent})) {
538             my $is_head = $p{parent}->nodeType == 1 &&
539             $p{parent}->localname eq 'head';
540             # detect tag
541             if (defined $spec{src}) {
542             $tag = 'img';
543             }
544             elsif (defined $spec{href}) {
545             $tag = $is_head ? 'link' : 'a';
546             }
547             else {
548             $tag = $is_head ? 'meta' : 'span';
549             }
550             }
551              
552             # okay generate the node
553             my %ns;
554              
555             if (my $nsuri = $p{parent}->lookupNamespaceURI($prefix)) {
556             $ns{$prefix} = $nsuri;
557             }
558              
559             for my $k (keys %spec) {
560             next unless $k =~ /^xmlns(?::(.*))/;
561             my $prefix = $1 || '';
562              
563             my $v = delete $spec{$k};
564             $v =~ s/^\s*(.*?)\s*$/$1/; # trim
565             $ns{$prefix} = $v;
566             }
567             $node = $self->_ELEM($tag, $p{doc}, \%ns);
568             _attach($node, $p{parent});
569              
570             # now do the attributes
571             for my $k (sort grep { $_ =~ QNAME_RE } keys %spec) {
572              
573             my $val = $self->_flatten($spec{$k}, $p{args});
574             $node->setAttribute($k => $val) if (defined $val);
575             }
576              
577             # special handler for explicit content
578             my $content = delete $spec{'-content'};
579             return $self->_XML(
580             spec => $content,
581             parent => $node,
582             doc => $p{doc},
583             args => $p{args}
584             ) if defined $content;
585             }
586             }
587             elsif (Scalar::Util::blessed($p{spec})
588             and $p{spec}->isa('XML::LibXML::Node')) {
589             $node = $p{spec}->cloneNode(1);
590             _attach($node, $p{parent});
591             }
592             else {
593             # spec is a text node, if defined
594             if (defined $p{spec}) {
595             $node = $p{doc}->createTextNode("$p{spec}");
596             _attach($node, $p{parent});
597             }
598             }
599              
600             $node;
601             }
602              
603             =head2 _XHTML | %PARAMS
604              
605             Generate an XHTML+RDFa stub. Return the CbodyE> and the
606             document when called in list context, otherwise return just the
607             CbodyE> in scalar context (which can be used in subsequent
608             calls to L).
609              
610             my ($body, $doc) = $self->_XHTML(%p);
611              
612             # or
613              
614             my $body = $self->_XHTML(%p);
615              
616             =head3 Parameters
617              
618             =over 4
619              
620             =item uri
621              
622             The C attribute of the C<> element.
623              
624             =item ns
625              
626             A mapping of namespace prefixes to URIs, which by default will appear
627             as I XML namespaces I the C attribute.
628              
629             =item prefix
630              
631             Also a mapping of prefixes to URIs. If this is set rather than C,
632             then the XML namespaces will I be set. Conversely, if this
633             parameter is defined but false, then I the contents of C
634             will appear in the conventional C way.
635              
636             =item title
637              
638             This can either be a literal title string, or C reference, or
639             C reference assumed to encompass the whole C<>
640             element, or an C reference where the first element is the title
641             and subsequent elements are predicates.
642              
643             =item link
644              
645             This can either be an C reference of ordinary markup specs, or
646             a C reference where the keys are the C attribute and the
647             values are one or more (via C ref) URIs. In the latter form the
648             following behaviour holds:
649              
650             =over 4
651              
652             =item
653              
654             Predicates are grouped by C, folded, and sorted alphabetically.
655              
656             =item
657              
658             C<> elements are sorted first lexically by the sorted
659             C, then by sorted C, then by C.
660              
661             =item
662              
663             A special empty C<""> hash key can be used to pass in another similar
664             structure whose keys represent C, or reverse predicates.
665              
666             =item
667              
668             A special C<-about> key can be used to specify another C
669             reference where the keys are subjects and the values are similar
670             structures to the one described.
671              
672             =back
673              
674             {
675             # ordinary links
676             'rel:prop' => [qw(urn:x-target:1 urn:x-target:2)],
677              
678             # special case for reverse links
679             '' => { 'rev:prop' => 'urn:x-demo-subject:id' },
680              
681             # special case for alternate subject
682             -about => {
683             'urn:x-demo-subject:id' => { 'some:property' => 'urn:x-target' } },
684             }
685              
686             The C reference form is passed along as-is.
687              
688             =item meta
689              
690             Behaves similarly to the C parameter, with the following exceptions:
691              
692             =over 4
693              
694             =item
695              
696             No C<""> or C<-about> pseudo-keys, as they are meaningless for
697             literals.
698              
699             =item
700              
701             Literal values can be expressed as an C reference of the form
702             C<[$val, $lang, $type]> with either the second or third element
703             C. They may also be represented as a C reference where
704             the keys are the language (denoted by a leading C<@>) or datatype
705             (everything else), and the values are the literal values.
706              
707             =back
708              
709             {
710             'prop:id' => ['foo', [2.3, undef, 'xsd:decimal']],
711             'exotic' => { '@en' => ['yo dawg', 'derp'] }
712             }
713              
714             =item head
715              
716             This is an optional C reference of C<> elements that
717             are neither C<> nor C<> (or, if you want,
718             additional unmolested C<> and C<> elements).
719              
720             =item attr
721              
722             These attributes (including C<-content>) will be passed into the
723             C<> element.
724              
725             =item content
726              
727             This parameter enables us to isolate the C<> content without
728             additional attributes.
729              
730             Note that setting this parameter will cause the method to return the
731             innermost, last node that is specified, rather than the C<>.
732              
733             =item transform
734              
735             This is the URI of a (e.g. XSLT) transform which will be included in a
736             processing instruction if supplied.
737              
738             =item args
739              
740             Same as C in L.
741              
742             =back
743              
744             =cut
745              
746             sub _sort_links {
747             # first test is about
748             #warn Data::Dumper::Dumper(\@_);
749             my @a = map { defined $_->{about} ? $_->{about} : '' } @_;
750             my $t1 = $a[0] cmp $a[1];
751             return $t1 if $t1;
752              
753             # then rel
754             my @rl = map { defined $_->{rel} ? $_->{rel} : '' } @_;
755             my $t2 = $rl[0] cmp $rl[1];
756             return $t2 if $t2;
757              
758             # then rev
759             my @rv = map { defined $_->{rev} ? $_->{rev} : '' } @_;
760             my $t3 = $rv[0] cmp $rv[1];
761             return $t3 if $t3;
762              
763             # then finally href
764             my @h = map { defined $_->{href} ? $_->{href} : '' } @_;
765             return $h[0] cmp $h[1];
766             }
767              
768             sub _handle_links {
769             my ($links, $uri) = @_;
770             $links ||= [];
771             return @$links if ref $links eq 'ARRAY';
772             Carp::croak('links must be ARRAY or HASH ref') unless ref $links eq 'HASH';
773              
774             my %l = %$links;
775             my %r = %{delete $l{''} || {}};
776             my %s = %{delete $l{-about} || {}};
777              
778              
779             # merge subjects; blank subject is document
780             %{$s{''} ||= {}} = (%{$s{''} || {}}, %l);
781              
782             my (%types, %titles); # map URIs to types and titles
783              
784             # accumulate predicates into a hierarchical structure of S -> O -> P
785             my (%fwd, %rev);
786             for my $s (keys %s) {
787             for my $p (keys %{$s{$s}}) {
788             my @o = ref $s{$s}{$p} eq 'ARRAY' ? @{$s{$s}{$p}} : ($s{$s}{$p});
789             for my $o (@o) {
790             my ($href, $type, $title) = ref $o eq 'ARRAY' ? @$o : ($o);
791             # XXX do a better uri match
792             $href = '' if $uri and $href eq $uri;
793             # XXX this overwrites titles oh well suck one
794             $types{$href} = $type;
795             $titles{$href} = $title;
796              
797             # accumulate the predicates
798             my $x = $fwd{$s} ||= {};
799             my $y = $rev{$href} ||= {};
800             my $z = $x->{$href} ||= $y->{$s} ||= {};
801             $z->{$p}++;
802             }
803             }
804             }
805              
806             # now do reverse links
807             for my $p (keys %r) {
808             my @o = ref $r{$p} eq 'ARRAY' ? @{$r{$p}} : ($r{$p});
809              
810             for my $o (@o) {
811             # we skip type and title because the link is reversed
812             my ($s) = ref $o eq 'ARRAY' ? @$o : ($o);
813             # XXX do a better uri match
814             $s = '' if $uri and $s eq $uri;
815             my $x = $fwd{$s} ||= {};
816             my $y = $rev{''} ||= {};
817             my $z = $x->{''} ||= $y->{$s} ||= {};
818             $z->{$p}++;
819             }
820             }
821              
822             # now we have accumulated all the predicates and aimed all the
823             # triples in the forward direction. now to construct the list.
824              
825             my (%fout, %rout, @out);
826              
827             # begin by making sure typed links point forward
828             for my $o (keys %types) {
829             for my $s (keys %{$rev{$o}}) {
830             $fout{$s} ||= {};
831             $rout{$o} ||= {};
832              
833             my $x = $fout{$s}{$o};
834             unless ($x) {
835             $x = $fout{$s}{$o} = $rout{$o}{$s} = { href => $o,
836             type => $types{$o} };
837             $x->{about} = $s if $s ne '';
838             push @out, $x;
839             }
840              
841             $x->{type} = $types{$o};
842             }
843             }
844              
845             # now do the same with titles
846             for my $o (keys %titles) {
847             for my $s (keys %{$rev{$o}}) {
848             $fout{$s} ||= {};
849             $rout{$o} ||= {};
850              
851             my $x = $fout{$s}{$o};
852             unless ($x) {
853             $x = $fout{$s}{$o} = $rout{$o}{$s} = { href => $o,
854             title => $titles{$o} };
855             $x->{about} = $s if $s ne '';
856             push @out, $x;
857             }
858              
859             $x->{title} = $titles{$o};
860             }
861             }
862              
863             # now we make sure blank subjects always face forward
864             if ($fwd{''}) {
865             for my $o (sort keys %{$fwd{''}}) {
866             $fout{''} ||= {};
867             $rout{$o} ||= {};
868              
869             my $x = $fout{''}{$o};
870             unless ($x) {
871             $x = $fout{''}{$o} = $rout{$o}{''} = { href => $o };
872             push @out, $x;
873             }
874             }
875             }
876              
877             # now do forward predicates (this mapping is symmetric)
878             for my $s (sort keys %fwd) {
879             for my $o (sort keys %{$fwd{$s}}) {
880             $fout{$s} ||= {};
881             $rout{$o} ||= {};
882              
883             # collate up the predicates
884             my $p = join ' ', sort keys %{$fwd{$s}{$o}};
885              
886             # first try forward
887             my $x = $fout{$s}{$o};
888             if ($x) {
889             # set the link direction based on derp
890             $x->{$x->{href} eq $o ? 'rel' : 'rev'} = $p;
891             # make sure rel exists
892             $x->{rel} = '' unless defined $x->{rel};
893             }
894             else {
895             # then try backward
896             $x = $rout{$s}{$o};
897             if ($x) {
898             # do the same thing but the other way around
899             $x->{$x->{href} eq $o ? 'rel' : 'rev' } = $p;
900             # and make sure rel exists
901             $x->{rel} = '' unless defined $x->{rel};
902             }
903             else {
904             # now just construct the thing
905             $x = $fout{$s}{$o} = $rout{$o}{$s} = {
906             href => $o, rel => $p };
907             $x->{about} = $s if $s ne '';
908             push @out, $x;
909             }
910             }
911             }
912             }
913              
914             #warn Data::Dumper::Dumper(\%fwd);
915              
916             # XXX LOLWUT this shit reuses @_ from *this* function
917             return sort { _sort_links($a, $b) } @out;
918             }
919              
920             sub _sort_meta {
921             # first test property
922             my @p = map { defined $_->{property} ? $_->{property} : '' } @_;
923             my $t1 = $p[0] cmp $p[1];
924             return $t1 if $t1;
925              
926             # next test language
927             my @l = map { defined $_->{'xml:lang'} ? $_->{'xml:lang'} : '' } @_;
928             my $t2 = $l[0] cmp $l[1];
929             return $t2 if $t2;
930              
931             # next test datatype
932             my @d = map { defined $_->{'datatype'} ? $_->{'datatype'} : '' } @_;
933             my $t3 = $d[0] cmp $d[1];
934             return $t3 if $t3;
935              
936             # finally test content
937             my @c = map { defined $_->{'content'} ? $_->{'content'} : '' } @_;
938             # TODO numeric comparison for appropriate datatypes
939             return $d[0] cmp $d[1];
940             }
941              
942             sub _handle_metas {
943             my $metas = shift || [];
944             return @$metas if ref $metas eq 'ARRAY';
945             Carp::croak('meta must be ARRAY or HASH ref') unless ref $metas eq 'HASH';
946              
947             my %m = %$metas;
948             my %c;
949             while (my ($k, $v) = each %m) {
950             my $rv = ref $v;
951              
952             # normalize the input into something we can use
953             my @v;
954             if ($rv eq 'HASH') {
955             # keys are lang/datatype
956             for my $dt (keys %$v) {
957             my $y = $v->{$dt};
958             my @z = ref $y eq 'ARRAY' ? @$y : ($y);
959             my $l = $dt if $dt =~ /^@/;
960             undef $dt if $l;
961             map { push @v, [$_, $l, $dt] } @z;
962             }
963             }
964             else {
965             @v = $rv eq 'ARRAY' ? @$v : ($v);
966             }
967              
968             # now we turn the thing inside out
969             for my $val (@v) {
970             my ($x, $l, $dt) = ref $val eq 'ARRAY' ? @$val : ($val);
971             next unless defined $x;
972              
973             # language becomes datatype if it is set
974             if (defined $l and $l ne '') {
975             $l = "\@$l" unless $l =~ /^@/;
976             $dt = $l;
977             }
978             #$dt ||= '';
979              
980             # now we create the structure
981             my $y = $c{$v} ||= {};
982             my $z = $y->{$dt || ''} ||= {};
983             $z->{$k}++;
984             }
985             }
986              
987             # now we have meta sorted by content
988             my @out;
989             for my $content (keys %c) {
990             while (my ($dt, $preds) = each %{$c{$content}}) {
991             my %meta = (content => $content,
992             property => join ' ', sort keys %$preds);
993             if ($dt =~ /^@(.+)/) {
994             $meta{'xml:lang'} = lc $1;
995             }
996             else {
997             $meta{datatype} = $dt unless $dt eq '';
998             }
999             push @out, \%meta;
1000             }
1001             }
1002             return sort { _sort_meta($a, $b) } @out;
1003             }
1004              
1005             sub _handle_title {
1006             my $title = shift;
1007             my $tr = ref $title;
1008             # this is a title tag but let's make sure
1009             return (%$title, -name => 'title') if $tr eq 'HASH';
1010              
1011             # this is a title tag with shorthand for predicate(s)
1012             if ($tr eq 'ARRAY') {
1013             my ($t, @p) = @{$title};
1014             my ($dt, $l);
1015             ($t, $dt, $l) = @$t if ref $t eq 'ARRAY';
1016             return (-name => 'title', -content => $t,
1017             property => join(' ', sort @p), datatype => $dt, lang => $l);
1018             }
1019              
1020             # this is anything else
1021             return (-name => 'title', -content => $title);
1022             }
1023              
1024             sub _isa_really {
1025             my ($obj, $class) = @_;
1026              
1027             defined $obj and ref $obj
1028             and Scalar::Util::blessed($obj) and $obj->isa($class);
1029             }
1030              
1031             sub _XHTML {
1032             my $self = shift;
1033             my %p = @_;
1034              
1035             # ns is empty if prefix has stuff in it
1036             my $nstemp = _isa_really($p{ns}, 'URI::NamespaceMap')
1037             ? { map +($_ => $p{ns}->namespace_uri($_)->as_string),
1038             $p{ns}->list_prefixes } : $p{ns};
1039             my %ns = map +("xmlns:$_" => $nstemp->{$_}), keys %{$nstemp || {}}
1040             unless $p{prefix};
1041              
1042             # deal with fancy metadata
1043             my @link = _handle_links($p{link}, $p{uri});
1044             my @meta = _handle_metas($p{meta});
1045             my @head = @{$p{head} || []};
1046              
1047             # deal with title
1048             my %title = _handle_title($p{title});
1049             # deal with base
1050             my $base = { -name => 'base', href => $p{uri} } if defined $p{uri};
1051              
1052             # deal with body
1053             my %body = (-name => 'body', %{$p{attr} || {}});
1054             $body{-content} = $p{content} if defined $p{content};
1055              
1056             my @spec = (
1057             { -doctype => 'html' },
1058             { -name => 'html', xmlns => XHTMLNS, %ns,
1059             -content => [
1060             { -name => 'head',
1061             -content => [\%title, $base, @link, @meta, @head] }, \%body ] }
1062             );
1063              
1064             # prefix is empty if it is defined but false, otherwise overrides ns
1065             my $pfxtemp = _isa_really($p{prefix}, 'URI::NamespaceMap')
1066             ? { map +($_ => $p{prefix}->namespace_uri($_)->as_string),
1067             $p{prefix}->list_prefixes } : $p{prefix};
1068             $spec[1]{prefix} = $pfxtemp ? $pfxtemp : defined $pfxtemp ? {} : $nstemp;
1069              
1070             # add transform if present
1071             unshift @spec, { -pi => 'xml-stylesheet', type => 'text/xsl',
1072             href => $p{transform} } if $p{transform};
1073              
1074             my $doc = $p{doc} || $self->_DOC;
1075             my $body = $self->_XML(
1076             doc => $doc,
1077             spec => \@spec,
1078             args => $p{args} || [],
1079             );
1080              
1081             return wantarray ? ($body, $doc) : $body;
1082             }
1083              
1084             =head1 AUTHOR
1085              
1086             Dorian Taylor, C<< >>
1087              
1088             =head1 BUGS
1089              
1090             Please report any bugs or feature requests to C
1091             rt.cpan.org>, or through the web interface at
1092             L. I
1093             will be notified, and then you'll automatically be notified of
1094             progress on your bug as I make changes.
1095              
1096             =head1 SUPPORT
1097              
1098             You can find documentation for this module with the perldoc command.
1099              
1100             perldoc Role::Markup::XML
1101              
1102             You can also look for information at:
1103              
1104             =over 4
1105              
1106             =item * RT: CPAN's request tracker (report bugs here)
1107              
1108             L
1109              
1110             =item * AnnoCPAN: Annotated CPAN documentation
1111              
1112             L
1113              
1114             =item * CPAN Ratings
1115              
1116             L
1117              
1118             =item * Search CPAN
1119              
1120             L
1121              
1122             =back
1123              
1124             =head1 SEE ALSO
1125              
1126             =over 4
1127              
1128             =item
1129              
1130             L
1131              
1132             =item
1133              
1134             L
1135              
1136             =item
1137              
1138             L
1139              
1140             =back
1141              
1142             =head1 LICENSE AND COPYRIGHT
1143              
1144             Copyright 2016 Dorian Taylor.
1145              
1146             Licensed under the Apache License, Version 2.0 (the "License"); you
1147             may not use this file except in compliance with the License. You may
1148             obtain a copy of the License at
1149             L.
1150              
1151             Unless required by applicable law or agreed to in writing, software
1152             distributed under the License is distributed on an "AS IS" BASIS,
1153             WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or
1154             implied. See the License for the specific language governing
1155             permissions and limitations under the License.
1156              
1157             =cut
1158              
1159             1; # End of Role::Markup::XML