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
9 ;;; * Redistributions of source code must retain the above copyright
10 ;;; notice, this list of conditions and the following disclaimer.
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.
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-types
)
31 (defstruct (param (:constructor make-param
(name value
)))
32 "@short{A named data type parameter.}
34 (With the XSD type library, parameters are known as restricting facets.)
35 @see-constructor{make-param}
37 @see{cxml-rng:pattern-params}
40 @see-slot{param-value}"
44 (setf (documentation 'make-param
'function
)
45 "@arg[name]{parameter name, a string}
46 @arg[value]{parameter value, a string}
47 @return{a @class{param}}
48 Create a data type parameter.
52 (setf (documentation 'param-name
'function
)
53 "@arg[instance]{an instance of @class{param}}
55 The data type parameter's name.
58 (setf (documentation 'param-value
'function
)
59 "@arg[instance]{an instance of @class{param}}
61 The data type parameter's value.
64 (defclass data-type
() ()
66 "@short{The abstract superclass of all types.}
68 Each type belongs to a datatype library, named by a keyword. In each
69 library, the types are named by strings.
71 @see-constructor{find-type}
73 @see-slot{type-library}
74 @see-slot{type-context-dependent-p}
76 @see{equal-using-type}
77 @see{lessp-using-type}
80 (defgeneric find-type
(library name params
)
82 "@arg[library]{datatype library, a keyword symbol}
83 @arg[name]{the type's name, a string}
84 @arg[params]{type parameters, a list of @class{param} instances}
85 @return{an instance of @class{data-type}, or @code{nil}}
86 @short{Look up the type named @em{name} in datatype library @em{library}.}
88 Additional parameters (knows as restricting facets in XSD) can be passed
89 to specify or restrict the type for the purposes of @fun{validp}.
91 Return a type instance for this type and the additional parameters,
92 @code{nil} if the type does not exist, or
93 @code{:error} if the type exists, but the specified parameters are not
98 (defgeneric type-library
(type)
100 "@arg[type]{an instance of @class{data-type}}
101 @return{library name, a keyword}
102 @short{Return the name of the library this type belongs to.}
105 @see{type-context-dependent-p}"))
107 (defgeneric type-name
(type)
109 "@arg[type]{an instance of @class{data-type}}
110 @return{type name, a string}
111 @short{Return the name this type has within its library.}
114 @see{type-context-dependent-p}"))
116 (defmethod find-type ((library t
) name params
)
117 (declare (ignore name params
))
120 (defgeneric type-context-dependent-p
(type)
122 "@arg[type]{an instance of @class{data-type}}
124 @short{Return true if parsing and validation of values by this type
125 depends on the validation context.}
127 In this case, the optional @code{context} argument to @fun{parse} and
128 @fun{validp} is required, and an error will be signalled if it is missing.
130 @see{validation-context}
133 @see{type-context-dependent-p}"))
135 (defmethod type-context-dependent-p ((type data-type
))
138 (defgeneric equal-using-type
(type u v
)
140 "@arg[type]{an instance of @class{data-type}}
141 @arg[u]{a parsed value as returned by @fun{parse}}
142 @arg[v]{a parsed value as returned by @fun{parse}}
144 @short{Compare the @emph{values} @code{u} and @code{v} using a
145 data-type-dependent equality function.}
149 (defgeneric parse
(type e
&optional context
)
151 "@arg[type]{an instance of @class{data-type}}
153 @arg[context]{an instance of @class{validation-context}}
155 @short{Parse string @code{e} and return a representation of its value
156 as defined by the data type.}
158 The @code{context} argument is required if @fun{type-context-dependent-p}
159 is true for @code{type}, and will be ignored otherwise.
161 @see{equal-using-type}
164 (defgeneric validp
(type e
&optional context
)
166 "@arg[type]{an instance of @class{data-type}}
168 @arg[context]{an instance of @class{validation-context}}
170 @short{Determine whether a string is a valid lexical representation
173 The @code{context} argument is required if @fun{type-context-dependent-p}
174 is true for @code{type}, and will be ignored otherwise.
177 @see{equal-using-type}"))
180 ;;; Validation context
182 (defclass validation-context
() ()
184 "@short{This abstract class defines a protocol allowing data types
185 to query the XML parser about its current state.}
187 Some types are context dependent, as indicated by
188 @fun{type-context-dependent-p}. Those types need access to state
189 computed by the XML parser implicitly, like namespace bindings or
192 User-defined subclasses must implement methods
193 for the functions @fun{context-find-namespace-binding} and
194 @fun{context-find-unparsed-entity}.
196 Two pre-defined validation context implementations are
197 provided, one for use with SAX, the other based on Klacks."))
199 (defgeneric context-find-namespace-binding
(context prefix
)
201 "@arg[context]{an instance of @class{validation-context}}
202 @arg[prefix]{name prefix, a string}
203 @return{the namespace URI as a string, or NIL}
204 @short{This function resolves a namespace prefix to a namespace URI in the
206 All currently declared namespaces
207 are taken into account, including those declared directly on the
210 (defgeneric context-find-unparsed-entity
(context name
)
212 "@arg[context]{an instance of @class{validation-context}}
213 @arg[name]{entity name, a string}
214 @return{@code{nil}, or a list of public id, system id, and notation name}
215 This function looks for an unparsed entity in the current context."))
217 (defclass klacks-validation-context
(validation-context)
218 ((source :initarg
:source
:accessor context-source
))
220 "A validation-context implementation that queries
221 a klacks source for information about the parser's current state.
222 @see-constructor{make-klacks-validation-context}"))
224 (defun make-klacks-validation-context (source)
225 "@arg[source]{a @a[http://common-lisp.net/project/cxml/klacks.html]{
227 @return{a @class{klacks-validation-context}}
228 Create a validation-context that will query the given klacks source for
229 the current parser context."
230 (make-instance 'klacks-validation-context
:source source
))
232 (defmethod context-find-namespace-binding
233 ((context klacks-validation-context
) prefix
)
234 (klacks:find-namespace-binding prefix
(context-source context
)))
237 (defmethod context-find-unparsed-entity
238 ((context klacks-validation-context
) name
)
239 (or (dolist (x (slot-value (context-source context
)
240 'cxml
::external-declarations
))
241 (when (and (eq (car x
) 'sax
:unparsed-entity-declaration
)
242 (equal (cadr x
) name
))
244 (dolist (x (slot-value (context-source context
)
245 'cxml
::internal-declarations
))
246 (when (and (eq (car x
) 'sax
:unparsed-entity-declaration
)
247 (equal (cadr x
) name
))
250 (defclass sax-validation-context-mixin
(validation-context)
251 ((stack :initform nil
:accessor context-stack
)
252 (unparsed-entities :initform
(make-hash-table :test
'equal
)
253 :accessor unparsed-entities
))
255 "@short{A class that implements validation-context as a mixin for
256 user-defined SAX handler classes.}
258 The mixin will record namespace information
259 automatically, and the user's SAX handler can simply be passed as a
260 validation context to data type functions."))
262 (defmethod sax:start-prefix-mapping
263 ((handler sax-validation-context-mixin
) prefix uri
)
264 (push (cons prefix uri
) (context-stack handler
)))
266 (defmethod sax:end-prefix-mapping
267 ((handler sax-validation-context-mixin
) prefix
)
268 (setf (context-stack handler
)
270 (context-stack handler
)
275 (defmethod sax:unparsed-entity-declaration
276 ((context sax-validation-context-mixin
)
277 name public-id system-id notation-name
)
278 (setf (gethash name
(unparsed-entities context
))
279 (list public-id system-id notation-name
)))
281 (defmethod context-find-namespace-binding
282 ((context sax-validation-context-mixin
) prefix
)
283 (cdr (assoc prefix
(context-stack context
) :test
#'equal
)))
285 (defmethod context-find-unparsed-entity
286 ((context sax-validation-context-mixin
) name
)
287 (gethash name
(unparsed-entities context
)))
290 ;;; Relax NG built-in type library
292 (defclass rng-type
(data-type) ()
294 "@short{The class of Relax NG built-in types.}
295 Relax NG defines two built-in data type: string and token.
297 The Relax NG type library is named @code{:||}."))
299 (defmethod print-object ((object rng-type
) stream
)
300 (print-unreadable-object (object stream
:type t
:identity nil
)))
302 (defclass string-type
(rng-type) ()
304 "@short{The Relax NG 'string' type.}
305 This data type allows arbitrary strings and interprets them as-is.
307 For this type, @fun{parse} will return any string unchanged, and
308 @fun{equal-using-type} compares strings using @code{equal}."))
310 (defclass token-type
(rng-type) ()
312 "@short{The Relax NG 'token' type.}
313 This data type allows arbitrary strings and normalizes all whitespaces.
315 For this type, @fun{parse} will return the string with leading and
316 trailing whitespace removed, and remaining sequences of spaces
317 compressed down to one space character each.
319 A method for @fun{equal-using-type} compares strings using @code{equal}."))
321 (defmethod type-library ((type rng-type
))
324 (defvar *string-data-type
* (make-instance 'string-type
))
325 (defvar *token-data-type
* (make-instance 'token-type
))
327 (defmethod find-type ((library (eql :||
)) name params
)
331 ((equal name
"string") *string-data-type
*)
332 ((equal name
"token") *token-data-type
*)
335 (defmethod equal-using-type ((type rng-type
) u v
)
338 (defmethod validp ((type rng-type
) e
&optional context
)
339 (declare (ignore e context
))
342 (defmethod type-name ((type string-type
)) "string")
343 (defmethod type-name ((type token-type
)) "token")
345 (defmethod parse ((type string-type
) e
&optional context
)
346 (declare (ignore context
))
349 (defmethod parse ((type token-type
) e
&optional context
)
350 (declare (ignore context
))
351 (normalize-whitespace e
))
353 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
354 (defparameter *whitespace
*
355 (format nil
"~C~C~C~C"
361 (defun normalize-whitespace (str)
362 (cl-ppcre:regex-replace-all
#.
(format nil
"[~A]+" *whitespace
*)
363 (string-trim *whitespace
* str
)
366 (defun replace-whitespace (str)
367 (cl-ppcre:regex-replace-all
#.
(format nil
"[~A]" *whitespace
*)
372 ;;; XML Schema Part 2: Datatypes Second Edition
374 (defparameter *xsd-types
* (make-hash-table :test
'equal
))
377 ((class-name type-name
) (&rest supers
) (&rest slots
) &rest args
)
379 (setf (gethash ,type-name
*xsd-types
*) ',class-name
)
380 (defclass ,class-name
,supers
381 ((type-name :initform
,type-name
387 (defgeneric patterns
(data-type)
389 "@arg[data-type]{a subtype of @class{xsd-type}}
390 @return{a list of strings}
391 This slot reader returns a list of the type's
392 @a[http://www.w3.org/TR/xmlschema-2/#rf-pattern]{pattern facets}."))
394 (defclass xsd-type
(data-type)
395 ((patterns :initform nil
:initarg
:patterns
:reader patterns
))
397 "@short{The class of XML Schema built-in types.}
399 Subclasses of xsd-type provide the built-in types of
400 @a[http://www.w3.org/TR/xmlschema-2/]{
401 XML Schema Part 2: Datatypes Second Edition}
402 as specified in @a[http://relaxng.org/xsd-20010907.html]{Guidelines for
403 using W3C XML Schema Datatypes with RELAX NG}.
406 is named @code{:|http://www.w3.org/2001/XMLSchema-datatypes|}.
408 @b{Parameters.} All XSD types accept regular expressions restricting
409 the set of strings accepted by the type. The pattern parameter is
410 called @code{\"pattern\"}. This parameter can be repeated to specify
411 multiple regular expressions that must all match the data.
412 As an initarg, specify @code{:pattern} with a list of regular expressions
415 @see-slot{patterns}"))
417 (defmethod print-object ((object xsd-type
) stream
)
418 (print-unreadable-object (object stream
:type t
:identity nil
)
419 (describe-facets object stream
)))
421 (defgeneric describe-facets
(object stream
)
422 (:method-combination progn
))
424 (defmethod describe-facets progn
((object xsd-type
) stream
)
425 (format stream
"~{ :pattern ~A~}" (patterns object
)))
427 (defmethod type-library ((type xsd-type
))
428 :|http
://www.w3.org
/2001/XMLSchema-datatypes|
)
430 (defun zip (keys values
)
431 (loop for key in keys for value in values collect key collect value
))
433 (defgeneric parse-parameter
(class-name type-name param-name value
))
435 (defun parse-parameters (type-class params
)
438 (dolist (param params
(values t patterns args
))
439 (let ((name (param-name param
))
440 (value (param-value param
)))
441 (if (equal name
"pattern")
442 (push value patterns
)
443 (multiple-value-bind (key required-class
)
444 (case (find-symbol (param-name param
) :keyword
)
445 (:|length|
(values :exact-length
'length-mixin
))
446 (:|maxLength|
(values :max-length
'length-mixin
))
447 (:|minLength|
(values :min-length
'length-mixin
))
448 (:|minInclusive|
(values :min-inclusive
'ordering-mixin
))
449 (:|maxInclusive|
(values :max-inclusive
'ordering-mixin
))
450 (:|minExclusive|
(values :min-exclusive
'ordering-mixin
))
451 (:|maxExclusive|
(values :max-exclusive
'ordering-mixin
))
452 (:|totalDigits|
(values :total-digits
'decimal-type
))
453 (:|fractionDigits|
(values :fraction-digits
'decimal-type
))
455 (unless (subtypep type-class required-class
)
458 for
(k nil
) on args by
#'cddr
461 (push (parse-parameter required-class
464 (normalize-whitespace value
))
466 (push key args
)))))))
469 ((library (eql :|http
://www.w3.org
/2001/XMLSchema-datatypes|
)) name params
)
472 (let ((class (gethash name
*xsd-types
*)))
474 (multiple-value-bind (ok patterns other-args
)
475 (parse-parameters class params
)
477 (apply #'make-instance
484 (defgeneric parse
/xsd
(type e context
))
486 (defgeneric validp
/xsd
(type v context
)
487 (:method-combination and
))
489 (defmethod validp/xsd and
((type xsd-type
) v context
)
490 (declare (ignore context
))
493 (every (lambda (pattern)
494 (cl-ppcre:all-matches pattern v
))
498 (defmethod validp ((type xsd-type
) e
&optional context
)
499 (not (eq :error
(parse/xsd type e context
))))
501 (defmethod parse ((type xsd-type
) e
&optional context
)
502 (let ((result (parse/xsd type e context
)))
503 (when (eq result
:error
)
504 (error "not valid for data type ~A: ~S" type e
))
507 ;; Handle the whiteSpace "facet" before the subclass sees it.
508 ;; If parsing succeded, check other facets by asking validp/xsd.
509 (defmethod parse/xsd
:around
((type xsd-type
) e context
)
510 (let ((result (call-next-method type
511 (munge-whitespace type e
)
513 (if (or (eq result
:error
) (validp/xsd type result context
))
517 (defgeneric munge-whitespace
(type e
))
519 (defmethod munge-whitespace ((type xsd-type
) e
)
520 (normalize-whitespace e
))
525 (defgeneric min-exclusive
(data-type)
527 "@arg[data-type]{an ordered data type}
528 @return{an integer, or @code{nil}}
529 This slot reader returns the type's
530 @a[http://www.w3.org/TR/xmlschema-2/#rf-minExclusive]{minExclusive facet},
531 or @code{nil} if none was specified.
534 @see{max-inclusive}"))
536 (defgeneric max-exclusive
(data-type)
538 "@arg[data-type]{an ordered data type}
539 @return{an integer, or @code{nil}}
540 This slot reader returns the type's
541 @a[http://www.w3.org/TR/xmlschema-2/#rf-maxExclusive]{maxExclusive facet},
542 or @code{nil} if none was specified.
545 @see{max-inclusive}"))
547 (defgeneric min-inclusive
(data-type)
549 "@arg[data-type]{an ordered data type}
550 @return{an integer, or @code{nil}}
551 This slot reader returns the type's
552 @a[http://www.w3.org/TR/xmlschema-2/#rf-minInclusive]{minInclusive facet},
553 or @code{nil} if none was specified.
556 @see{max-inclusive}"))
558 (defgeneric max-inclusive
(data-type)
560 "@arg[data-type]{an ordered data type}
561 @return{an integer, or @code{nil}}
562 This slot reader returns the type's
563 @a[http://www.w3.org/TR/xmlschema-2/#rf-maxInclusive]{maxInclusive facet},
564 or @code{nil} if none was specified.
567 @see{min-inclusive}"))
569 (defclass ordering-mixin
()
570 ((min-exclusive :initform nil
571 :initarg
:min-exclusive
572 :accessor min-exclusive
)
573 (max-exclusive :initform nil
574 :initarg
:max-exclusive
575 :accessor max-exclusive
)
576 (min-inclusive :initform nil
577 :initarg
:min-inclusive
578 :accessor min-inclusive
)
579 (max-inclusive :initform nil
580 :initarg
:max-inclusive
581 :accessor max-inclusive
)))
583 (defmethod describe-facets progn
((object ordering-mixin
) stream
)
584 (dolist (slot '(min-exclusive max-exclusive min-inclusive max-inclusive
))
585 (let ((value (slot-value object slot
)))
587 (format stream
" ~A ~A"
588 (intern (symbol-name slot
) :keyword
)
591 (defmethod parse-parameter
592 ((class-name (eql 'ordering-mixin
)) type-name
(param t
) value
)
593 (parse (make-instance type-name
) value nil
))
595 (defgeneric lessp-using-type
(type u v
)
597 "@arg[type]{an ordered @class{data-type}}
598 @arg[u]{a parsed value as returned by @fun{parse}}
599 @arg[v]{a parsed value as returned by @fun{parse}}
601 @short{Compare the @emph{values} @code{u} and @code{v} using a
602 data-type-dependent partial ordering.}
604 A method for this function is provided only by types that have a
605 natural partial ordering.
607 @see{equal-using-type}"))
609 (defun <-using-type
(type u v
)
610 (lessp-using-type type u v
))
612 (defun <=-using-type
(type u v
)
613 (or (lessp-using-type type u v
) (equal-using-type type u v
)))
615 ;; it's only a partial ordering, so in general this is not the opposite of <=
616 (defun >-using-type
(type u v
)
617 (lessp-using-type type v u
))
619 ;; it's only a partial ordering, so in general this is not the opposite of <
620 (defun >=-using-type
(type u v
)
621 (or (lessp-using-type type v u
) (equal-using-type type v u
)))
623 (defmethod validp/xsd and
((type ordering-mixin
) v context
)
624 (declare (ignore context
))
625 (with-slots (min-exclusive max-exclusive min-inclusive max-inclusive
) type
626 (and (or (null min-exclusive
) (>-using-type type v min-exclusive
))
627 (or (null max-exclusive
) (<-using-type type v max-exclusive
))
628 (or (null min-inclusive
) (>=-using-type type v min-inclusive
))
629 (or (null max-inclusive
) (<=-using-type type v max-inclusive
)))))
634 (defgeneric exact-length
(data-type)
636 "@arg[data-type]{a data type supporting restrictions on value lengths}
637 @return{an integer, or @code{nil}}
638 This slot reader returns the type's
639 @a[http://www.w3.org/TR/xmlschema-2/#rf-length]{length facet},
640 or @code{nil} if none was specified.
644 (defgeneric min-length
(data-type)
646 "@arg[data-type]{a data type supporting restrictions on value lengths}
647 @return{an integer, or @code{nil}}
648 This slot reader returns the type's
649 @a[http://www.w3.org/TR/xmlschema-2/#rf-minLength]{minLength facet},
650 or @code{nil} if none was specified.
654 (defgeneric max-length
(data-type)
656 "@arg[data-type]{a data type supporting restrictions on value lengths}
657 @return{an integer, or @code{nil}}
658 This slot reader returns the type's
659 @a[http://www.w3.org/TR/xmlschema-2/#rf-maxLength]{maxLength facet},
660 or @code{nil} if none was specified.
664 (defclass length-mixin
()
665 ((exact-length :initform nil
:initarg
:exact-length
:accessor exact-length
)
666 (min-length :initform nil
:initarg
:min-length
:accessor min-length
)
667 (max-length :initform nil
:initarg
:max-length
:accessor max-length
)))
669 (defmethod describe-facets progn
((object length-mixin
) stream
)
670 (dolist (slot '(exact-length min-length max-length
))
671 (let ((value (slot-value object slot
)))
673 (format stream
" ~A ~A"
674 (intern (symbol-name slot
) :keyword
)
677 (defmethod parse-parameter
678 ((class-name (eql 'length-mixin
)) (type-name t
) (param t
) value
)
679 (parse (make-instance 'non-negative-integer-type
) value nil
))
681 ;; extra-hack fuer die "Laenge" eines QName...
682 (defgeneric length-using-type
(type u
))
683 (defmethod length-using-type ((type length-mixin
) e
) (length e
))
685 (defmethod validp/xsd and
((type length-mixin
) v context
)
686 (declare (ignore context
))
687 (with-slots (exact-length min-length max-length
) type
688 (or (not (or exact-length min-length max-length
))
689 (let ((l (length-using-type type v
)))
690 (and (or (null exact-length
) (eql l exact-length
))
691 (or (null min-length
) (>= l min-length
))
692 (or (null max-length
) (<= l max-length
)))))))
697 (defclass enumeration-type
(xsd-type length-mixin
)
698 ((word-type :reader word-type
)))
700 (defmethod initialize-instance :after
((type enumeration-type
) &key
)
701 (setf (min-length type
) (max* 1 (min-length type
))))
703 (defmethod parse/xsd
((type enumeration-type
) e context
)
704 (let ((wt (word-type type
)))
706 for word in
(cl-ppcre:split
" " e
)
707 for v
= (parse wt word context
)
709 when
(eq v
:error
) do
(return :error
))))
717 (defxsd (duration-type "duration") (xsd-type ordering-mixin
)
720 "@short{The duration data type, representing a duration of time.}
722 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
723 the @a[http://www.w3.org/TR/xmlschema-2/#duration]{specification}.
725 @b{Implementation.} This type returns lists of the form
726 @code{(years months days hours minutes seconds)}. Each
727 value can be @code{nil} or a number. All values are integers
728 except for @code{seconds}, which is a real.
730 @b{Example.} @code{P1Y2M3DT10H30M}
731 maps to @code{(1 2 3 10 30 nil)}
733 @b{Parameters.} This type is ordered and allows the parameters
734 @slot{max-inclusive}, @slot{min-inclusive},
735 @slot{max-exclusive}, and @slot{min-exclusive}."))
737 (defmethod equal-using-type ((type duration-type
) u v
)
740 ;; zzz das ist vielleicht ein bisschen zu woertlich implementiert
741 (defmethod lessp-using-type ((type duration-type
) u v
)
742 (let ((dt (make-instance 'date-time-type
)))
744 (let ((s (parse dt str nil
)))
746 (datetime+duration s u
)
747 (datetime+duration s v
))))
748 '("1696-09-01T00:00:00Z"
749 "1697-02-01T00:00:00Z"
750 "1903-03-01T00:00:00Z"
751 "1903-07-01T00:00:00Z"))))
753 (defun datetime+duration
(s d
)
754 (destructuring-bind (syear smonth sday shour sminute ssecond szone
) s
755 (destructuring-bind (dyear dmonth dday dhour dminute dsecond
) d
756 (setf dhour
(or dhour
0))
757 (setf dminute
(or dminute
0))
758 (setf dsecond
(or dsecond
0))
759 (labels ((floor3 (a low high
)
760 (multiple-value-bind (u v
)
761 (floor (- a low
) (- high low
))
762 (values u
(+ low v
))))
763 (maximum-day-in-month-for (yearvalue monthvalue
)
764 (multiple-value-bind (m y
)
765 (floor3 monthvalue
1 13)
766 (day-limit m
(+ yearvalue y
)))))
767 (multiple-value-bind (carry emonth
) (floor3 (+ smonth dmonth
) 1 13)
768 (let ((eyear (+ syear dyear carry
))
770 (multiple-value-bind (carry esecond
) (floor (+ ssecond dsecond
) 60)
771 (multiple-value-bind (carry eminute
)
772 (floor (+ sminute dminute carry
) 60)
773 (multiple-value-bind (carry ehour
)
774 (floor (+ shour dhour carry
) 24)
775 (let* ((mdimf (maximum-day-in-month-for eyear emonth
))
776 (tmpdays (max 1 (min sday mdimf
)))
777 (eday (+ tmpdays dday carry
)))
779 (let* ((mdimf (maximum-day-in-month-for eyear emonth
))
783 (setf eday
(+ eday mdimf
))
786 (setf eday
(- eday mdimf
))
790 (tmp (+ emonth carry
)))
791 (multiple-value-bind (y m
)
795 (list eyear emonth eday ehour eminute esecond
798 (defun scan-to-strings (&rest args
)
799 (coerce (nth-value 1 (apply #'cl-ppcre
:scan-to-strings args
)) 'list
))
801 (defmethod parse/xsd
((type duration-type
) e context
)
802 (declare (ignore context
))
803 (destructuring-bind (&optional minusp y m d tp h min s
)
804 (scan-to-strings "(?x)
806 P(?:(\\d+)Y)? # years
807 (?:(\\d+)M)? # months
811 (?:(\\d+)M)? # minutes
812 (?:(\\d+(?:[.]\\d+)?)S)? # seconds
815 (if (and (or y m d h min s
)
816 (or (null tp
) (or h min s
)))
817 (let ((f (if minusp -
1 1)))
819 (and str
(* f
(parse-integer str
)))))
820 (list (int y
) (int m
) (int d
) (int h
) (int min
)
821 (and s
(* f
(parse-number:parse-number s
))))))
827 (defclass time-ordering-mixin
(ordering-mixin) ())
829 (defxsd (date-time-type "dateTime") (xsd-type time-ordering-mixin
)
832 "@short{The dateTime data type, representing a moment in time.}
834 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
835 the @a[http://www.w3.org/TR/xmlschema-2/#dateTime]{specification}.
837 @b{Implementation.} This type returns lists of the form
838 @code{(year month day hour minute second timezone)}. Each
839 value is an integer, except except for @code{second}, which is a real,
840 and @code{timezone} which is a real or @code{nil}.
841 A @code{timezone} of @code{nil} indicates UTC.
843 @b{Example.} @code{2002-10-10T12:00:00-05:00}
844 maps to @code{(2002 10 10 12 0 0 -5)}
846 @b{Parameters.} This type is ordered and allows the parameters
847 @slot{max-inclusive}, @slot{min-inclusive},
848 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
849 except within a timezone, see the spec for details."))
851 (defmethod equal-using-type ((type time-ordering-mixin
) u v
)
854 ;; add zone-offset as a duration (if any), but keep a boolean in the
855 ;; zone-offset field indicating whether there was a time-zone
856 (defun normalize-date-time (u)
857 (destructuring-bind (year month day hour minute second zone-offset
) u
858 (let ((v (list year month day hour minute second
(and zone-offset t
))))
860 (multiple-value-bind (h m
)
861 (truncate zone-offset
)
862 (datetime+timezone v h
(* m
100)))
865 (defun datetime+timezone
(d h m
)
866 (datetime+duration d
(list 0 0 0 h m
0)))
868 (defmethod lessp-using-type ((type time-ordering-mixin
) p q
)
869 (destructuring-bind (pyear pmonth pday phour pminute psecond pzone
)
870 (normalize-date-time p
)
871 (destructuring-bind (qyear qmonth qday qhour qminute qsecond qzone
)
872 (normalize-date-time q
)
874 ((and pzone
(not qzone
))
875 (lessp-using-type type p
(datetime+timezone q
14 0)))
876 ((and (not pzone
) qzone
)
877 (lessp-using-type type
(datetime+timezone p -
14 0) q
))
879 ;; zzz hier sollen wir <> liefern bei Feldern, die in genau einer
880 ;; der Zeiten fehlen. Wir stellen aber fehlende Felder derzeit
881 ;; defaulted dar, koennen diese Situation also nicht feststellen.
882 ;; Einen Unterschied sollte das nur machen, wenn Werte verschiedener
883 ;; Datentypen miteinander verglichen werden. Das bieten wir einfach
886 for a in
(list pyear pmonth pday phour pminute psecond
)
887 for b in
(list qyear qmonth qday qhour qminute qsecond
)
894 (defun day-limit (m y
)
897 (or (zerop (mod y
400))
898 (and (zerop (mod y
4))
899 (not (zerop (mod y
100))))))
902 ((if (<= m
7) (oddp m
) (evenp m
)) 31)
905 (defun parse-time (minusp y m d h min s tz tz-sign tz-h tz-m
907 (declare (ignore tz start end
)) ;zzz
908 ;; parse into numbers
910 (and str
(parse-integer str
)))
912 (and str
(parse-number:parse-number str
))))
913 (setf (values y m d h min s tz-h tz-m
)
914 (values (* (int y
) (if minusp -
1 1))
915 (int m
) (int d
) (int h
) (int min
)
917 (int tz-h
) (int tz-m
))))
918 (let ((day-limit (day-limit m y
)))
927 ;; zzz sind leap seconds immer erlaubt?
929 ;; 24:00:00 must be canonicalized
930 (when (and (eql h
24) (zerop min
) (zerop s
))
933 (when (> d day-limit
)
940 (* (if (equal tz-sign
"-") -
1 1)
941 (+ tz-h
(/ tz-m
100))))))
942 (list (* y
(if minusp -
1 1)) m d h min s tz-offset
)
943 ;; (subseq ... start end)
948 (defmethod parse/xsd
((type date-time-type
) e context
)
949 (declare (ignore context
))
950 (destructuring-bind (&optional minusp y m d h min s tz tz-sign tz-h tz-m
)
951 (scan-to-strings "(?x)
953 ((?:[1-9]\\d*)?\\d{4}) # year
959 :(\\d+(?:[.]\\d+)?) # second
960 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
963 (parse-time minusp y m d h min s tz tz-sign tz-h tz-m
)))
968 (defxsd (time-type "time") (xsd-type time-ordering-mixin
)
971 "@short{The time data type, representing a time of day.}
973 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
974 the @a[http://www.w3.org/TR/xmlschema-2/#dateTime]{specification}.
976 @b{Implementation.} This type returns the same kind of lists as
977 @class{date-time-type}, except that the fields @code{year},
978 @code{month} and @code{day} are filled with dummy values from the
981 @b{Parameters.} This type is ordered and allows the parameters
982 @slot{max-inclusive}, @slot{min-inclusive},
983 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
984 except within a timezone, see the spec for details."))
986 (defmethod parse/xsd
((type time-type
) e context
)
987 (declare (ignore context
))
988 (destructuring-bind (&optional h min s tz tz-sign tz-h tz-m
)
989 (scan-to-strings "(?x)
992 :(\\d+(?:[.]\\d+)?) # second
993 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
996 (parse-time nil
"1" "1" "1" h min s tz tz-sign tz-h tz-m
1002 (defxsd (date-type "date") (xsd-type time-ordering-mixin
)
1005 "@short{The date data type, representing a day of the year.}
1007 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1008 the @a[http://www.w3.org/TR/xmlschema-2/#date]{specification}.
1010 @b{Implementation.} This type returns the same kind of lists as
1011 @class{date-time-type}, except that the fields @code{hour},
1012 @code{minute} and @code{second} are filled with dummy values from the
1013 Gregorian year AD 1.
1015 @b{Parameters.} This type is ordered and allows the parameters
1016 @slot{max-inclusive}, @slot{min-inclusive},
1017 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1018 except within a timezone, see the spec for details."))
1020 (defmethod parse/xsd
((type date-type
) e context
)
1021 (declare (ignore context
))
1022 (destructuring-bind (&optional minusp y m d tz tz-sign tz-h tz-m
)
1023 (scan-to-strings "(?x)
1025 ((?:[1-9]\\d*)?\\d{4}) # year
1028 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
1031 (parse-time minusp y m d
"0" "0" "0" tz tz-sign tz-h tz-m
1037 (defxsd (year-month-type "gYearMonth") (xsd-type time-ordering-mixin
)
1040 "@short{The gYearMonth data type, representing the calendar month of a
1043 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1044 the @a[http://www.w3.org/TR/xmlschema-2/#gYearMonth]{specification}.
1046 @b{Implementation.} This type returns the same kind of lists as
1047 @class{date-time-type}, except that the fields @code{day}, @code{hour},
1048 @code{minute} and @code{second} are filled with dummy values from the
1049 Gregorian year AD 1.
1051 @b{Parameters.} This type is ordered and allows the parameters
1052 @slot{max-inclusive}, @slot{min-inclusive},
1053 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1054 except within a timezone, see the spec for details."))
1056 (defmethod parse/xsd
((type year-month-type
) e context
)
1057 (declare (ignore context
))
1058 (destructuring-bind (&optional minusp y m
)
1059 (scan-to-strings "(?x)
1061 ((?:[1-9]\\d*)?\\d{4}) # year
1065 (parse-time minusp y m
"1" "0" "0" "0" nil nil nil nil
1071 (defxsd (year-type "gYear") (xsd-type time-ordering-mixin
)
1074 "@short{The gYear data type, representing a calendar year.}
1076 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1077 the @a[http://www.w3.org/TR/xmlschema-2/#gYear]{specification}.
1079 @b{Implementation.} This type returns the same kind of lists as
1080 @class{date-time-type}, except that the fields @code{month}, @code{day},
1081 @code{hour}, @code{minute} and @code{second} are filled with dummy values
1082 from the Gregorian year AD 1.
1084 @b{Parameters.} This type is ordered and allows the parameters
1085 @slot{max-inclusive}, @slot{min-inclusive},
1086 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1087 except within a timezone, see the spec for details."))
1089 (defmethod parse/xsd
((type year-type
) e context
)
1090 (declare (ignore context
))
1091 (destructuring-bind (&optional minusp y tz tz-sign tz-h tz-m
)
1092 (scan-to-strings "(?x)
1094 ((?:[1-9]\\d*)?\\d{4}) # year
1095 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
1098 (parse-time minusp y
"1" "1" "0" "0" "0" tz tz-sign tz-h tz-m
1104 (defxsd (month-day-type "gMonthDay") (xsd-type time-ordering-mixin
)
1107 "@short{The gMonthDay data type, representing a calendar month and day.}
1109 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1110 the @a[http://www.w3.org/TR/xmlschema-2/#monthDay]{specification}.
1112 @b{Implementation.} This type returns the same kind of lists as
1113 @class{date-time-type}, except that the fields @code{year},
1114 @code{hour}, @code{minute} and @code{second} are filled with dummy values
1115 from the Gregorian year AD 1.
1117 @b{Parameters.} This type is ordered and allows the parameters
1118 @slot{max-inclusive}, @slot{min-inclusive},
1119 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1120 except within a timezone, see the spec for details."))
1122 (defmethod parse/xsd
((type month-day-type
) e context
)
1123 (declare (ignore context
))
1124 (destructuring-bind (&optional m d tz tz-sign tz-h tz-m
)
1125 (scan-to-strings "(?x)
1128 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
1131 (parse-time nil
"1" m d
"0" "0" "0" tz tz-sign tz-h tz-m
1137 (defxsd (day-type "gDay") (xsd-type time-ordering-mixin
)
1140 "@short{The gDay data type, representing a calendar day.}
1142 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1143 the @a[http://www.w3.org/TR/xmlschema-2/#gDay]{specification}.
1145 @b{Implementation.} This type returns the same kind of lists as
1146 @class{date-time-type}, except that the fields @code{year}, @code{month},
1147 @code{hour}, @code{minute} and @code{second} are filled with dummy values
1148 from the Gregorian year AD 1.
1150 @b{Parameters.} This type is ordered and allows the parameters
1151 @slot{max-inclusive}, @slot{min-inclusive},
1152 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1153 except within a timezone, see the spec for details."))
1155 (defmethod parse/xsd
((type day-type
) e context
)
1156 (declare (ignore context
))
1157 (destructuring-bind (&optional d tz tz-sign tz-h tz-m
)
1158 (scan-to-strings "(?x)
1160 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
1163 (parse-time nil
"1" "1" d
"0" "0" "0" tz tz-sign tz-h tz-m
1169 (defxsd (month-type "gMonth") (xsd-type time-ordering-mixin
)
1172 "@short{The gMonth data type, representing a calendar month.}
1174 @b{Syntax.} This type accepts an ISO-like syntax. For details refer to
1175 the @a[http://www.w3.org/TR/xmlschema-2/#gMonth]{specification}.
1177 @b{Implementation.} This type returns the same kind of lists as
1178 @class{date-time-type}, except that the fields @code{year}, @code{day},
1179 @code{hour}, @code{minute} and @code{second} are filled with dummy values
1180 from the Gregorian year AD 1.
1182 @b{Parameters.} This type is ordered and allows the parameters
1183 @slot{max-inclusive}, @slot{min-inclusive},
1184 @slot{max-exclusive}, and @slot{min-exclusive}. The ordering is partial
1185 except within a timezone, see the spec for details."))
1187 (defmethod parse/xsd
((type month-type
) e context
)
1188 (declare (ignore context
))
1189 (destructuring-bind (&optional m tz tz-sign tz-h tz-m
)
1190 (scan-to-strings "(?x)
1192 (([+-])(\\d\\d):(\\d\\d)|Z)? # opt timezone
1195 (parse-time nil
"1" m
"1" "0" "0" "0" tz tz-sign tz-h tz-m
1201 (defxsd (boolean-type "boolean") (xsd-type)
1204 "@short{The boolean data type.}
1206 @b{Syntax.} \"1\", \"0\", \"true\", or \"false\".
1207 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#boolean]{specification}.
1209 @b{Implementation.} This type returns @code{t} or @code{nil}.
1211 @b{Parameters.} No parameters except for @fun{pattern} are available for
1214 (defmethod parse/xsd
((type boolean-type
) e context
)
1215 (declare (ignore context
))
1216 (case (find-symbol e
:keyword
)
1218 ((:|false|
:|
0|
) nil
)))
1223 (defxsd (base64-binary-type "base64Binary") (xsd-type length-mixin
)
1226 "@short{The base64Binary data type.}
1228 @b{Syntax.} Normal Base64 syntax.
1229 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#base64Binary]{specification}.
1231 @b{Implementation.} This type returns an @code{(unsigned-byte 8)}
1234 @b{Parameters.} This type allows restrictions on the length of the octet
1235 vector through the parameters @slot{exact-length}, @slot{min-length}, and
1236 @slot{max-length}."))
1238 (defmethod equal-using-type ((type base64-binary-type
) u v
)
1241 (defmethod parse/xsd
((type base64-binary-type
) e context
)
1242 (declare (ignore context
))
1243 (if (cl-ppcre:all-matches
1245 ^(([A-Za-z0-9+/][ ]?[A-Za-z0-9+/][ ]?[A-Za-z0-9+/]
1246 [ ]?[A-Za-z0-9+/][ ]?)*
1247 (([A-Za-z0-9+/][ ]?[A-Za-z0-9+/][ ]?[A-Za-z0-9+/][ ]?[A-Za-z0-9+/])
1248 | ([A-Za-z0-9+/][ ]?[A-Za-z0-9+/][ ]?[AEIMQUYcgkosw048][ ]?=)
1249 | ([A-Za-z0-9+/][ ]?[AQgw][ ]?=[ ]?=)))?$"
1252 (cl-base64:base64-string-to-usb8-array e
)
1254 (error "unexpected failure in Base64 decoding: ~A" c
)))
1260 (defxsd (hex-binary-type "hexBinary") (xsd-type length-mixin
)
1263 "@short{The hexBinary data type.}
1265 @b{Syntax.} A sequence of two-digit hexadecimal numbers representing
1267 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#hexBinary]{specification}.
1269 @b{Implementation.} This type returns an @code{(unsigned-byte 8)}
1272 @b{Parameters.} This type allows restrictions on the length of the octet
1273 vector through the parameters @slot{exact-length}, @slot{min-length}, and
1274 @slot{max-length}."))
1276 (defmethod equal-using-type ((type hex-binary-type
) u v
)
1279 (defmethod parse/xsd
((type hex-binary-type
) e context
)
1280 (declare (ignore context
))
1281 (if (evenp (length e
))
1283 (make-array (/ (length e
) 2) :element-type
'(unsigned-byte 8))))
1285 for i from
0 below
(length e
) by
2
1288 (setf (elt result j
)
1290 (parse-integer e
:start i
:end
(+ i
2) :radix
16)
1293 finally
(return result
)))
1299 (defxsd (float-type "float") (xsd-type ordering-mixin
)
1302 "@short{The float data type.}
1304 @b{Syntax.} A floating-point number in a \"scientific notation\".
1305 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#float]{specification}.
1307 @b{Implementation.} This type returns a @code{single-float} or, on
1308 implementations where Infinity and Nan cannot be represented as such,
1309 a special symbol that is treated as if it was Infinity or NaN by the
1312 @b{Parameters.} This type is ordered and allows the parameters
1313 @slot{max-inclusive}, @slot{min-inclusive},
1314 @slot{max-exclusive}, and @slot{min-exclusive}."))
1316 (defmethod equal-using-type ((type float-type
) u v
)
1317 #+(or sbcl allegro
) (= u v
)
1318 #-
(or sbcl allegro
) (float= u v
))
1320 (defmethod lessp-using-type ((type float-type
) u v
)
1321 #+(or sbcl allegro
) (< u v
)
1322 #-
(or sbcl allegro
) (float< u v
))
1324 ;; this one is more complex than would seem necessary, because too-large
1325 ;; and too-small values must be rounded to infinity rather than erroring out
1326 (defun parse-float (e min max
+inf -inf nan
)
1328 ((equal e
"INF") +inf
)
1329 ((equal e
"-INF") -inf
)
1330 ((equal e
"Nan") nan
)
1332 (destructuring-bind (&optional a b
)
1333 (scan-to-strings "^([^eE]+)(?:[eE]([^eE]+))?$" e
)
1335 (let* ((mantissa (parse/xsd
(make-instance 'decimal-type
) a nil
))
1338 (parse/xsd
(make-instance 'integer-type
) b nil
))))
1339 (if (or (eq mantissa
:error
) (eq exponent
:error
))
1341 (let ((ratio (* mantissa
(expt 10 (or exponent
1)))))
1343 ((< ratio min
) -inf
)
1344 ((> ratio max
) +inf
)
1345 (t (float ratio min
))))))
1348 ;; zzz nehme hier an, dass single-float in IEEE single float ist.
1349 ;; Das stimmt unter LispWorks bestimmt wieder nicht.
1350 (defmethod parse/xsd
((type float-type
) e context
)
1351 (declare (ignore context
))
1353 most-negative-single-float
1354 most-positive-single-float
1355 single-float-positive-infinity
1356 single-float-negative-infinity
1362 (defgeneric fraction-digits
(data-type)
1364 "@arg[data-type]{a subtype of @class{decimal-type}}
1365 @return{an integer, or @code{nil}}
1366 This slot reader returns the type's
1367 @a[http://www.w3.org/TR/xmlschema-2/#rf-fractionDigits]{fractionDigits facet},
1368 or @code{nil} if none was specified.
1369 @see{total-digits}"))
1371 (defgeneric total-digits
(data-type)
1373 "@arg[data-type]{a subtype of @class{decimal-type}}
1374 @return{an integer, or @code{nil}}
1375 This slot reader returns the type's
1376 @a[http://www.w3.org/TR/xmlschema-2/#rf-totalDigits]{totalDigits facet},
1377 or @code{nil} if none was specified.
1378 @see{fraction-digits}"))
1380 (defxsd (decimal-type "decimal") (xsd-type ordering-mixin
)
1381 ((fraction-digits :initform nil
1382 :initarg
:fraction-digits
1383 :accessor fraction-digits
)
1384 (total-digits :initform nil
1385 :initarg
:total-digits
1386 :accessor total-digits
))
1388 "@short{The decimal data type.}
1390 @b{Syntax.} A rational number, written using an optional decimal point
1392 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#decimal]{specification}.
1394 @b{Implementation.} This type returns a @code{rational}.
1396 @b{Parameters.} This type is ordered and allows the parameters
1397 @slot{max-inclusive}, @slot{min-inclusive},
1398 @slot{max-exclusive}, and @slot{min-exclusive}.
1400 In addition, the facets @slot{fraction-digits} @slot{total-digits}
1403 (defmethod describe-facets progn
((object decimal-type
) stream
)
1404 (dolist (slot '(fraction-digits total-digits
))
1405 (let ((value (slot-value object slot
)))
1407 (format stream
" ~A ~A"
1408 (intern (symbol-name slot
) :keyword
)
1411 (defmethod parse-parameter
1412 ((class-name (eql 'decimal-type
))
1414 (param (eql :fraction-digits
))
1416 (parse (make-instance 'non-negative-integer-type
) value nil
))
1418 (defmethod parse-parameter
1419 ((class-name (eql 'decimal-type
))
1421 (param (eql :total-digits
))
1423 (parse (make-instance 'positive-integer-type
) value nil
))
1425 (defmethod lessp-using-type ((type decimal-type
) u v
)
1428 (defmethod equal-using-type ((type decimal-type
) u v
)
1431 (defmethod validp/xsd and
((type decimal-type
) v context
)
1432 (declare (ignore context
))
1433 (with-slots (fraction-digits total-digits
) type
1434 (and (or (null fraction-digits
)
1435 (let* ((betrag (abs v
))
1436 (fraction (- betrag
(truncate betrag
)))
1437 (scaled (* fraction
(expt 10 fraction-digits
))))
1438 (zerop (mod scaled
1))))
1439 (or (null total-digits
)
1440 (let ((scaled (abs v
)))
1442 until
(zerop (mod scaled
1))
1443 do
(setf scaled
(* scaled
10)))
1444 (< scaled
(expt 10 total-digits
)))))))
1446 (defmethod parse/xsd
((type decimal-type
) e context
)
1447 (declare (ignore context
))
1448 (destructuring-bind (&optional a b
)
1449 (scan-to-strings "^([+-]?\\d*)(?:[.](\\d+))?$" e
)
1450 (if (plusp (+ (length a
) (length b
)))
1451 (+ (if (plusp (length a
))
1454 (if (plusp (length b
))
1455 (/ (parse-integer b
) (expt 10 (length b
)))
1462 (defxsd (double-type "double") (xsd-type ordering-mixin
)
1465 "@short{The double data type.}
1467 @b{Syntax.} A floating-point number in a \"scientific notation\".
1468 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#double]{specification}.
1470 @b{Implementation.} This type returns a @code{double-float} or, on
1471 implementations where Infinity and Nan cannot be represented as such,
1472 a special symbol that is treated as if it was Infinity or NaN by the
1475 @b{Parameters.} This type is ordered and allows the parameters
1476 @slot{max-inclusive}, @slot{min-inclusive},
1477 @slot{max-exclusive}, and @slot{min-exclusive}."))
1479 (defmethod equal-using-type ((type double-type
) u v
)
1480 #+(or sbcl allegro
) (= u v
)
1481 #-
(or sbcl allegro
) (float= u v
))
1483 (defmethod lessp-using-type ((type double-type
) u v
)
1484 #+(or sbcl allegro
) (< u v
)
1485 #-
(or sbcl allegro
) (float< u v
))
1487 ;; zzz nehme hier an, dass double-float in IEEE double float ist.
1488 ;; Auch das ist nicht garantiert.
1489 (defmethod parse/xsd
((type double-type
) e context
)
1490 (declare (ignore context
))
1492 most-negative-double-float
1493 most-positive-double-float
1494 double-float-positive-infinity
1495 double-float-negative-infinity
1501 (defxsd (any-uri-type "anyURI") (xsd-type length-mixin
)
1504 "@short{The anyURI data type.}
1506 @b{Syntax.} An arbitrary string (!).
1507 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#anyURI]{specification}.
1509 @b{Implementation.} This type returns a normalized string in which
1510 special characters have been escaped.
1512 @b{Parameters.} This type allows restrictions on the length of the
1513 normalized string through the parameters @slot{exact-length},
1514 @slot{min-length}, and @slot{max-length}."))
1516 (defmethod equal-using-type ((type any-uri-type
) u v
)
1519 (defmethod parse/xsd
((type any-uri-type
) e context
)
1520 (cxml-rng::escape-uri e
))
1526 (defclass qname-like
(xsd-type length-mixin
) ())
1528 (defxsd (qname-type "QName") (qname-like)
1531 "@short{The QName data type.}
1533 @b{Syntax.} A Qualified Name, as per the \"Namespaces in XML\"
1534 specification. The namespace prefix must be bound to a namespace URI
1536 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#QName]{specification}.
1538 @b{Context dependent.} This type is context dependent and requires
1539 the @code{context} argument to @fun{parse} and @fun{validp}.
1541 @b{Implementation.} This type returns a structure with two components,
1542 the namespace URI and the local name. fixme: and the original length.
1543 fixme: export this structure.
1545 @b{Parameters.} This type allows restrictions on the length of the
1546 original QName through the parameters @slot{exact-length},
1547 @slot{min-length}, and @slot{max-length}."))
1549 (defxsd (notation-type "NOTATION") (qname-like)
1552 "@short{The NOTATION data type.}
1554 @b{Syntax.} A qualified name.
1555 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#NOTATION]{specification}.
1557 @b{Implementation.} This type is treated exactly like
1558 @class{qname-type}, as specified in
1559 @a[http://relaxng.org/xsd-20010907.html]{Guidelines for using W3C XML
1560 Schema Datatypes with RELAX NG}.
1562 @b{Parameters.} This type allows restrictions on the length of the
1563 original QName through the parameters @slot{exact-length},
1564 @slot{min-length}, and @slot{max-length}."))
1566 (defstruct (qname (:constructor make-qname
(uri lname length
)))
1571 (defmethod length-using-type ((type qname-like
) e
)
1574 (defmethod equal-using-type ((type qname-like
) u v
)
1575 (and (equal (qname-uri u
) (qname-uri v
))
1576 (equal (qname-lname u
) (qname-lname v
))))
1579 (and (not (zerop (length str
)))
1580 (cxml::name-start-rune-p
(elt str
0))
1581 (every #'cxml
::name-rune-p str
)))
1583 (defmethod parse/xsd
((type qname-like
) e context
)
1586 (multiple-value-bind (prefix local-name
) (cxml::split-qname e
)
1587 (let ((uri (when prefix
1588 (context-find-namespace-binding context prefix
))))
1589 (if (and prefix
(not uri
))
1591 (make-qname uri local-name
(length e
)))))
1593 (cxml:well-formedness-violation
()
1599 (defxsd (xsd-string-type "string") (xsd-type length-mixin
)
1602 "@short{The string data type.}
1604 @b{Syntax.} An arbitrary string.
1605 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#string]{specification}.
1607 @b{Implementation.} Returns the string unchanged. This is the only
1608 XSD type that does not normalize or replace whitespace.
1610 @b{Parameters.} This type allows restrictions on the length of the
1611 string through the parameters @slot{exact-length},
1612 @slot{min-length}, and @slot{max-length}."))
1614 (defmethod equal-using-type ((type xsd-string-type
) u v
)
1617 (defmethod munge-whitespace ((type xsd-string-type
) e
)
1620 (defmethod parse/xsd
((type xsd-string-type
) e context
)
1628 ;;; normalizedString
1630 (defxsd (normalized-string-type "normalizedString") (xsd-string-type)
1633 "@short{The normalizedString data type, derived from string.}
1635 @b{Syntax.} An arbitrary string.
1636 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#normalizedString]{specification}.
1638 @b{Implementation.} Returns the string with whitespace replaced.
1640 I.e., each whitespace character is replaced by a space
1641 (character code 32), but multiple spaces, as well as
1642 leading and trailing spaces will still be returned.
1644 (This is the only XSD type that replaces whitespace in this way.)
1646 @b{Parameters.} This type allows restrictions on the length of the
1647 normalized string through the parameters @slot{exact-length},
1648 @slot{min-length}, and @slot{max-length}."))
1650 (defmethod munge-whitespace ((type normalized-string-type
) e
)
1651 (replace-whitespace e
))
1656 (defxsd (xsd-token-type "token") (normalized-string-type)
1659 "@short{The token data type, derived from normalizedString.}
1661 @b{Syntax.} An arbitrary string.
1662 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#token]{specification}.
1664 @b{Implementation.} Returns the string with normalized whitespace.
1666 I.e., each whitespace character is replaced by a space
1667 (character code 32), multiple spaces are collapsed into one character,
1668 and leading and trailing spaces will be removed.
1670 (This is the standard behaviour of all XSD types with the exception of
1671 token's supertypes @class{string-type} and @class{normalized-string-type}.)
1673 @b{Parameters.} This type allows restrictions on the length of the
1674 normalized string through the parameters @slot{exact-length},
1675 @slot{min-length}, and @slot{max-length}."))
1677 (defmethod munge-whitespace ((type xsd-token-type
) e
)
1678 (normalize-whitespace e
))
1683 (defxsd (language-type "language") (xsd-token-type)
1684 ((patterns :initform
'("[a-zA-Z]{1,8}(-[a-zA-Z0-9]{1,8})*")))
1686 "@short{The language data type, derived from token.}
1688 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#language]{specification}.
1690 @b{Restrictions.} This type restricts its supertype @class{token-type}
1691 to strings of the pattern \"[a-zA-Z]{1,8@}(-[a-zA-Z0-9]{1,8@})*\".
1693 @b{Parameters and implementation.} Unchanged from the supertype."))
1698 (defxsd (name-type "Name") (xsd-token-type)
1699 ((patterns :initform
'("\\i\\c*")))
1701 "@short{The Name data type, derived from token.}
1703 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#Name]{specification}.
1705 @b{Restrictions.} This type restricts its supertype @class{token-type}
1706 to strings of the pattern \"\\i\\c*\".
1708 @b{Parameters and implementation.} Unchanged from the supertype."))
1713 (defxsd (ncname-type "NCName") (name-type)
1714 ((patterns :initform
'("[\\i-[:]][\\c-[:]]*")))
1716 "@short{The NCName data type, derived from Name.}
1718 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#NCName]{specification}.
1720 @b{Restrictions.} This type restricts its supertype @class{name-type}
1721 to strings of the pattern \"[\\i-[:]][\\c-[:]]*\".
1723 @b{Parameters and implementation.} Unchanged from the supertype."))
1725 (defmethod equal-using-type ((type ncname-type
) u v
)
1728 (defun nc-name-p (str)
1729 (and (namep str
) (cxml::nc-name-p str
)))
1731 (defmethod parse/xsd
((type ncname-type
) e context
)
1732 ;; zzz mit pattern machen
1739 (defxsd (id-type "ID") (ncname-type)
1742 "@short{The ID data type, derived from NCName.}
1744 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#ID]{specification}.
1746 @b{Restrictions.} None, except when used with DTD compatibility.
1747 See @a[http://relaxng.org/xsd-20010907.html]{Guidelines for using W3C XML
1748 Schema Datatypes with RELAX NG}.
1749 (fixme: not implemented yet -- dfl, 2007-06-06)
1751 @b{Parameters and implementation.} Unchanged from the supertype."))
1756 (defxsd (idref-type "IDREF") (id-type)
1759 "@short{The IDREF data type, derived from ID.}
1761 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#IDREF]{specification}.
1763 @b{Restrictions.} None, except when used with DTD compatibility.
1764 See @a[http://relaxng.org/xsd-20010907.html]{Guidelines for using W3C XML
1765 Schema Datatypes with RELAX NG}.
1766 (fixme: not implemented yet -- dfl, 2007-06-06)
1768 @b{Parameters and implementation.} Unchanged from the supertype."))
1773 (defxsd (idrefs-type "IDREFS") (enumeration-type)
1774 ((word-type :initform
(make-instance 'idref-type
)))
1776 "@short{The IDREFS data type, an enumeration.}
1778 @b{Syntax.} A whitespace-separated sequence of @class{idref-type}
1779 values, with at least one element.
1781 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#IDREFS]{specification}.
1783 @b{Implementation.} This type returns a list of the values as returned by
1786 @b{Parameters.} This type allows restrictions on the number of values
1787 through the parameters @slot{exact-length}, @slot{min-length}, and
1788 @slot{max-length}."))
1793 (defxsd (entity-type "ENTITY") (ncname-type)
1796 "@short{The ENTITY data type, derived from NCName.}
1798 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#ENTITY]{specification}.
1800 @b{Restrictions.} This type restricts its supertype @class{ncname-type}
1801 to names that have been declared as unparsed entities in the context.
1803 @b{Context dependent.} This type is context dependent and requires
1804 the @code{context} argument to @fun{parse} and @fun{validp}.
1806 @b{Parameters and implementation.} Unchanged from the supertype."))
1808 (defmethod parse/xsd
((type entity-type
) e context
)
1809 (if (context-find-unparsed-entity context e
)
1816 (defxsd (entities-type "ENTITIES") (enumeration-type)
1817 ((word-type :initform
(make-instance 'entity-type
)))
1819 "@short{The ENTITIES data type, an enumeration.}
1821 @b{Syntax.} A whitespace-separated sequence of @class{entity-type}
1822 values, with at least one element.
1824 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#ENTITIES]{specification}.
1826 @b{Implementation.} This type returns a list of the values as returned by
1827 @class{entity-type}.
1829 @b{Context dependent.} This type is context dependent and requires
1830 the @code{context} argument to @fun{parse} and @fun{validp}.
1832 @b{Parameters.} This type allows restrictions on the number of values
1833 through the parameters @slot{exact-length}, @slot{min-length}, and
1834 @slot{max-length}."))
1839 (defxsd (nmtoken-type "NMTOKEN") (xsd-token-type)
1840 ((patterns :initform
'("\\c+")))
1842 "@short{The NMTOKEN data type, derived from token.}
1844 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#NMTOKEN]{specification}.
1846 @b{Restrictions.} This type restricts its supertype @class{token-type}
1847 to strings of the pattern \"\\c+\".
1849 @b{Parameters and implementation.} Unchanged from the supertype."))
1854 (defxsd (nmtokens-type "NMTOKENS") (enumeration-type)
1855 ((word-type :initform
(make-instance 'nmtoken-type
)))
1857 "@short{The NMTOKENS data type, an enumeration.}
1859 @b{Syntax.} A whitespace-separated sequence of @class{nmtoken-type}
1860 values, with at least one element.
1862 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#NMTOKENS]{specification}.
1864 @b{Implementation.} This type returns a list of the values as returned by
1865 @class{nmtoken-type}.
1867 @b{Parameters.} This type allows restrictions on the number of values
1868 through the parameters @slot{exact-length}, @slot{min-length}, and
1869 @slot{max-length}."))
1874 (defxsd (integer-type "integer") (decimal-type)
1877 "@short{The integer data type, derived from decimal.}
1879 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#integer]{specification}.
1881 @b{Syntax.} An integer, written it the decimal system without leading
1882 zeros. No decimal point is permitted.
1884 @b{Implementation.} This type returns an @code{integer}.
1886 @b{Parameters and implementation.} Unchanged from the supertype."))
1888 ;; period is forbidden, so there's no point in letting decimal handle parsing
1889 ;; fixme: sind fuehrende nullen nun erlaubt oder nicht? die spec sagt ja,
1890 ;; das pattern im schema nicht.
1891 (defmethod parse/xsd
((type integer-type
) e context
)
1892 (declare (ignore context
))
1893 (if (cl-ppcre:all-matches
"^[+-]?(?:[1-9]\\d*|0)$" e
)
1894 (parse-number:parse-number e
)
1898 ;;; nonPositiveInteger
1900 (defxsd (non-positive-integer-type "nonPositiveInteger") (integer-type)
1903 "@short{The nonPositiveInteger data type, derived from integer.}
1905 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#nonPositiveInteger]{specification}.
1907 @b{Restrictions.} This type allows only values <= 0.
1909 @b{Parameters and implementation.} Unchanged from the supertype."))
1923 (defmethod initialize-instance :after
((type non-positive-integer-type
) &key
)
1924 (setf (max-inclusive type
)
1925 (min* 0 (max-inclusive type
))))
1928 ;;; nonPositiveInteger
1930 (defxsd (negative-integer-type "negativeInteger") (non-positive-integer-type)
1933 "@short{The negativeInteger data type, derived from nonPositiveInteger.}
1935 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#negativeInteger]{specification}.
1937 @b{Restrictions.} This type allows only values < 0.
1939 @b{Parameters and implementation.} Unchanged from the supertype."))
1941 (defmethod initialize-instance :after
((type negative-integer-type
) &key
)
1942 (setf (max-inclusive type
)
1943 (min* -
1 (max-inclusive type
))))
1948 (defxsd (long-type "long") (integer-type)
1951 "@short{The long data type, derived from integer.}
1953 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#long]{specification}.
1955 @b{Restrictions.} This type allows only values from the interval
1958 @b{Parameters and implementation.} Unchanged from the supertype."))
1960 (defmethod initialize-instance :after
((type long-type
) &key
)
1961 (setf (max-inclusive type
) (min* 9223372036854775807 (max-inclusive type
)))
1962 (setf (min-inclusive type
) (max* -
9223372036854775808 (min-inclusive type
))))
1967 (defxsd (int-type "int") (long-type)
1970 "@short{The int data type, derived from long.}
1972 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#int]{specification}.
1974 @b{Restrictions.} This type allows only values from the interval
1977 @b{Parameters and implementation.} Unchanged from the supertype."))
1979 (defmethod initialize-instance :after
((type int-type
) &key
)
1980 (setf (max-inclusive type
) (min* 2147483647 (max-inclusive type
)))
1981 (setf (min-inclusive type
) (max* -
2147483648 (min-inclusive type
))))
1986 (defxsd (short-type "short") (int-type)
1989 "@short{The short data type, derived from int.}
1991 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#short]{specification}.
1993 @b{Restrictions.} This type allows only values from the interval
1996 @b{Parameters and implementation.} Unchanged from the supertype."))
1998 (defmethod initialize-instance :after
((type short-type
) &key
)
1999 (setf (max-inclusive type
) (min* 32767 (max-inclusive type
)))
2000 (setf (min-inclusive type
) (max* -
32768 (min-inclusive type
))))
2005 (defxsd (byte-type "byte") (short-type)
2008 "@short{The byte data type, derived from short.}
2010 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#byte]{specification}.
2012 @b{Restrictions.} This type allows only values from the interval
2015 @b{Parameters and implementation.} Unchanged from the supertype."))
2017 (defmethod initialize-instance :after
((type byte-type
) &key
)
2018 (setf (max-inclusive type
) (min* 127 (max-inclusive type
)))
2019 (setf (min-inclusive type
) (max* -
128 (min-inclusive type
))))
2022 ;;; nonNegativeInteger
2024 (defxsd (non-negative-integer-type "nonNegativeInteger") (integer-type)
2027 "@short{The nonNegativeInteger data type, derived from integer.}
2029 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#nonNegativeInteger]{specification}.
2031 @b{Restrictions.} This type allows only values >= 0.
2033 @b{Parameters and implementation.} Unchanged from the supertype."))
2035 (defmethod initialize-instance :after
((type non-negative-integer-type
) &key
)
2036 (setf (min-inclusive type
) (max* 0 (min-inclusive type
))))
2041 (defxsd (unsigned-long-type "unsignedLong") (non-negative-integer-type)
2044 "@short{The unsignedLong data type, derived from nonNegativeInteger.}
2046 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#unsignedLong]{specification}.
2048 @b{Restrictions.} This type allows only values from the interval
2051 @b{Parameters and implementation.} Unchanged from the supertype."))
2053 (defmethod initialize-instance :after
((type unsigned-long-type
) &key
)
2054 (setf (max-inclusive type
) (min* 18446744073709551615 (max-inclusive type
))))
2059 (defxsd (unsigned-int-type "unsignedInt") (unsigned-long-type)
2062 "@short{The unsignedInt data type, derived from unsignedLong.}
2064 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#unsignedInt]{specification}.
2066 @b{Restrictions.} This type allows only values from the interval
2069 @b{Parameters and implementation.} Unchanged from the supertype."))
2071 (defmethod initialize-instance :after
((type unsigned-int-type
) &key
)
2072 (setf (max-inclusive type
) (min* 4294967295 (max-inclusive type
))))
2077 (defxsd (unsigned-short-type "unsignedShort") (unsigned-int-type)
2080 "@short{The unsignedShort data type, derived from unsignedInt.}
2082 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#unsignedShort]{specification}.
2084 @b{Restrictions.} This type allows only values from the interval
2087 @b{Parameters and implementation.} Unchanged from the supertype."))
2089 (defmethod initialize-instance :after
((type unsigned-short-type
) &key
)
2090 (setf (max-inclusive type
) (min* 65535 (max-inclusive type
))))
2095 (defxsd (unsigned-byte-type "unsignedByte") (unsigned-short-type)
2098 "@short{The unsignedByte data type, derived from unsignedInt.}
2100 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#unsignedByte]{specification}.
2102 @b{Restrictions.} This type allows only values from the interval
2105 @b{Parameters and implementation.} Unchanged from the supertype."))
2107 (defmethod initialize-instance :after
((type unsigned-byte-type
) &key
)
2108 (setf (max-inclusive type
) (min* 255 (max-inclusive type
))))
2113 (defxsd (positive-integer-type "positiveInteger") (non-negative-integer-type)
2116 "@short{The positiveInteger data type, derived from nonNegativeInteger.}
2118 C.f. the @a[http://www.w3.org/TR/xmlschema-2/#positiveInteger]{specification}.
2120 @b{Restrictions.} This type allows only values > 0.
2122 @b{Parameters and implementation.} Unchanged from the supertype."))
2124 (defmethod initialize-instance :after
((type positive-integer-type
) &key
)
2125 (setf (min-inclusive type
) (max* 1 (min-inclusive type
))))