1 ;;; -*- show-trailing-whitespace: t; indent-tabs-mode: nil -*-
3 ;;; Copyright (c) 2007,2008 David Lichteblau, Ivan Shvedunov.
4 ;;; All rights reserved.
6 ;;; Redistribution and use in source and binary forms, with or without
7 ;;; modification, are permitted provided that the following conditions
10 ;;; * Redistributions of source code must retain the above copyright
11 ;;; notice, this list of conditions and the following disclaimer.
13 ;;; * Redistributions in binary form must reproduce the above
14 ;;; copyright notice, this list of conditions and the following
15 ;;; disclaimer in the documentation and/or other materials
16 ;;; provided with the distribution.
18 ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED
19 ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
20 ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21 ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY
22 ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23 ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE
24 ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
25 ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY,
26 ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
27 ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
28 ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
30 (in-package :xuriella
)
32 (defun map-namespace-declarations (fn element
&optional include-redeclared
)
33 (let ((parent (stp:parent element
)))
34 (maphash (lambda (prefix uri
)
35 (unless (and (not include-redeclared
)
36 (typep parent
'stp
:element
)
37 (equal (stp:find-namespace prefix parent
) uri
))
38 (funcall fn prefix uri
)))
39 (cxml-stp-impl::collect-local-namespaces element
))))
41 (defun maybe-wrap-namespaces (child exprs
)
42 (if (typep child
'stp
:element
)
45 (map-namespace-declarations (lambda (prefix uri
)
46 (push (list prefix uri
) bindings
))
48 (stp:with-attributes
((erp "exclude-result-prefixes" *xsl
*))
50 (dolist (prefix (words (or erp
"")))
51 (when (equal prefix
"#default")
53 (push (or (stp:find-namespace prefix child
)
54 (xslt-error "namespace not found: ~A" prefix
))
56 (if (or bindings excluded-uris
)
57 `((xsl:with-namespaces
,bindings
58 (xsl:with-excluded-namespaces
,excluded-uris
63 (defun parse-body (node &optional
(start 0) (param-names '()))
64 (let ((n (stp:count-children-if
#'identity node
)))
67 (let ((child (stp:nth-child i node
)))
68 (if (namep child
"variable")
69 (maybe-wrap-namespaces
71 (only-with-attributes (name select
) child
72 (when (and select
(stp:list-children child
))
73 (xslt-error "variable with select and body"))
74 `((let ((,name
,(or select
75 `(progn ,@(parse-body child
)))))
76 (xsl:with-duplicates-check
(,name
)
77 ,@(recurse (1+ i
)))))))
78 (append (maybe-wrap-namespaces
80 (list (parse-instruction child
)))
81 (recurse (1+ i
))))))))
82 (let ((result (recurse start
)))
84 `((xsl:with-duplicates-check
(,@param-names
)
88 (defun parse-param (node)
90 (only-with-attributes (name select
) node
92 (xslt-error "name not specified for parameter"))
93 (when (and select
(stp:list-children node
))
94 (xslt-error "param with select and body"))
97 `(progn ,@(parse-body node
))))))
99 (defun parse-instruction (node)
104 ((equal (stp:namespace-uri node
) *xsl
*)
105 (let ((sym (find-symbol (stp:local-name node
) :xuriella
)))
108 (parse-instruction/xsl-element sym node
))
109 (*forwards-compatible-p
*
110 (parse-fallback-children node
))
112 (xslt-error "undefined instruction: ~A"
113 (stp:local-name node
))))))
114 ((find (stp:namespace-uri node
)
115 *extension-namespaces
*
117 (parse-fallback-children node
))
119 (parse-instruction/literal-element node
))))
120 (parent (stp:parent node
)))
121 (if (and (equal (stp:base-uri node
) (stp:base-uri parent
))
122 (equal (stp:namespace-uri parent
) *xsl
*)
123 (find-symbol (stp:local-name parent
) :xuriella
))
125 `(xsl:with-base-uri
,(stp:base-uri node
)
128 `(xsl:text
,(stp:data node
)))))
130 (defun parse-instruction/literal-element
(node)
131 (let ((extensions '()))
132 (stp:with-attributes
((eep "extension-element-prefixes" *xsl
*))
134 (dolist (prefix (words (or eep
"")))
135 (when (equal prefix
"#default")
137 (push (or (stp:find-namespace prefix node
)
138 (xslt-error "namespace not found: ~A" prefix
))
140 (if (find (stp:namespace-uri node
) extensions
:test
#'equal
)
141 ;; oops, this isn't a literal result element after all
142 (parse-fallback-children node
)
144 `(xsl:literal-element
145 (,(stp:local-name node
)
146 ,(stp:namespace-uri node
)
147 ,(stp:namespace-prefix node
))
148 (xsl:use-attribute-sets
149 ,(stp:attribute-value node
"use-attribute-sets" *xsl
*))
151 for a in
(stp:list-attributes node
)
152 for xslp
= (equal (stp:namespace-uri a
) *xsl
*)
154 do
(unless (find (stp:local-name a
)
156 "extension-element-prefixes"
157 "exclude-result-prefixes"
158 "use-attribute-sets")
161 "unknown attribute on literal result element: ~A"
164 collect
`(xsl:literal-attribute
166 ,(stp:namespace-uri a
)
167 ,(stp:namespace-prefix a
))
169 ,@ (let ((*extension-namespaces
*
170 (append extensions
*extension-namespaces
*)))
172 (version (stp:attribute-value node
"version" *xsl
*)))
175 `(xsl:with-extension-namespaces
,extensions
176 (xsl:with-excluded-namespaces
,extensions
180 `(xsl:with-version
,version
184 (defun parse-fallback-children (node)
187 for fallback in
(stp:filter-children
(of-name "fallback") node
)
188 do
(only-with-attributes () fallback
)
189 append
(parse-body fallback
))))
194 "no fallback children in unknown element using forwards compatible processing")))))
196 (defmacro define-instruction-parser
(name (node-var) &body body
)
198 (setf (gethash ,(symbol-name name
) *available-instructions
*) t
)
199 (defmethod parse-instruction/xsl-element
200 ((.name.
(eql ',name
)) ,node-var
)
201 (declare (ignore .name.
))
204 (define-instruction-parser |fallback|
(node)
205 (only-with-attributes () node
208 (define-instruction-parser |apply-templates|
(node)
209 (only-with-attributes (select mode
) node
210 (multiple-value-bind (decls rest
)
213 for cons on
(stp:filter-children
215 (or (typep node
'stp
:element
)
216 (xslt-error "non-element in apply-templates")))
218 for
(child . nil
) = cons
219 while
(namep child
"sort")
220 collect
(parse-sort child
) into decls
221 finally
(return (values decls cons
)))
222 `(xsl:apply-templates
223 (:select
,select
:mode
,mode
)
225 ,@(mapcar (lambda (clause)
226 (unless (namep clause
"with-param")
227 (xslt-error "undefined instruction: ~A"
228 (stp:local-name clause
)))
229 (parse-param clause
))
232 (define-instruction-parser |apply-imports|
(node)
233 (only-with-attributes () node
)
234 (assert-no-body node
)
235 `(xsl:apply-imports
))
237 (define-instruction-parser |call-template|
(node)
238 (only-with-attributes (name) node
240 ,name
,@(stp:map-children
'list
242 (if (namep clause
"with-param")
244 (xslt-error "undefined instruction: ~A"
245 (stp:local-name clause
))))
248 (define-instruction-parser |if|
(node)
249 (only-with-attributes (test) node
251 ,@(parse-body node
))))
253 (define-instruction-parser |choose|
(node)
256 (only-with-attributes () node
258 ,@(stp:map-children
'list
261 ((namep clause
"when")
263 (only-with-attributes (test) clause
265 ,@(parse-body clause
))))
266 ((namep clause
"otherwise")
267 `(t ,@(parse-body clause
)))
269 (xslt-error "invalid <choose> clause: ~A"
270 (stp:local-name clause
)))))
273 (xslt-error "<choose> without <when>")))))
275 (define-instruction-parser |element|
(node)
276 (only-with-attributes (name namespace use-attribute-sets
) node
277 `(xsl:element
(,name
:namespace
,namespace
)
278 (xsl:use-attribute-sets
,use-attribute-sets
)
279 ,@(parse-body node
))))
281 (define-instruction-parser |attribute|
(node)
282 (only-with-attributes (name namespace
) node
283 `(xsl:attribute
(,name
:namespace
,namespace
)
284 ,@(parse-body node
))))
286 (defun boolean-or-error (str)
290 ((or (null str
) (equal str
"no"))
293 (xslt-error "not a boolean: ~A" str
))))
295 (define-instruction-parser |text|
(node)
296 (only-with-attributes (select disable-output-escaping
) node
297 (when (xpath:evaluate
"boolean(*)" node
)
298 (xslt-error "non-text found in xsl:text"))
299 (if (boolean-or-error disable-output-escaping
)
300 `(xsl:unescaped-text
,(stp:string-value node
))
301 `(xsl:text
,(stp:string-value node
)))))
303 (define-instruction-parser |comment|
(node)
304 (only-with-attributes () node
305 `(xsl:comment
,@(parse-body node
))))
307 (define-instruction-parser |processing-instruction|
(node)
308 (only-with-attributes (name) node
309 `(xsl:processing-instruction
,name
310 ,@(parse-body node
))))
312 (defun assert-no-body (node)
313 (when (stp:list-children node
)
314 (xslt-error "no child nodes expected in ~A" (stp:local-name node
))))
316 (define-instruction-parser |value-of|
(node)
317 (only-with-attributes (select disable-output-escaping
) node
318 (assert-no-body node
)
319 (if (boolean-or-error disable-output-escaping
)
320 `(xsl:unescaped-value-of
,select
)
321 `(xsl:value-of
,select
))))
323 (define-instruction-parser |copy-of|
(node)
324 (only-with-attributes (select) node
325 (assert-no-body node
)
326 `(xsl:copy-of
,select
)))
328 (define-instruction-parser |copy|
(node)
329 (only-with-attributes (use-attribute-sets) node
331 (xsl:use-attribute-sets
,use-attribute-sets
)
332 ,@(parse-body node
))))
334 (define-instruction-parser |variable|
(node)
335 (xslt-error "unhandled xsl:variable"))
337 (define-instruction-parser |for-each|
(node)
338 (only-with-attributes (select) node
339 (multiple-value-bind (decls body-position
)
342 for child in
(stp:list-children node
)
343 while
(namep child
"sort")
344 collect
(parse-sort child
) into decls
345 finally
(return (values decls i
)))
346 `(xsl:for-each
,select
348 ,@(parse-body node body-position
)))))
350 (defun parse-sort (node)
351 (only-with-attributes (select lang data-type order case-order
) node
352 (assert-no-body node
)
353 `(sort :select
,select
355 :data-type
,data-type
357 :case-order
,case-order
)))
359 (define-instruction-parser |message|
(node)
360 (only-with-attributes (terminate) node
361 (if (boolean-or-error terminate
)
362 `(xsl:terminate
,@(parse-body node
))
363 `(xsl:message
,@(parse-body node
)))))
365 (define-instruction-parser |number|
(node)
366 (only-with-attributes (level count from value format lang letter-value
367 grouping-separator grouping-size
)
369 (assert-no-body node
)
370 `(xsl:number
:level
,level
376 :letter-value
,letter-value
377 :grouping-separator
,grouping-separator
378 :grouping-size
,grouping-size
)))
380 (define-instruction-parser |document|
(node)
381 (only-with-attributes
382 (href method indent doctype-public doctype-system
) node
383 `(xsl:document
(,href
:method
,method
385 :doctype-public
,doctype-public
386 :doctype-system
,doctype-system
)
387 ,@(parse-body node
))))