File Coverage

blib/lib/Types/XSD.pm
Criterion Covered Total %
statement 81 91 89.0
branch 7 10 70.0
condition 4 9 44.4
subroutine 23 25 92.0
pod 4 5 80.0
total 119 140 85.0


line stmt bran cond sub pod time code
1             package Types::XSD;
2              
3 41     41   4692295 use 5.008003;
  41         293  
4 41     41   246 use strict;
  41         92  
  41         810  
5 41     41   182 use warnings;
  41         81  
  41         974  
6 41     41   2215 use utf8;
  41         113  
  41         296  
7              
8             BEGIN {
9 41     41   1950 $Types::XSD::AUTHORITY = 'cpan:TOBYINK';
10 41         1309 $Types::XSD::VERSION = '0.007';
11             }
12              
13 41     41   316 use B qw(perlstring);
  41         94  
  41         2361  
14 41     41   295 use Carp;
  41         453  
  41         2909  
15 41     41   20796 use DateTimeX::Auto qw( dt dur );
  41         23515848  
  41         801  
16 41     41   46241 use DateTime::Incomplete ();
  41         2740803  
  41         1589  
17 41     41   25881 use Type::Utils;
  41         933975  
  41         378  
18 41         251 use Type::Library -base, -declare => qw(
19             Name NmToken NmTokens NCName Id IdRef IdRefs Entity Entities
20             QName Notation Duration DateTime Time Date GYearMonth
21             GYear GMonthDay GDay GMonth
22             DateTimeStamp YearMonthDuration DayTimeDuration
23 41     41   65282 );
  41         111  
24 41     41   140454 use Types::Standard;
  41         2070225  
  41         453  
25 41     41   49859 use Types::XSD::Lite 0.003 ();
  41         4414633  
  41         1696  
26 41     41   23781 use XML::RegExp;
  41         26412  
  41         5732  
27              
28             our @EXPORT_OK = qw( dt_cmp dur_cmp dt_parse dur_parse );
29              
30             BEGIN {
31 41     41   382 Type::Utils::extends('Types::XSD::Lite');
32            
33 41         471160 *create_range_check = \&Types::XSD::Lite::create_range_check;
34 41         138 *quick_range_check = \&Types::XSD::Lite::quick_range_check;
35 41         114 *hex_length = \&Types::XSD::Lite::hex_length;
36 41         206 *b64_length = \&Types::XSD::Lite::b64_length;
37 41         2226 *facet = \&Types::XSD::Lite::facet;
38             };
39              
40 41     41   366 use constant MAGIC_DATES => map dt($_), qw( 1696-09-01 1697-02-01 1903-03-01 1903-07-01 );
  41         99  
  41         325  
41 41     41   74223 use constant MAGIC_TABLE => +{ "-1-1-1-1" => -1, "0000" => 0, "1111" => 1 };
  41         133  
  41         112600  
42             sub dur_cmp
43             {
44 352     352 1 704218 my @durations = do {
45 352     1408   2492 local $SIG{__WARN__} = sub {};
46 352 50       2114 map ref($_) ? $_ : dur($_), @_[0,1];
47             };
48 352         131412 my $result = join q[], map "DateTime::Duration"->compare(@durations, $_), MAGIC_DATES;
49 352 50       2796988 return MAGIC_TABLE->{$result} if exists MAGIC_TABLE->{$result};
50 0         0 return undef;
51             }
52              
53             our @patterns; my $pattern_i = -1;
54             our @assertions; my $assertion_i = -1;
55             my %facets = (
56             explicitTimezone => sub {
57             my ($o, $var) = @_;
58             return unless exists $o->{explicitTimezone};
59             my $etz = delete $o->{explicitTimezone};
60             return sprintf('%s =~ m/(?:Z|(?:[+-]\d{2}:?\d{2}))$/xism', $var)
61             if lc($etz) eq 'required';
62             return sprintf('%s !~ m/(?:Z|(?:[+-]\d{2}:?\d{2}))$/xism', $var)
63             if lc($etz) eq 'prohibited';
64             return '!!1'
65             if lc($etz) eq 'optional';
66             croak "explicitTimezone facet expected to be 'required', 'prohibited' or 'optional'"
67             },
68             maxInclusiveDuration => sub {
69             my ($o, $var) = @_;
70             return unless exists $o->{maxInclusive};
71             sprintf('(Types::XSD::dur_cmp(%s, %s)||0) <= 0', $var, perlstring delete $o->{maxInclusive});
72             },
73             minInclusiveDuration => sub {
74             my ($o, $var) = @_;
75             return unless exists $o->{minInclusive};
76             sprintf('(Types::XSD::dur_cmp(%s, %s)||0) >= 0', $var, perlstring delete $o->{minInclusive});
77             },
78             maxExclusiveDuration => sub {
79             my ($o, $var) = @_;
80             return unless exists $o->{maxExclusive};
81             sprintf('(Types::XSD::dur_cmp(%s, %s)||0) < 0', $var, perlstring delete $o->{maxExclusive});
82             },
83             minExclusiveDuration => sub {
84             my ($o, $var) = @_;
85             return unless exists $o->{minExclusive};
86             sprintf('(Types::XSD::dur_cmp(%s, %s)||0) > 0', $var, perlstring delete $o->{minExclusive});
87             },
88             maxInclusiveDT => sub {
89             my ($o, $var) = @_;
90             return unless exists $o->{maxInclusive};
91             sprintf('(Types::XSD::dt_cmp(%s, %s, %s)||0) <= 0', perlstring($Types::XSD::Lite::T), $var, perlstring delete $o->{maxInclusive});
92             },
93             minInclusiveDT => sub {
94             my ($o, $var) = @_;
95             return unless exists $o->{minInclusive};
96             sprintf('(Types::XSD::dt_cmp(%s, %s, %s)||0) >= 0', perlstring($Types::XSD::Lite::T), $var, perlstring delete $o->{minInclusive});
97             },
98             maxExclusiveDT => sub {
99             my ($o, $var) = @_;
100             return unless exists $o->{maxExclusive};
101             sprintf('(Types::XSD::dt_cmp(%s, %s, %s)||0) < 0', perlstring($Types::XSD::Lite::T), $var, perlstring delete $o->{maxExclusive});
102             },
103             minExclusiveDT => sub {
104             my ($o, $var) = @_;
105             return unless exists $o->{minExclusive};
106             sprintf('(Types::XSD::dt_cmp(%s, %s, %s)||0) > 0', perlstring($Types::XSD::Lite::T), $var, perlstring delete $o->{minExclusive});
107             },
108             );
109              
110             $Types::XSD::Lite::facets{$_} = $facets{$_} for keys %facets;
111              
112             our @dtarr;
113             my $i = -1;
114             our $base_datetime = "DateTime"->new(year => 2000, month => 1, day => 1); # leap year, 31 day month
115             our %dt_regexps;
116             sub dt_maker
117             {
118 369     369 0 1283 my ($name, $regexp, @fields) = @_;
119 369         648 my $j = ++$i; $dtarr[$j] = $regexp;
  369         709  
120            
121             my $inlined = sub
122             {
123 1756     1756   3975040 my $var = $_[1];
124 1756         3147 my @code;
125 1756         3565 push @code, "do { my \$ok = 1;";
126 1756         15251 push @code, sprintf(
127             'my (%s) = (%s =~ $Types::XSD::dtarr[%d]) or --$ok;',
128             join(', ', map "\$$_", @fields),
129             $var,
130             $j,
131             );
132 1756         12017 push @code, sprintf(
133             '$ok and eval { "DateTime::Incomplete"->new(%s)->to_datetime(base => $Types::XSD::base_datetime) };',
134             join(', ', map "$_ => \$$_", @fields),
135             );
136 1756         3953 push @code, "}";
137 1756         59645 "@code";
138 369         1460 };
139            
140 369         971 my $type = "Type::Tiny"->new(
141             name => $name,
142             library => __PACKAGE__,
143             constraint => eval sprintf('sub { %s }', $inlined->(undef, '$_')),
144             inlined => $inlined,
145             );
146 369         22918 __PACKAGE__->add_type($type);
147            
148 369         149547 facet(
149             qw( pattern whiteSpace enumeration maxInclusiveDT maxExclusiveDT minInclusiveDT minExclusiveDT explicitTimezone ),
150             $type,
151             );
152            
153 369         150476 $dt_regexps{$type} = [$regexp, @fields];
154             }
155              
156             sub dt_parse
157             {
158 0     0 1 0 my ($type, $a) = @_;
159 0         0 my ($re, @fields) = @{ $dt_regexps{$type} };
  0         0  
160 0         0 my %d;
161 0         0 @d{@fields} = ($a =~ $re);
162 0   0     0 !defined($d{$_}) && delete($d{$_}) for @fields;
163 0         0 "DateTime::Incomplete"->new(%d);
164             }
165              
166             sub dur_parse
167             {
168 0     0 1 0 goto \&DateTimeX::Auto::dur;
169             }
170              
171             {
172             my %cache;
173             sub _detect_type
174             {
175 1387     1387   3111 my ($lib, $v) = @_;
176 1387         3264 for my $type (qw(DateTime Time Date GYearMonth GYear GMonthDay GDay GMonth)) {
177 6181 100       122344 return $type if $lib->get_type($type)->check($v);
178             }
179 0         0 return $lib->get_type('DateTime');
180             }
181             sub dt_cmp
182             {
183 2774     2774 1 7260173 my ($type, $a, $b) = @_;
184 2774 100       10462 $type = __PACKAGE__->_detect_type($a) unless $type;
185 2774 50       837012 $type = __PACKAGE__->get_type($type) unless ref $type;
186 2774   66     45203 my $A = eval($cache{"$type;a"} ||= $type->inline_check('$a'));
187 2774   66     1652567 my $B = eval($cache{"$type;b"} ||= $type->inline_check('$b'));
188 2774         1636355 $A <=> $B;
189             }
190             }
191              
192             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
193             declare Name, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::Name)\z}sm];
194              
195             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
196             declare NmToken, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::NmToken)\z}sm];
197              
198             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
199             declare NmTokens, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::NmToken)(?:\s+$XML::RegExp::NmToken)*\z}sm];
200              
201             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
202             declare NCName, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::NCName)\z}sm];
203              
204             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
205             declare Id, as NCName;
206              
207             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
208             declare IdRef, as NCName;
209              
210             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
211             declare IdRefs, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::NCName)(?:\s+$XML::RegExp::NCName)*\z}sm];
212              
213             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
214             declare Entity, as NCName;
215              
216             facet qw( length minLength maxLength pattern enumeration whiteSpace ),
217             declare Entities, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::NCName)(?:\s+$XML::RegExp::NCName)*\z}sm];
218              
219             facet qw( lengthQName minLengthQName maxLengthQName pattern enumeration whiteSpace ),
220             declare QName, as Types::Standard::StrMatch[qr{\A(?:$XML::RegExp::QName)\z}sm];
221              
222             facet qw( lengthQName minLengthQName maxLengthQName pattern enumeration whiteSpace ),
223             declare Notation, as QName;
224              
225             facet qw( pattern whiteSpace enumeration maxInclusiveDuration maxExclusiveDuration minInclusiveDuration minExclusiveDuration ),
226             declare Duration, as Types::Standard::StrMatch[
227             qr{\A
228             -?
229             P
230             (?:[0-9]+Y)?
231             (?:[0-9]+M)?
232             (?:[0-9]+D)?
233             (?:T
234             (?:[0-9]+H)?
235             (?:[0-9]+M)?
236             (?:[0-9]+(?:\.[0-9]+)?S)?
237             )?
238             \z}xism
239             ];
240              
241             facet qw( pattern whiteSpace enumeration maxInclusiveDuration maxExclusiveDuration minInclusiveDuration minExclusiveDuration ),
242             declare YearMonthDuration, as Duration->parameterize(pattern => qr{\A[^DT]*\z}i);
243              
244             facet qw( pattern whiteSpace enumeration maxInclusiveDuration maxExclusiveDuration minInclusiveDuration minExclusiveDuration ),
245             declare DayTimeDuration, as Duration->parameterize(pattern => qr{\A[^YM]*[DT].*\z}i);
246              
247             dt_maker(
248             DateTime => qr{\A
249             (-?[0-9]{4,})
250             -
251             ([0-9]{2})
252             -
253             ([0-9]{2})
254             T
255             ([0-9]{2})
256             :
257             ([0-9]{2})
258             :
259             ([0-9]{2}(?:\.[0-9]+)?)
260             (Z | (?: [+-]\d{2}:?\d{2} ))?
261             \z}xism,
262             qw( year month day hour minute second time_zone ),
263             );
264              
265             dt_maker(
266             DateTimeStamp => qr{\A
267             (-?[0-9]{4,})
268             -
269             ([0-9]{2})
270             -
271             ([0-9]{2})
272             T
273             ([0-9]{2})
274             :
275             ([0-9]{2})
276             :
277             ([0-9]{2}(?:\.[0-9]+)?)
278             (Z | (?: [+-]\d{2}:?\d{2} ))
279             \z}xism,
280             qw( year month day hour minute second time_zone ),
281             );
282              
283             dt_maker(
284             Time => qr{\A
285             ([0-9]{2})
286             :
287             ([0-9]{2})
288             :
289             ([0-9]{2}(?:\.[0-9]+)?)
290             (Z | (?: [+-]\d{2}:?\d{2} ))?
291             \z}xism,
292             qw( hour minute second time_zone ),
293             );
294              
295             dt_maker(
296             Date => qr{\A
297             (-?[0-9]{4,})
298             -
299             ([0-9]{2})
300             -
301             ([0-9]{2})
302             (Z | (?: [+-]\d{2}:?\d{2} ))?
303             \z}xism,
304             qw( year month day time_zone ),
305             );
306              
307             dt_maker(
308             GYearMonth => qr{\A
309             (-?[0-9]{4,})
310             -
311             ([0-9]{2})
312             (Z | (?: [+-]\d{2}:?\d{2} ))?
313             \z}xism,
314             qw( year month time_zone ),
315             );
316              
317             dt_maker(
318             GYear => qr{\A
319             (-?[0-9]{4,})
320             (Z | (?: [+-]\d{2}:?\d{2} ))?
321             \z}xism,
322             qw( year time_zone ),
323             );
324              
325             dt_maker(
326             GMonthDay => qr{\A
327             -
328             -
329             ([0-9]{2})
330             -
331             ([0-9]{2})
332             (Z | (?: [+-]\d{2}:?\d{2} ))?
333             \z}xism,
334             qw( month day time_zone ),
335             );
336              
337             dt_maker(
338             GDay => qr{\A
339             -
340             -
341             -
342             ([0-9]{2})
343             (Z | (?: [+-]\d{2}:?\d{2} ))?
344             \z}xism,
345             qw( day time_zone ),
346             );
347              
348             dt_maker(
349             GMonth => qr{\A
350             -
351             -
352             ([0-9]{2})
353             (Z | (?: [+-]\d{2}:?\d{2} ))?
354             \z}xism,
355             qw( month time_zone ),
356             );
357              
358             1;
359              
360             __END__
361              
362             =pod
363              
364             =encoding utf-8
365              
366             =head1 NAME
367              
368             Types::XSD - type constraints based on XML schema datatypes
369              
370             =head1 SYNOPSIS
371              
372             package Person;
373            
374             use Moo;
375             use Types::XSD qw( PositiveInteger String );
376            
377             has name => (is => "ro", isa => String[ minLength => 1 ]);
378             has age => (is => "ro", isa => PositiveInteger);
379              
380             =head1 DESCRIPTION
381              
382             Types::XSD is a type constraint library inspired by XML Schema, and built
383             with L<Type::Library>. It can be used as a type constraint library for
384             L<Moo>, L<Mouse> or L<Moose>, or used completely independently of any OO
385             framework.
386              
387             This module is an extension of L<Types::XSD::Lite> (which has fewer type
388             constraints, but fewer dependencies). For completeness, the type constraints
389             and other features inherited from Types::XSD::Lite are documented below
390             too.
391              
392             =head2 Type Constraints
393              
394             This module defines the following type constraints based on the data types
395             defined in L<XML Schema|http://www.w3.org/TR/xmlschema-2/>. (The names of
396             the type constraints are the same as the XML Schema data types, but
397             capitalization often differs.)
398              
399             I've added some quick explainations of what each type is, but for details,
400             see the XML Schema specification.
401              
402             =over
403              
404             =item C<< AnyType >>
405              
406             As per C<Any> from L<Types::Standard>.
407              
408             =item C<< AnySimpleType >>
409              
410             As per C<Value> from L<Types::Standard>.
411              
412             =item C<< String >>
413              
414             As per C<Str> from L<Types::Standard>.
415              
416             =item C<< NormalizedString >>
417              
418             A string containing no line breaks, carriage returns or tabs.
419              
420             =item C<< Token >>
421              
422             Like C<NormalizedString>, but also no leading or trailing space, and no
423             doubled spaces (i.e. not C<< /\s{2,}/ >>).
424              
425             =item C<< Language >>
426              
427             An RFC 3066 language code.
428              
429             =item C<< Name >>
430              
431             Something that could be a valid XML element or attribute name. These roughly
432             correspond to Perl identifiers but may also contain colons, hyphens and stops.
433             (Digits, hyphens and stops are not allowed as the first character.)
434              
435             =item C<< NmToken >>
436              
437             Slightly looser version of C<Name>; allows digits, hyphens and stops in the
438             first character.
439              
440             =item C<< NmTokens >>
441              
442             Space-separated list of C<NmToken>.
443              
444             =item C<< NCName >>
445              
446             Slightly tighter vesion of C<Name>; disallows colons.
447              
448             =item C<< Id >>
449              
450             Effectively the same as C<NCName>.
451              
452             =item C<< IdRef >>
453              
454             Effectively the same as C<NCName>.
455              
456             =item C<< IdRefs >>
457              
458             Space-separated list of C<IdRef>.
459              
460             =item C<< Entity >>
461              
462             Effectively the same as C<NCName>.
463              
464             =item C<< Entities >>
465              
466             Space-separated list of C<Entity>.
467              
468             =item C<< Boolean >>
469              
470             Allows C<< "true" >>, C<< "false" >>, C<< "1" >> and C<< "0" >>
471             (case-insensitively).
472              
473             Gotcha: The string C<< "false" >> evaluates to true in Perl. You probably
474             want to use C<< Bool >> from L<Types::Standard> instead.
475              
476             =item C<< Base64Binary >>
477              
478             Strings which are valid Base64 data. Allows whitespace.
479              
480             Gotcha: If you parameterize this with C<length>, C<maxLength> or C<minLength>,
481             it is the length of the I<decoded> string which will be checked.
482              
483             =item C<< HexBinary >>
484              
485             Strings which are valid hexadecimal data. Disallows whitespace; disallows
486             leading C<< 0x >>.
487              
488             Gotcha: If you parameterize this with C<length>, C<maxLength> or C<minLength>,
489             it is the length of the I<decoded> string which will be checked.
490              
491             =item C<< Float >>
492              
493             As per C<Num> from L<Types::Standard>.
494              
495             =item C<< Double >>
496              
497             As per C<Num> from L<Types::Standard>.
498              
499             =item C<< AnyURI >>
500              
501             Any absolute I<< or relative >> URI. Effectively, any string at all!
502              
503             =item C<< QName >>
504              
505             An XML QName; something that could be used as a valid element name in a
506             namespaced XML document.
507              
508             Gotcha: while C<length>, C<maxLength> and C<minLength> are allowed facets for
509             parameterization, they are silently ignored, as per the specification!
510              
511             =item C<< Notation >>
512              
513             Effectively the same as C<QName>. According to XML Schema, this is I<always>
514             supposed to be parameterized with an enumeration. But we don't enforce that.
515              
516             Gotcha: while C<length>, C<maxLength> and C<minLength> are allowed facets for
517             parameterization, they are silently ignored, as per the specification!
518              
519             =item C<< Decimal >>
520              
521             Numbers possibly including a decimal point, but not allowing exponential
522             notation (e.g. C<< "3.14e-3" >>).
523              
524             =item C<< Integer >>
525              
526             As per C<Int> from L<Types::Standard>.
527              
528             =item C<< NonPositiveInteger >>
529              
530             An C<Integer> 0 or below.
531              
532             =item C<< NegativeInteger >>
533              
534             An C<Integer> -1 or below.
535              
536             =item C<< Long >>
537              
538             An C<Integer> between -9223372036854775808 and 9223372036854775807 (inclusive).
539              
540             =item C<< Int >>
541              
542             An C<Integer> between -2147483648 and 2147483647 (inclusive).
543              
544             =item C<< Short >>
545              
546             An C<Integer> between -32768 and 32767 (inclusive).
547              
548             =item C<< Byte >>
549              
550             An C<Integer> between -128 and 127 (inclusive).
551              
552             =item C<< NonNegativeInteger >>
553              
554             An C<Integer> 0 or above.
555              
556             =item C<< PositiveInteger >>
557              
558             An C<Integer> 1 or above.
559              
560             =item C<< UnsignedLong >>
561              
562             A C<NonNegativeInteger> between 0 and 18446744073709551615 (inclusive).
563              
564             =item C<< UnsignedInt >>
565              
566             A C<NonNegativeInteger> between 0 and 4294967295 (inclusive).
567              
568             =item C<< UnsignedShort >>
569              
570             A C<NonNegativeInteger> between 0 and 65535 (inclusive).
571              
572             =item C<< UnsignedByte >>
573              
574             A C<NonNegativeInteger> between 0 and 255 (inclusive).
575              
576             =item C<< Duration >>
577              
578             An ISO 8601 duration.
579              
580             =item C<< YearMonthDuration >>
581              
582             An ISO 8601 duration restricted to cover only years and months.
583              
584             =item C<< DayTimeDuration >>
585              
586             An ISO 8601 duration restricted to cover only days, hours, minutes and
587             seconds. (Note that this still permits durations of many years, as the
588             days component is an arbitrary non-negative integer.)
589              
590             =item C<< DateTime >>
591              
592             An ISO 8601 datetime with optional timezone.
593              
594             =item C<< DateTimeStamp >>
595              
596             An ISO 8601 datetime with required timezone.
597              
598             =item C<< Time >>
599              
600             An ISO 8601 time with optional timezone.
601              
602             =item C<< Date >>
603              
604             An ISO 8601 date with optional timezone.
605              
606             =item C<< GYearMonth >>
607              
608             An year-month pair with optional timezone.
609              
610             =item C<< GYear >>
611              
612             An year with optional timezone.
613              
614             =item C<< GMonthDay >>
615              
616             An month-day pair with optional timezone.
617              
618             =item C<< GDay >>
619              
620             An day with optional timezone.
621              
622             =item C<< GMonth >>
623              
624             An month with optional timezone.
625              
626             =back
627              
628             =head2 Parameters
629              
630             Datatypes can be parameterized using the facets defined by XML Schema. For
631             example:
632              
633             use Types::XSD qw( String Decimal PositiveInteger Token );
634            
635             my @sizes = qw( XS S M L XL XXL );
636            
637             has name => (is => "ro", isa => String[ minLength => 1 ]);
638             has price => (is => "ro", isa => Decimal[ fractionDigits => 2 ]);
639             has rating => (is => "ro", isa => PositiveInteger[ maxInclusive => 5 ]);
640             has size => (is => "ro", isa => Token[ enumeration => \@sizes ]);
641              
642             The following facets exist, but not all facets are supported for all
643             datatypes. (The module will croak if you try to use an unsupported facet.)
644              
645             =over
646              
647             =item C<< enumeration >>
648              
649             An arrayref of allowable values. You should probably use L<Type::Tiny::Enum>
650             instead.
651              
652             =item C<< pattern >>
653              
654             A regular expression that the value is expected to conform to. Use a normal
655             Perl quoted regexp:
656              
657             Token[ pattern => qr{^[a-z]+$} ]
658              
659             =item C<< whiteSpace >>
660              
661             The C<whiteSpace> facet is ignored as I'm not entirely sure what it should
662             do. It perhaps makes sense for coercions, but this module doesn't define any
663             coercions.
664              
665             =item C<< assertions >>
666              
667             An arrayref of arbitrary additional restrictions, expressed as strings of
668             Perl code or coderefs operating on C<< $_ >>.
669              
670             For example:
671              
672             Integer[
673             assertions => [
674             '$_ % 3 == 0', # multiple of three, and...
675             sub { is_nice($_) }, # is nice (whatever that means)
676             ],
677             ],
678              
679             Strings of Perl code will result in faster-running type constraints.
680              
681             =item C<< length >>, C<< maxLength >>, C<< minLength >>
682              
683             Restrict the length of a value. For example C<< Integer[length=>2] >> allows
684             C<10>, C<99> and C<-1>, but not C<100>, C<9> or C<-10>.
685              
686             Types::XSD won't prevent you from making ridiculous constraints such as
687             C<< String[ maxLength => 1, minLength => 2 ] >>.
688              
689             Note that on C<HexBinary> and C<Base64Binary> types, the lengths apply to
690             the decoded string. Length restrictions are silently ignored for C<QName>
691             and C<Notation> because the W3C doesn't think you should care what length
692             these datatypes are.
693              
694             =item C<< maxInclusive >>, C<< minInclusive >>, C<< maxExclusive >>, C<< minExclusive >>
695              
696             Supported for numeric types and datetime/duration-related types.
697              
698             Note that to be super-correct, the C<< {max,min}{Inclusive,Exclusive} >>
699             facets for numeric types are performed by passing the numbers through
700             L<Math::BigInt> or L<Math::BigFloat>, so may be a little slow.
701              
702             =item C<< totalDigits >>
703              
704             For a decimal (or type derived from decimals) specifies that the total number
705             of digits for the value must be at most this number. Given
706             C<< Decimal[ totalDigits => 3 ] >>, C<1.23>, C<12.3>, C<123>, C<1.2> and C<1>
707             are all allowable; C<1.234> is not. C<1.230> is also not, but this may change
708             in a future version.
709              
710             =item C<< fractionDigits >>
711              
712             Like C<totalDigits> but ignores digits before the decimal point.
713              
714             =item C<< explicitTimezone >>
715              
716             May be C<< "optional" >>, C<< "prohibited" >> or C<< "required" >>. For
717             example:
718              
719             Time[ explicitTimezone => "prohibited" ]
720              
721             =back
722              
723             =head2 Functions
724              
725             This module also exports some convenience functions:
726              
727             =over
728              
729             =item C<< dur_parse($str) >>
730              
731             Parse an xsd:duration string, returning a L<DateTime::Duration>.
732              
733             =item C<< dur_cmp($a, $b) >>
734              
735             Compare two strings conforming to the xsd:duration datatype to indicate
736             which is the longer duration.
737              
738             Returns -1 if $a is shorter. Returns 1 if $b is shorter. Returns 0 if the
739             durations are identical. Returns undef if the comparison is indeterminate;
740             for example, "P1Y" (one year) and "P365D" (365 days) are not necessarily
741             identical - in leap years "P365D" is shorter.
742              
743             =item C<< dt_cmp($type, $a, $b) >>
744              
745             Compare two datetime-like strings. For example, two C<gYearMonth> strings
746             can be compared using:
747              
748             dt_cmp(GYearMonth, "2009-02", "2010-10");
749              
750             Both strings are expected to conform to the same datatype. It doesn't make
751             much sense to compare them otherwise.
752              
753             =item C<< dt_parse($type, $str) >>
754              
755             Parse a datetime-like string, returning a L<DateTime::Incomplete> object.
756             Note that L<DateTime::Incomplete> objects are always returned, even if the
757             datetime is potentially complete.
758              
759             =back
760              
761             =head1 BUGS
762              
763             Please report any bugs to
764             L<http://rt.cpan.org/Dist/Display.html?Queue=Types-XSD>.
765              
766             =head1 SEE ALSO
767              
768             L<Type::Tiny>, L<Types::XSD::Lite>, L<Types::Standard>.
769              
770             =over
771              
772             =item *
773              
774             L<http://www.w3.org/TR/xmlschema-2/> Datatypes in XML Schema 1.0
775              
776             =item *
777              
778             L<http://www.w3.org/TR/xmlschema11-2/> Datatypes in XML Schema 1.1
779              
780             =back
781              
782             =head1 AUTHOR
783              
784             Toby Inkster E<lt>tobyink@cpan.orgE<gt>.
785              
786             =head1 COPYRIGHT AND LICENCE
787              
788             This software is copyright (c) 2013-2014, 2021 by Toby Inkster.
789              
790             This is free software; you can redistribute it and/or modify it under
791             the same terms as the Perl 5 programming language system itself.
792              
793             =head1 DISCLAIMER OF WARRANTIES
794              
795             THIS PACKAGE IS PROVIDED "AS IS" AND WITHOUT ANY EXPRESS OR IMPLIED
796             WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED WARRANTIES OF
797             MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
798