Fixed (setf document-element) in the presence of non-element children
[cxml-stp.git] / element.lisp
blob18dec15b83c65c9d51203907f07fbc57dc08299b
1 ;;; -*- show-trailing-whitespace: t; indent-tabs: nil -*-
3 ;;; Copyright (c) 2007 David Lichteblau. All rights reserved.
5 ;;; Redistribution and use in source and binary forms, with or without
6 ;;; modification, are permitted provided that the following conditions
7 ;;; are met:
8 ;;;
9 ;;; * Redistributions of source code must retain the above copyright
10 ;;; notice, this list of conditions and the following disclaimer.
11 ;;;
12 ;;; * Redistributions in binary form must reproduce the above
13 ;;; copyright notice, this list of conditions and the following
14 ;;; disclaimer in the documentation and/or other materials
15 ;;; provided with the distribution.
16 ;;;
17 ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED
18 ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
19 ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
20 ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY
21 ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
22 ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE
23 ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
24 ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY,
25 ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
26 ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
27 ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
29 (in-package :cxml-stp-impl)
31 #+sbcl
32 (declaim (optimize (debug 2)))
35 ;;;; Class ELEMENT
37 (defgeneric local-name (node)
38 (:documentation
39 "@arg[node]{an @class{element} or @class{attribute}}
40 @return{string, an NCName}
41 @short{Returns the node's local name.}
42 @see{qualified-name}
43 @see{namespace-uri}
44 @see{namespace-prefix}"))
46 (defgeneric namespace-uri (node)
47 (:documentation
48 "@arg[node]{an @class{element} or @class{attribute}}
49 @return{string, a URI}
50 @short{Returns the node's namespace URI.}
51 @see{qualified-name}
52 @see{local-name}
53 @see{namespace-prefix}"))
55 (defgeneric namespace-prefix (node)
56 (:documentation
57 "@arg[node]{an @class{element} or @class{attribute}}
58 @return{string, an NCName}
59 @short{Returns the node's namespace prefix.}
60 @see{qualified-name}
61 @see{local-name}
62 @see{namespace-uri}"))
64 (defgeneric (setf value) (newval attribute)
65 (:documentation
66 "@arg[newval]{a string of XML characters}
67 @arg[attribute]{an @class{attribute}}
68 @return{the value}
69 @short{Sets the attribute's value.}"))
72 (defun make-element (name &optional (uri ""))
73 "@arg[name]{string, a QName or NCName}
74 @arg[uri]{a string, the namespace URI}
75 @return{an @class{element}}
76 @short{This function creates an element node of the given name.}"
77 (check-type name runes:rod)
78 (let ((result (make-instance 'element)))
79 (multiple-value-bind (prefix local-name)
80 (cxml::split-qname name)
81 (setf prefix (or prefix ""))
82 (setf (namespace-prefix result) prefix)
83 (setf (namespace-uri result) uri)
84 (setf (local-name result) local-name))
85 result))
87 (defmethod copy ((node element))
88 (let ((result (make-instance 'element)))
89 (setf (%namespace-prefix result) (%namespace-prefix node))
90 (setf (%local-name result) (%local-name node))
91 (setf (%namespace-uri result) (%namespace-uri node))
92 (setf (%namespaces result)
93 (when (%namespaces node)
94 (alexandria:copy-hash-table (%namespaces node))))
95 (setf (%attributes result) (copy-attributes result node))
96 (setf (%base-uri result) (find-base-uri node))
97 (do-children (child node)
98 (append-child result (copy child)))
99 result))
101 (defun copy-attributes (new old)
102 (mapcar (lambda (x)
103 (let ((y (copy x)))
104 (setf (%parent y) new)
106 (%attributes old)))
108 (defun of-name (name &optional (uri ""))
109 "@arg[name]{an NCName string or @code{nil}}
110 @arg[uri]{a string, the namespace URI}
111 @return{an function of one argument}
112 @short{This function creates a test function for nodes of this name.}
114 The function returned will return T if the argument is an instance
115 of @class{attribute} or @class{element} and has the specified local-name
116 and namespace URI, and will return NIL otherwise.
118 If local-name is nil, only the namespace URI is considered for comparison.
120 @see{local-name}
121 @see{namespace-uri}"
122 (when (find #\: name)
123 (stp-error "of-name used with QName as an argument"))
124 (lambda (x)
125 (and (typep x '(or attribute element))
126 (or (null name) (equal (local-name x) name))
127 (equal (namespace-uri x) uri))))
129 (defun qualified-of-name (qname element)
130 "@arg[qname]{string, a QName}
131 @arg[element]{an element in which to look up @code{name}'s namespace}
132 @return{an function of one argument}
133 @short{This function creates a test function for nodes of this name.}
135 @code{qname}'s namespace prefix is resolved into its namespace URI
136 as declared by @code{element}. If @code{qname} does not have a prefix,
137 the namespace URI is the empty string. If @code{qname}'s prefix is
138 not declared on @code{element}, an error is signalled.
140 A function is returned that will return T if the argument is an instance
141 of @class{attribute} or @class{element} and has the local-name
142 namespace URI specified by @code{qname}, and will return NIL otherwise.
144 @see{qualified-name}
145 @see{local-name}
146 @see{find-namespace}
147 @see{namespace-uri}"
148 (multiple-value-bind (prefix local-name)
149 (cxml::split-qname qname)
150 (let ((uri (find-namespace prefix element)))
151 (unless uri
152 (stp-error "namespace ~A not declared on ~A" prefix element))
153 (of-name local-name uri))))
155 (defun map-extra-namespaces (fn element)
156 "@arg[fn]{a designator for a function of two arguments}
157 @arg[element]{an instance of @class{element}}
158 @return{nil}
159 Call fn for each extra namespace declared on @code{element} with
160 namespace prefix and URI as arguments."
161 (when (%namespaces element)
162 (maphash fn (%namespaces element))))
164 (defun find-extra-namespace (prefix element)
165 "@arg[prefix]{a string}
166 @arg[element]{an instance of @class{element}}
167 @return{the namespace URI (a string), or nil}
168 Find the extra namespace named @code{prefix} declared on @code{element}
169 and return its namespace URI, or return nil if no such namespace was found."
170 (when (%namespaces element)
171 (gethash prefix (%namespaces element))))
173 (defun add-attribute (element attribute)
174 "@arg[element]{an instance of @class{element}}
175 @arg[attribute]{an instance of @class{attribute}}
176 @short{Add a new attribute to @code{element} or replace an existing
177 attribute node of the same name.}
179 It is an error if the attribute's namespace conflicts with existing
180 namespace declarations on this element."
181 (check-type element element)
182 (check-type attribute attribute)
183 (assert-orphan attribute)
184 (let ((local-name (local-name attribute))
185 (prefix (namespace-prefix attribute))
186 (uri (namespace-uri attribute)))
187 (when (and (plusp (length prefix))
188 (not (equal "xml" prefix)))
189 (when (and (equal prefix (namespace-prefix element))
190 (not (equal uri (namespace-uri element))))
191 (stp-error "namespace collision with element when adding ~A to ~A"
192 attribute element))
193 (let ((extra-uri (find-extra-namespace prefix element)))
194 (when (and extra-uri (not (equal extra-uri uri)))
195 (stp-error "collision with extra namespaces when adding ~A to ~A"
196 attribute element))))
197 (let ((other (find-attribute-namespace prefix element)))
198 (when (and other (not (equal other uri)))
199 (stp-error "collision with attribute namespace when adding ~A to ~A"
200 attribute element)))
201 (let ((old (find-attribute-named element local-name uri)))
202 (when old
203 (%remove-attribute old)))
204 (%add-attribute attribute element)
205 (setf (%parent attribute) element)))
207 (defun %add-attribute (attribute element)
208 (push attribute (%attributes element)))
210 (defun %remove-attribute (attribute)
211 (alexandria:deletef (%attributes (parent attribute)) attribute)
212 (setf (%parent attribute) nil)
213 attribute)
215 (defun remove-attribute (element attribute)
216 "@arg[element]{an instance of @class{element}}
217 @arg[attribute]{an instance of @class{attribute}}
218 @return{the attribute}
219 @short{Remove an attribute node from @code{element}.}
221 It is an error if @code{attribute} is not an attribute of @code{element}."
222 (check-type element element)
223 (check-type attribute attribute)
224 (unless (eq (parent attribute) element)
225 (stp-error "attempt to remove ~A from non-parent ~A" attribute element))
226 (%remove-attribute attribute))
228 (defun find-attribute-named (element name &optional (uri ""))
229 "@arg[element]{an instance of @class{element}}
230 @arg[name]{string, an NCName}
231 @arg[uri]{string, a namespace URI}
232 @return{an @class{attribute} or nil}
233 @short{Searches for an attribute node of @code{element} with the
234 specified local name and namespace URI and returns it.}
236 Returns nil if no such attribute was found."
237 (find-attribute-if (of-name name uri) element))
239 (defun find-attribute-if (test element)
240 "@arg[test]{a designator for a function of one argument.}
241 @arg[element]{an instance of @class{element}}
242 @return{an @class{attribute} or nil}
243 @short{Searches for an attribute node of @code{element} satisfying
244 @code{test}}
246 Returns nil if no such attribute was found."
247 (find-if test (%attributes element)))
249 (defun sanitize-attribute-name (element name uri urip)
250 (multiple-value-bind (prefix local-name)
251 (cxml::split-qname name)
252 (when prefix
253 (let ((uri2 (find-namespace prefix element)))
254 (cond
255 ((null uri2))
256 ((not urip) (setf uri uri2))
257 ((equal uri uri2))
258 (t (stp-error "prefix ~A does not match uri ~A" prefix uri)))))
259 (values local-name uri)))
261 (defun attribute-value (element name &optional (uri "" urip))
262 "@arg[element]{an instance of @class{element}}
263 @arg[name]{string, an NCName}
264 @arg[uri]{string, a namespace URI}
265 @return{a string or nil}
266 @short{Searches for an attribute node of @code{element} with the
267 specified local name and namespace URI and returns its value.}
269 Returns nil if no such attribute was found."
270 (multiple-value-bind (local-name uri)
271 (sanitize-attribute-name element name uri urip)
272 (let ((a (find-attribute-named element local-name uri)))
273 (if a
274 (value a)
275 nil))))
277 (defun (setf attribute-value) (newval element name &optional (uri "" urip))
278 (multiple-value-bind (local-name uri)
279 (sanitize-attribute-name element name uri urip)
280 (let ((a (find-attribute-named element local-name uri)))
281 (if a
282 (setf (value a) newval)
283 (add-attribute element (make-attribute newval name uri)))
284 newval)))
286 (defmacro with-attributes ((&rest entries) element &body body)
287 "Evaluate body with the specified attributes bound lexically as if they
288 were variables.
290 Each entry in @code{entries} is a list of the form
291 @em{(variable-name attribute-name &optional uri)}, where
292 @code{variable-name}
293 is a symbol and @code{attribute-name} and @code{uri} are strings.
295 The macro with-attributes invokes @fun{attribute-value}
296 to access the attributes. specified by each entry.
297 Both setf and setq can be used to set the value of the attribute."
298 (alexandria:once-only (element)
299 `(symbol-macrolet
300 ,(mapcar (lambda (entry)
301 (destructuring-bind (var name &optional (uri ""))
302 (if (and (listp entry) (cdr entry))
303 entry
304 (list entry (string-downcase
305 (princ-to-string
306 (symbol-name entry)))))
307 `(,var (attribute-value ,element ,name ,uri))))
308 entries)
309 ,@body)))
310 (defun list-attributes (element)
311 "@arg[element]{an @class{element}}
312 @return{a list of @class{attribute} nodes}
313 Returns a freshly consed list containing the attributes of @code{element}."
314 (copy-list (%attributes element)))
316 (defun map-attributes (result-type fn element)
317 "@arg[result-type]{a sequence type specifier, or nil}
318 @arg[fn]{a designator for a function of one argument}
319 @arg[element]{an instance of @class{element}}
320 @return{an sequence of @code{result-type}, or nil}
321 @short{Applies @code{fn} to each attribute nodes of @code{element}.}
323 The @code{result-type} specifies the type of the resulting sequence.
324 @code{map-children} returns nil if @code{result-type} is nil."
325 (map result-type fn (%attributes element)))
327 (defun qualified-name (node)
328 "@arg[node]{an @class{element} or @class{attribute}}
329 @return{string, a QName}
330 @short{Returns the node's qualified name.}
331 The qualified name is computed as prefix ':' local-name.
332 @see{local-name}
333 @see{namespace-uri}
334 @see{namespace-prefix}"
335 (let ((prefix (namespace-prefix node))
336 (local-name (local-name node)))
337 (if (plusp (length prefix))
338 (format nil "~A:~A" prefix local-name)
339 local-name)))
341 (defun find-namespace (prefix element)
342 "@arg[prefix]{a string}
343 @arg[element]{an instance of @class{element}}
344 @return{the namespace URI (a string), or nil}
345 @short{Find the namespace @code{prefix} declared on @code{element}
346 or its parent and return its namespace URI, or return nil if no such
347 namespace was found.}
349 This functions returns the same result as @fun{find-local-namespace}
350 if the namespace is declared directly on @code{element}. Otherwise
351 it takes into account namespaces declared on parent elements."
352 (setf prefix (or prefix ""))
353 (cond
354 ((find-local-namespace prefix element))
355 ((typep (parent element) 'element)
356 (find-namespace prefix (parent element)))
357 ((equal prefix "")
360 nil)))
362 (defun find-attribute-namespace (prefix element)
363 (setf prefix (or prefix ""))
364 (unless (equal prefix "")
365 (let ((a (find prefix
366 (%attributes element)
367 :key #'namespace-prefix
368 :test #'equal)))
369 (if a
370 (namespace-uri a)
371 nil))))
373 (defun find-local-namespace (prefix element)
374 "@arg[prefix]{a string}
375 @arg[element]{an instance of @class{element}}
376 @return{the namespace URI (a string), or nil}
377 @short{Find the namespace @code{prefix} declared on @code{element}
378 and return its namespace URI, or return nil if no such namespace was found.}
380 The namespaces considered by this function are: The namespace of the element
381 itself. The namespaces of element's attributes. Extra namespaces declared
382 by the element. The \"xmlns\" namespace, which is always fixed."
383 (setf prefix (or prefix ""))
384 (cond
385 ((equal prefix (namespace-prefix element))
386 (namespace-uri element))
387 ((equal prefix "xml")
388 "http://www.w3.org/XML/1998/namespace")
389 ((equal prefix "xmlns")
390 "http://www.w3.org/2000/xmlns/")
391 ((find-extra-namespace prefix element))
393 (find-attribute-namespace prefix element))))
395 (defun namep (str)
396 (and (not (zerop (length str)))
397 (cxml::name-start-rune-p (elt str 0))
398 (every #'cxml::name-rune-p str)))
400 (defun nc-name-p (str)
401 (and (namep str) (cxml::nc-name-p str)))
403 (defun check-nc-name (str)
404 (unless (nc-name-p str)
405 (stp-error "not an NCName: ~A" str)))
407 (defgeneric (setf local-name) (newval node))
408 (defmethod (setf local-name) (newval (node element))
409 (check-nc-name newval)
410 (setf (%local-name node) newval))
412 (defun check-uri-like (newval)
413 (declare (optimize speed (safety 0)))
414 (check-type newval string)
415 (when (some (lambda (c)
416 (let ((code (char-code c)))
417 (or (> code 126)
418 (and (< code 32)
419 (not (eql code 9))
420 (not (eql code 10))
421 (not (eql code 13))))))
422 newval)
423 (stp-error "invalid characters in URI")))
425 (defun (setf namespace-uri) (newval element)
426 (check-type element element)
427 (unless newval
428 (setf newval ""))
429 (unless (equal newval (%namespace-uri element))
430 (check-uri-like newval)
431 (if (zerop (length newval))
432 (unless (zerop (length (%namespace-prefix element)))
433 (stp-error "attempt to set empty URI on element with a prefix"))
434 (check-namespace-uri newval))
435 (when (or (find-extra-namespace (%namespace-prefix element) element)
436 (find-attribute-namespace (%namespace-prefix element) element))
437 (stp-error "cannot change element URI because of a conflicting ~
438 declaration for its prefix"))
439 (when (xor (equal newval "http://www.w3.org/XML/1998/namespace")
440 (equal (%namespace-prefix element) "xml"))
441 (stp-error "prefix/URI mismatch for `xml' namespace"))
442 (setf (%namespace-uri element) newval))
443 newval)
445 (defun (setf namespace-prefix) (newval element)
446 (check-type element element)
447 (unless newval
448 (setf newval ""))
449 (when (plusp (length newval))
450 (check-nc-name newval))
451 (let ((uri (find-local-namespace newval element)))
452 (if uri
453 (unless (or (equal uri (%namespace-uri element))
454 (equal newval "xml"))
455 (stp-error "conflicting declarations in namespace prefix change"))
456 (when (and (equal (%namespace-uri element) "") ;not for unintialized
457 (not (zerop (length newval))))
458 (stp-error "cannot assign prefix to element in no namespace"))))
459 (setf (%namespace-prefix element) newval))
461 (defun delete-children (parent)
462 "@arg[parent]{an @class{element}}
463 @return{nil}
464 Deletes all children of @code{element}."
465 (delete-child-if (constantly t) parent))
467 (defun childp (a b)
468 (loop
469 for node = a then (parent node)
470 while node
471 thereis (eq node b)))
473 (defmethod check-insertion-allowed ((parent element) child i)
474 (check-type child node)
475 (assert-orphan child)
476 (typecase child
477 (element
478 (when (childp parent child)
479 (stp-error "attempt to add a node as its own descendant")))
480 ((or comment processing-instruction text))
482 (stp-error "not a valid child of an element: ~A" child))))
484 (defmethod check-deletion-allowed ((parent element) (child node) i))
486 ;; ;; trivial optimization
487 ;; (defmethod replace-children
488 ;; ((parent element) seq &key start1 end1 start2 end2)
489 ;; (setf start1 (or start1 0))
490 ;; (setf start2 (or start2 0))
491 ;; (setf end1 (or end1 (length (%children parent))))
492 ;; (setf end2 (or end2 (length seq)))
493 ;; (cond
494 ;; ((and (eql (- start1 end1) (length (%children parent)))
495 ;; (eql start2 end2))
496 ;; (do-children (loser parent)
497 ;; (fill-in-base-uri loser)
498 ;; (setf (%parent loser) nil))
499 ;; (setf (fill-pointer (%children parent)) 0))
500 ;; (t
501 ;; (call-next-method)))
502 ;; t)
504 (defun add-extra-namespace (element prefix uri)
505 "@arg[prefix]{string, an NCName}
506 @arg[uri]{string, a namespace URI}
507 @arg[element]{an instance of @class{element}}
508 @return{@code{uri}}
509 @short{Add an extra namespace to @code{element} that maps @code{prefix} to
510 @code{uri}.}
512 It is an error if the new namespace conflicts with existing namespace
513 declarations on this element."
514 (unless prefix (setf prefix ""))
515 (unless uri (setf uri ""))
516 (check-uri-like uri)
517 (unless
518 (cond
519 ((equal prefix "xmlns")
520 (unless (equal uri "")
521 (stp-error "attempt to declare `xmlns' prefix"))
523 ((equal prefix "xml")
524 (unless (equal uri "http://www.w3.org/XML/1998/namespace")
525 (stp-error "incorrect URI for `xml' namespace"))
527 ((equal uri "http://www.w3.org/XML/1998/namespace")
528 (stp-error "incorrect prefix for `xml' namespace")))
529 (cond
530 ((plusp (length prefix))
531 (check-nc-name prefix)
532 (check-namespace-uri uri))
533 ((plusp (length uri))
534 (check-namespace-uri uri)))
535 (let ((old (find-local-namespace prefix element)))
536 (when (and old (not (equal old uri)))
537 (stp-error "extra namespace conflicts with existing declarations")))
538 (unless (%namespaces element)
539 (setf (%namespaces element) (make-hash-table :test 'equal)))
540 (setf (gethash prefix (%namespaces element)) uri)
541 uri))
543 (defun remove-extra-namespace (element prefix)
544 "@arg[prefix]{string, an NCName}
545 @arg[element]{an instance of @class{element}}
546 @return{@code{uri}}
547 Removed the extra namespace declared on @code{element} for @code{prefix}."
548 (when (%namespaces element)
549 (remhash (or prefix "") (%namespaces element))))
551 (defun collect-local-namespaces (element)
552 ;; zzz ERH optimiert das noch fuer den fall nur eines ergebnisses
553 (let ((result (if (%namespaces element)
554 (alexandria:copy-hash-table (%namespaces element))
555 (make-hash-table :test 'equal))))
556 (setf (gethash (%namespace-prefix element) result)
557 (%namespace-uri element))
558 (dolist (a (%attributes element))
559 (when (plusp (length (namespace-prefix a)))
560 (setf (gethash (namespace-prefix a) result) (namespace-uri a))))
561 result))
563 (defmethod serialize ((node element) handler)
564 (let ((uri (%namespace-uri node))
565 (local-name (%local-name node))
566 (qname (qualified-name node))
567 (attrs (mapcar (lambda (a)
568 (sax:make-attribute
569 :namespace-uri (namespace-uri a)
570 :local-name (local-name a)
571 :qname (qualified-name a)
572 :value (value a)))
573 (%attributes node)))
574 (element-parent
575 (when (typep (parent node) 'element)
576 (parent node))))
577 (maphash (lambda (prefix uri)
578 (unless (equal prefix "xml")
579 (let ((upper (when element-parent
580 (find-namespace prefix element-parent))))
581 (unless (or (equal upper uri)
582 (and (null upper) (zerop (length uri))))
583 (push (if (plusp (length prefix))
584 (sax:make-attribute
585 :namespace-uri "http://www.w3.org/2000/xmlns/"
586 :local-name prefix
587 :qname (concatenate 'string "xmlns:" prefix)
588 :value uri)
589 (sax:make-attribute
590 :namespace-uri "http://www.w3.org/2000/xmlns/"
591 :local-name "xmlns"
592 :qname "xmlns"
593 :value uri))
594 attrs)))))
595 (collect-local-namespaces node))
596 (sax:start-element handler uri local-name qname attrs)
597 (map nil (lambda (x) (serialize x handler)) (%children node))
598 (sax:end-element handler uri local-name qname)))
600 (defmethod (setf base-uri) (newval (node element))
601 (setf (%base-uri node) newval))
603 (defun escape-uri (string)
604 (with-output-to-string (out)
605 (loop for c across (cxml::rod-to-utf8-string string) do
606 (let ((code (char-code c)))
607 ;; http://www.w3.org/TR/xlink/#link-locators
608 (if (or (>= code 127) (<= code 32) (find c "<>\"{}|\\^`"))
609 (format out "%~2,'0X" code)
610 (write-char c out))))))
612 (defmethod base-uri ((node element))
613 (let ((xml-base
614 (or (attribute-value node
615 "base"
616 "http://www.w3.org/XML/1998/namespace")
617 (%base-uri node)))
618 (parent (parent node)))
619 (if parent
620 (puri:render-uri (puri:merge-uris xml-base (base-uri parent)) nil)
621 xml-base)))
623 ;;; below a literal translation of XOM's Java code for BASE-URI.
624 ;;; Unfortunately I don't understand a word of what's going on here, hence
625 ;;; the trivial definition above instead.
627 ;;;(defmethod base-uri ((node element))
628 ;;; (let ((defaults "")
629 ;;; (relative-uri (%base-uri node)))
630 ;;; (loop
631 ;;; for n = node then (parent node)
632 ;;; while n
633 ;;; do
634 ;;; (let ((%base-uri (%base-uri n)))
635 ;;; (when (and (plusp (length relative-uri))
636 ;;; (not (equals relative-uri %base-uri)))
637 ;;; (return (merge-uris relative-uri defaults)))
638 ;;; (when (typep n 'document)
639 ;;; (return (merge-uris %base-uri defaults)))
640 ;;; (let ((xml-base (attribute-value
641 ;;; n
642 ;;; "base"
643 ;;; "http://www.w3.org/XML/1998/namespace")))
644 ;;; (when xml-base
645 ;;; (setf xml-base (escape-uri xml-base))
646 ;;; (cond
647 ;;; ((zerop (length xml-base))
648 ;;; (setf defaults (get-entity-uri node)))
649 ;;; (t
650 ;;; (cond
651 ;;; ((zerop (length defaults))
652 ;;; (setf defaults xml-base))
653 ;;; (...isopaque...
654 ;;; (return defaults))
655 ;;; (t
656 ;;; (setf defaults (merge-uris xml-base defaults))))
657 ;;; (when (isabsolute xml-base)
658 ;;; (return defaults)))))))
659 ;;; finally ;parent is null
660 ;;; (return (merge-uris %base-uri defaults)))))
662 (defmethod string-value ((node element))
663 (with-output-to-string (s)
664 (labels ((recurse (x)
665 (do-children (child x)
666 (typecase child
667 ((or comment processing-instruction))
668 (text (write-string (string-value child) s))
669 (element (recurse child))))))
670 (recurse node))))
673 ;;; printing
675 (defun non-empty-string (x)
676 (plusp (length x)))
678 (defmethod slots-for-print-object append ((node named-node-mixin))
679 '((:local-name local-name)
680 (:namespace-prefix namespace-prefix non-empty-string)
681 (:namespace-uri namespace-uri non-empty-string)))
683 (defun attributes-for-print (elt)
684 (sort (list-attributes elt) #'string< :key #'qualified-name))
686 (defmethod slots-for-print-object append ((node element))
687 '((:attributes attributes-for-print identity)
688 (:extra-namespaces namespaces-for-print identity)))
690 (defun namespaces-for-print (element)
691 (when (%namespaces element)
692 (loop
693 for prefix being each hash-key in (%namespaces element)
694 using (hash-value uri)
695 collect `(,prefix ,uri))))
697 (defreader named-node-mixin (local-name
698 (namespace-prefix "")
699 (namespace-uri ""))
700 (setf (%local-name this) local-name)
701 (setf (%namespace-prefix this) namespace-prefix)
702 (setf (%namespace-uri this) namespace-uri))
704 (defreader element ((attributes nil) (extra-namespaces nil))
705 (dolist (a attributes)
706 (add-attribute this a))
707 (loop for (prefix uri) in extra-namespaces do
708 (add-extra-namespace this prefix uri)))