1/*
2  date_parse.c: Coded by Tadayoshi Funaba 2011,2012
3*/
4
5#include "ruby.h"
6#include "ruby/encoding.h"
7#include "ruby/re.h"
8#include <ctype.h>
9
10/* #define TIGHT_PARSER */
11
12#define sizeof_array(o) (sizeof o / sizeof o[0])
13
14#define f_negate(x) rb_funcall(x, rb_intern("-@"), 0)
15#define f_add(x,y) rb_funcall(x, '+', 1, y)
16#define f_sub(x,y) rb_funcall(x, '-', 1, y)
17#define f_mul(x,y) rb_funcall(x, '*', 1, y)
18#define f_div(x,y) rb_funcall(x, '/', 1, y)
19#define f_idiv(x,y) rb_funcall(x, rb_intern("div"), 1, y)
20#define f_mod(x,y) rb_funcall(x, '%', 1, y)
21#define f_expt(x,y) rb_funcall(x, rb_intern("**"), 1, y)
22
23#define f_lt_p(x,y) rb_funcall(x, '<', 1, y)
24#define f_gt_p(x,y) rb_funcall(x, '>', 1, y)
25#define f_le_p(x,y) rb_funcall(x, rb_intern("<="), 1, y)
26#define f_ge_p(x,y) rb_funcall(x, rb_intern(">="), 1, y)
27
28#define f_to_s(x) rb_funcall(x, rb_intern("to_s"), 0)
29
30#define f_match(r,s) rb_funcall(r, rb_intern("match"), 1, s)
31#define f_aref(o,i) rb_funcall(o, rb_intern("[]"), 1, i)
32#define f_aref2(o,i,j) rb_funcall(o, rb_intern("[]"), 2, i, j)
33#define f_begin(o,i) rb_funcall(o, rb_intern("begin"), 1, i)
34#define f_end(o,i) rb_funcall(o, rb_intern("end"), 1, i)
35#define f_aset(o,i,v) rb_funcall(o, rb_intern("[]="), 2, i, v)
36#define f_aset2(o,i,j,v) rb_funcall(o, rb_intern("[]="), 3, i, j, v)
37#define f_sub_bang(s,r,x) rb_funcall(s, rb_intern("sub!"), 2, r, x)
38#define f_gsub_bang(s,r,x) rb_funcall(s, rb_intern("gsub!"), 2, r, x)
39
40#define set_hash(k,v) rb_hash_aset(hash, ID2SYM(rb_intern(k)), v)
41#define ref_hash(k) rb_hash_aref(hash, ID2SYM(rb_intern(k)))
42#define del_hash(k) rb_hash_delete(hash, ID2SYM(rb_intern(k)))
43
44#define cstr2num(s) rb_cstr_to_inum(s, 10, 0)
45#define str2num(s) rb_str_to_inum(s, 10, 0)
46
47static const char *abbr_days[] = {
48    "sun", "mon", "tue", "wed",
49    "thu", "fri", "sat"
50};
51
52static const char *abbr_months[] = {
53    "jan", "feb", "mar", "apr", "may", "jun",
54    "jul", "aug", "sep", "oct", "nov", "dec"
55};
56
57#define issign(c) ((c) == '-' || (c) == '+')
58#define asp_string() rb_str_new(" ", 1)
59#ifdef TIGHT_PARSER
60#define asuba_string() rb_str_new("\001", 1)
61#define asubb_string() rb_str_new("\002", 1)
62#define asubw_string() rb_str_new("\027", 1)
63#define asubt_string() rb_str_new("\024", 1)
64#endif
65
66#define DECDIGIT "0123456789"
67
68static void
69s3e(VALUE hash, VALUE y, VALUE m, VALUE d, int bc)
70{
71    VALUE c = Qnil;
72
73    if (TYPE(m) != T_STRING)
74	m = f_to_s(m);
75
76    if (!NIL_P(y) && !NIL_P(m) && NIL_P(d)) {
77	VALUE oy = y;
78	VALUE om = m;
79	VALUE od = d;
80
81	y = od;
82	m = oy;
83	d = om;
84    }
85
86    if (NIL_P(y)) {
87	if (!NIL_P(d) && RSTRING_LEN(d) > 2) {
88	    y = d;
89	    d = Qnil;
90	}
91	if (!NIL_P(d) && *RSTRING_PTR(d) == '\'') {
92	    y = d;
93	    d = Qnil;
94	}
95    }
96
97    if (!NIL_P(y)) {
98	const char *s, *bp, *ep;
99	size_t l;
100
101	s = RSTRING_PTR(y);
102	while (!issign((unsigned char)*s) && !isdigit((unsigned char)*s))
103	    s++;
104	bp = s;
105	if (issign((unsigned char)*s))
106	    s++;
107	l = strspn(s, DECDIGIT);
108	ep = s + l;
109	if (*ep) {
110	    y = d;
111	    d = rb_str_new(bp, ep - bp);
112	}
113    }
114
115    if (!NIL_P(m)) {
116	const char *s;
117
118	s = RSTRING_PTR(m);
119	if (*s == '\'' || RSTRING_LEN(m) > 2) {
120	    /* us -> be */
121	    VALUE oy = y;
122	    VALUE om = m;
123	    VALUE od = d;
124
125	    y = om;
126	    m = od;
127	    d = oy;
128	}
129    }
130
131    if (!NIL_P(d)) {
132	const char *s;
133
134	s = RSTRING_PTR(d);
135	if (*s == '\'' || RSTRING_LEN(d) > 2) {
136	    VALUE oy = y;
137	    VALUE od = d;
138
139	    y = od;
140	    d = oy;
141	}
142    }
143
144    if (!NIL_P(y)) {
145	const char *s, *bp, *ep;
146	int sign = 0;
147	size_t l;
148	VALUE iy;
149
150	s = RSTRING_PTR(y);
151	while (!issign((unsigned char)*s) && !isdigit((unsigned char)*s))
152	    s++;
153	bp = s;
154	if (issign(*s)) {
155	    s++;
156	    sign = 1;
157	}
158	if (sign)
159	    c = Qfalse;
160	l = strspn(s, DECDIGIT);
161	ep = s + l;
162	if (l > 2)
163	    c = Qfalse;
164	{
165	    char *buf;
166
167	    buf = ALLOCA_N(char, ep - bp + 1);
168	    memcpy(buf, bp, ep - bp);
169	    buf[ep - bp] = '\0';
170	    iy = cstr2num(buf);
171	}
172	set_hash("year", iy);
173    }
174
175    if (bc)
176	set_hash("_bc", Qtrue);
177
178    if (!NIL_P(m)) {
179	const char *s, *bp, *ep;
180	size_t l;
181	VALUE im;
182
183	s = RSTRING_PTR(m);
184	while (!isdigit((unsigned char)*s))
185	    s++;
186	bp = s;
187	l = strspn(s, DECDIGIT);
188	ep = s + l;
189	{
190	    char *buf;
191
192	    buf = ALLOCA_N(char, ep - bp + 1);
193	    memcpy(buf, bp, ep - bp);
194	    buf[ep - bp] = '\0';
195	    im = cstr2num(buf);
196	}
197	set_hash("mon", im);
198    }
199
200    if (!NIL_P(d)) {
201	const char *s, *bp, *ep;
202	size_t l;
203	VALUE id;
204
205	s = RSTRING_PTR(d);
206	while (!isdigit((unsigned char)*s))
207	    s++;
208	bp = s;
209	l = strspn(s, DECDIGIT);
210	ep = s + l;
211	{
212	    char *buf;
213
214	    buf = ALLOCA_N(char, ep - bp + 1);
215	    memcpy(buf, bp, ep - bp);
216	    buf[ep - bp] = '\0';
217	    id = cstr2num(buf);
218	}
219	set_hash("mday", id);
220    }
221
222    if (!NIL_P(c))
223	set_hash("_comp", c);
224}
225
226#define DAYS "sunday|monday|tuesday|wednesday|thursday|friday|saturday"
227#define MONTHS "january|february|march|april|may|june|july|august|september|october|november|december"
228#define ABBR_DAYS "sun|mon|tue|wed|thu|fri|sat"
229#define ABBR_MONTHS "jan|feb|mar|apr|may|jun|jul|aug|sep|oct|nov|dec"
230
231#ifdef TIGHT_PARSER
232#define VALID_DAYS "(?:" DAYS ")" "|(?:tues|wednes|thurs|thur|" ABBR_DAYS ")\\.?"
233#define VALID_MONTHS "(?:" MONTHS ")" "|(?:sept|" ABBR_MONTHS ")\\.?"
234#define DOTLESS_VALID_MONTHS "(?:" MONTHS ")" "|(?:sept|" ABBR_MONTHS ")"
235#define BOS "\\A\\s*"
236#define FPA "\\001"
237#define FPB "\\002"
238#define FPW "\\027"
239#define FPT "\\024"
240#define FPW_COM "\\s*(?:" FPW "\\s*,?)?\\s*"
241#define FPT_COM "\\s*(?:" FPT "\\s*,?)?\\s*"
242#define COM_FPW "\\s*(?:,?\\s*" FPW ")?\\s*"
243#define COM_FPT "\\s*(?:,?\\s*(?:@|\\b[aA][tT]\\b)?\\s*" FPT ")?\\s*"
244#define TEE_FPT "\\s*(?:[tT]?" FPT ")?"
245#define EOS "\\s*\\z"
246#endif
247
248static VALUE
249regcomp(const char *source, long len, int opt)
250{
251    VALUE pat;
252
253    pat = rb_reg_new(source, len, opt);
254    rb_gc_register_mark_object(pat);
255    return pat;
256}
257
258#define REGCOMP(pat,opt) \
259{ \
260    if (NIL_P(pat)) \
261	pat = regcomp(pat##_source, sizeof pat##_source - 1, opt); \
262}
263
264#define REGCOMP_0(pat) REGCOMP(pat, 0)
265#define REGCOMP_I(pat) REGCOMP(pat, ONIG_OPTION_IGNORECASE)
266
267#define MATCH(s,p,c) \
268{ \
269    return match(s, p, hash, c); \
270}
271
272static int
273match(VALUE str, VALUE pat, VALUE hash, int (*cb)(VALUE, VALUE))
274{
275    VALUE m;
276
277    m = f_match(pat, str);
278
279    if (NIL_P(m))
280	return 0;
281
282    (*cb)(m, hash);
283
284    return 1;
285}
286
287static int
288subx(VALUE str, VALUE rep, VALUE pat, VALUE hash, int (*cb)(VALUE, VALUE))
289{
290    VALUE m;
291
292    m = f_match(pat, str);
293
294    if (NIL_P(m))
295	return 0;
296
297    {
298	VALUE be, en;
299
300	be = f_begin(m, INT2FIX(0));
301	en = f_end(m, INT2FIX(0));
302	f_aset2(str, be, LONG2NUM(NUM2LONG(en) - NUM2LONG(be)), rep);
303	(*cb)(m, hash);
304    }
305
306    return 1;
307}
308
309#define SUBS(s,p,c) \
310{ \
311    return subx(s, asp_string(), p, hash, c); \
312}
313
314#ifdef TIGHT_PARSER
315#define SUBA(s,p,c) \
316{ \
317    return subx(s, asuba_string(), p, hash, c); \
318}
319
320#define SUBB(s,p,c) \
321{ \
322    return subx(s, asubb_string(), p, hash, c); \
323}
324
325#define SUBW(s,p,c) \
326{ \
327    return subx(s, asubw_string(), p, hash, c); \
328}
329
330#define SUBT(s,p,c) \
331{ \
332    return subx(s, asubt_string(), p, hash, c); \
333}
334#endif
335
336struct zone {
337    const char *name;
338    int offset;
339};
340
341static struct zone zones_source[] = {
342    {"ut",   0*3600}, {"gmt",  0*3600}, {"est", -5*3600}, {"edt", -4*3600},
343    {"cst", -6*3600}, {"cdt", -5*3600}, {"mst", -7*3600}, {"mdt", -6*3600},
344    {"pst", -8*3600}, {"pdt", -7*3600},
345    {"a",    1*3600}, {"b",    2*3600}, {"c",    3*3600}, {"d",    4*3600},
346    {"e",    5*3600}, {"f",    6*3600}, {"g",    7*3600}, {"h",    8*3600},
347    {"i",    9*3600}, {"k",   10*3600}, {"l",   11*3600}, {"m",   12*3600},
348    {"n",   -1*3600}, {"o",   -2*3600}, {"p",   -3*3600}, {"q",   -4*3600},
349    {"r",   -5*3600}, {"s",   -6*3600}, {"t",   -7*3600}, {"u",   -8*3600},
350    {"v",   -9*3600}, {"w",  -10*3600}, {"x",  -11*3600}, {"y",  -12*3600},
351    {"z",    0*3600},
352
353    {"utc",  0*3600}, {"wet",  0*3600},
354    {"at",  -2*3600}, {"brst",-2*3600}, {"ndt", -(2*3600+1800)},
355    {"art", -3*3600}, {"adt", -3*3600}, {"brt", -3*3600}, {"clst",-3*3600},
356    {"nst", -(3*3600+1800)},
357    {"ast", -4*3600}, {"clt", -4*3600},
358    {"akdt",-8*3600}, {"ydt", -8*3600},
359    {"akst",-9*3600}, {"hadt",-9*3600}, {"hdt", -9*3600}, {"yst", -9*3600},
360    {"ahst",-10*3600},{"cat",-10*3600}, {"hast",-10*3600},{"hst",-10*3600},
361    {"nt",  -11*3600},
362    {"idlw",-12*3600},
363    {"bst",  1*3600}, {"cet",  1*3600}, {"fwt",  1*3600}, {"met",  1*3600},
364    {"mewt", 1*3600}, {"mez",  1*3600}, {"swt",  1*3600}, {"wat",  1*3600},
365    {"west", 1*3600},
366    {"cest", 2*3600}, {"eet",  2*3600}, {"fst",  2*3600}, {"mest", 2*3600},
367    {"mesz", 2*3600}, {"sast", 2*3600}, {"sst",  2*3600},
368    {"bt",   3*3600}, {"eat",  3*3600}, {"eest", 3*3600}, {"msk",  3*3600},
369    {"msd",  4*3600}, {"zp4",  4*3600},
370    {"zp5",  5*3600}, {"ist",  (5*3600+1800)},
371    {"zp6",  6*3600},
372    {"wast", 7*3600},
373    {"cct",  8*3600}, {"sgt",  8*3600}, {"wadt", 8*3600},
374    {"jst",  9*3600}, {"kst",  9*3600},
375    {"east",10*3600}, {"gst", 10*3600},
376    {"eadt",11*3600},
377    {"idle",12*3600}, {"nzst",12*3600}, {"nzt", 12*3600},
378    {"nzdt",13*3600},
379
380    {"afghanistan",             16200}, {"alaskan",                -32400},
381    {"arab",                    10800}, {"arabian",                 14400},
382    {"arabic",                  10800}, {"atlantic",               -14400},
383    {"aus central",             34200}, {"aus eastern",             36000},
384    {"azores",                  -3600}, {"canada central",         -21600},
385    {"cape verde",              -3600}, {"caucasus",                14400},
386    {"cen. australia",          34200}, {"central america",        -21600},
387    {"central asia",            21600}, {"central europe",           3600},
388    {"central european",         3600}, {"central pacific",         39600},
389    {"central",                -21600}, {"china",                   28800},
390    {"dateline",               -43200}, {"e. africa",               10800},
391    {"e. australia",            36000}, {"e. europe",                7200},
392    {"e. south america",       -10800}, {"eastern",                -18000},
393    {"egypt",                    7200}, {"ekaterinburg",            18000},
394    {"fiji",                    43200}, {"fle",                      7200},
395    {"greenland",              -10800}, {"greenwich",                   0},
396    {"gtb",                      7200}, {"hawaiian",               -36000},
397    {"india",                   19800}, {"iran",                    12600},
398    {"jerusalem",                7200}, {"korea",                   32400},
399    {"mexico",                 -21600}, {"mid-atlantic",            -7200},
400    {"mountain",               -25200}, {"myanmar",                 23400},
401    {"n. central asia",         21600}, {"nepal",                   20700},
402    {"new zealand",             43200}, {"newfoundland",           -12600},
403    {"north asia east",         28800}, {"north asia",              25200},
404    {"pacific sa",             -14400}, {"pacific",                -28800},
405    {"romance",                  3600}, {"russian",                 10800},
406    {"sa eastern",             -10800}, {"sa pacific",             -18000},
407    {"sa western",             -14400}, {"samoa",                  -39600},
408    {"se asia",                 25200}, {"malay peninsula",         28800},
409    {"south africa",             7200}, {"sri lanka",               21600},
410    {"taipei",                  28800}, {"tasmania",                36000},
411    {"tokyo",                   32400}, {"tonga",                   46800},
412    {"us eastern",             -18000}, {"us mountain",            -25200},
413    {"vladivostok",             36000}, {"w. australia",            28800},
414    {"w. central africa",        3600}, {"w. europe",                3600},
415    {"west asia",               18000}, {"west pacific",            36000},
416    {"yakutsk",                 32400}
417};
418
419VALUE
420date_zone_to_diff(VALUE str)
421{
422    VALUE offset = Qnil;
423
424    long l, i;
425    char *s, *dest, *d;
426    int sp = 1;
427
428    l = RSTRING_LEN(str);
429    s = RSTRING_PTR(str);
430
431    dest = d = ALLOCA_N(char, l + 1);
432
433    for (i = 0; i < l; i++) {
434	if (isspace((unsigned char)s[i]) || s[i] == '\0') {
435	    if (!sp)
436		*d++ = ' ';
437	    sp = 1;
438	}
439	else {
440	    if (isalpha((unsigned char)s[i]))
441		*d++ = tolower((unsigned char)s[i]);
442	    else
443		*d++ = s[i];
444	    sp = 0;
445	}
446    }
447    if (d > dest) {
448	if (*(d - 1) == ' ')
449	    --d;
450	*d = '\0';
451    }
452    str = rb_str_new2(dest);
453    {
454#define STD " standard time"
455#define DST " daylight time"
456	char *ss, *ds;
457	long sl, dl;
458	int dst = 0;
459
460	sl = RSTRING_LEN(str) - (sizeof STD - 1);
461	ss = RSTRING_PTR(str) + sl;
462	dl = RSTRING_LEN(str) - (sizeof DST - 1);
463	ds = RSTRING_PTR(str) + dl;
464
465	if (sl >= 0 && strcmp(ss, STD) == 0) {
466	    str = rb_str_new(RSTRING_PTR(str), sl);
467	}
468	else if (dl >= 0 && strcmp(ds, DST) == 0) {
469	    str = rb_str_new(RSTRING_PTR(str), dl);
470	    dst = 1;
471	}
472#undef STD
473#undef DST
474	else {
475#define DST " dst"
476	    char *ds;
477	    long dl;
478
479	    dl = RSTRING_LEN(str) - (sizeof DST - 1);
480	    ds = RSTRING_PTR(str) + dl;
481
482	    if (dl >= 0 && strcmp(ds, DST) == 0) {
483		str = rb_str_new(RSTRING_PTR(str), dl);
484		dst = 1;
485	    }
486#undef DST
487	}
488	{
489	    static VALUE zones = Qnil;
490
491	    if (NIL_P(zones)) {
492		int i;
493
494		zones = rb_hash_new();
495		rb_gc_register_mark_object(zones);
496		for (i = 0; i < (int)sizeof_array(zones_source); i++) {
497		    VALUE name = rb_str_new2(zones_source[i].name);
498		    VALUE offset = INT2FIX(zones_source[i].offset);
499		    rb_hash_aset(zones, name, offset);
500		}
501	    }
502
503	    offset = f_aref(zones, str);
504	    if (!NIL_P(offset)) {
505		if (dst)
506		    offset = f_add(offset, INT2FIX(3600));
507		goto ok;
508	    }
509	}
510	{
511	    char *s, *p;
512	    VALUE sign;
513	    VALUE hour = Qnil, min = Qnil, sec = Qnil;
514	    VALUE str_orig;
515
516	    s = RSTRING_PTR(str);
517	    str_orig = str;
518
519	    if (strncmp(s, "gmt", 3) == 0 ||
520		strncmp(s, "utc", 3) == 0)
521		s += 3;
522	    if (issign(*s)) {
523		sign = rb_str_new(s, 1);
524		s++;
525
526		str = rb_str_new2(s);
527
528		if (p = strchr(s, ':')) {
529		    hour = rb_str_new(s, p - s);
530		    s = ++p;
531		    if (p = strchr(s, ':')) {
532			min = rb_str_new(s, p - s);
533			s = ++p;
534			if (p = strchr(s, ':')) {
535			    sec = rb_str_new(s, p - s);
536			}
537			else
538			    sec = rb_str_new2(s);
539		    }
540		    else
541			min = rb_str_new2(s);
542		    RB_GC_GUARD(str_orig);
543		    goto num;
544		}
545		if (strpbrk(RSTRING_PTR(str), ",.")) {
546		    char *a, *b;
547
548		    a = ALLOCA_N(char, RSTRING_LEN(str) + 1);
549		    strcpy(a, RSTRING_PTR(str));
550		    b = strpbrk(a, ",.");
551		    *b = '\0';
552		    b++;
553
554		    hour = cstr2num(a);
555		    min = f_mul(rb_rational_new2
556				(cstr2num(b),
557				 f_expt(INT2FIX(10),
558					LONG2NUM((long)strlen(b)))),
559				INT2FIX(60));
560		    goto num;
561		}
562		{
563		    const char *cs = RSTRING_PTR(str);
564		    long cl = RSTRING_LEN(str);
565
566		    if (cl % 2) {
567			if (cl >= 1)
568			    hour = rb_str_new(&cs[0], 1);
569			if (cl >= 3)
570			    min  = rb_str_new(&cs[1], 2);
571			if (cl >= 5)
572			    sec  = rb_str_new(&cs[3], 2);
573		    }
574		    else {
575			if (cl >= 2)
576			    hour = rb_str_new(&cs[0], 2);
577			if (cl >= 4)
578			    min  = rb_str_new(&cs[2], 2);
579			if (cl >= 6)
580			    sec  = rb_str_new(&cs[4], 2);
581		    }
582		    goto num;
583		}
584	      num:
585		if (NIL_P(hour))
586		    offset = INT2FIX(0);
587		else {
588		    if (TYPE(hour) == T_STRING)
589			hour = str2num(hour);
590		    offset = f_mul(hour, INT2FIX(3600));
591		}
592		if (!NIL_P(min)) {
593		    if (TYPE(min) == T_STRING)
594			min = str2num(min);
595		    offset = f_add(offset, f_mul(min, INT2FIX(60)));
596		}
597		if (!NIL_P(sec))
598		    offset = f_add(offset, str2num(sec));
599		if (!NIL_P(sign) &&
600		    RSTRING_LEN(sign) == 1 &&
601		    *RSTRING_PTR(sign) == '-')
602		    offset = f_negate(offset);
603	    }
604	}
605    }
606    RB_GC_GUARD(str);
607  ok:
608    return offset;
609}
610
611static int
612day_num(VALUE s)
613{
614    int i;
615
616    for (i = 0; i < (int)sizeof_array(abbr_days); i++)
617	if (strncasecmp(abbr_days[i], RSTRING_PTR(s), 3) == 0)
618	    break;
619    return i;
620}
621
622static int
623mon_num(VALUE s)
624{
625    int i;
626
627    for (i = 0; i < (int)sizeof_array(abbr_months); i++)
628	if (strncasecmp(abbr_months[i], RSTRING_PTR(s), 3) == 0)
629	    break;
630    return i + 1;
631}
632
633static int
634parse_day_cb(VALUE m, VALUE hash)
635{
636    VALUE s;
637
638    s = rb_reg_nth_match(1, m);
639    set_hash("wday", INT2FIX(day_num(s)));
640    return 1;
641}
642
643static int
644parse_day(VALUE str, VALUE hash)
645{
646    static const char pat_source[] =
647#ifndef TIGHT_PARSER
648	"\\b(" ABBR_DAYS ")[^-/\\d\\s]*"
649#else
650	"(" VALID_DAYS ")"
651#endif
652	;
653    static VALUE pat = Qnil;
654
655    REGCOMP_I(pat);
656#ifndef TIGHT_PARSER
657    SUBS(str, pat, parse_day_cb);
658#else
659    SUBW(str, pat, parse_day_cb);
660#endif
661}
662
663static int
664parse_time2_cb(VALUE m, VALUE hash)
665{
666    VALUE h, min, s, f, p;
667
668    h = rb_reg_nth_match(1, m);
669    h = str2num(h);
670
671    min = rb_reg_nth_match(2, m);
672    if (!NIL_P(min))
673	min = str2num(min);
674
675    s = rb_reg_nth_match(3, m);
676    if (!NIL_P(s))
677	s = str2num(s);
678
679    f = rb_reg_nth_match(4, m);
680
681    if (!NIL_P(f))
682	f = rb_rational_new2(str2num(f),
683			     f_expt(INT2FIX(10), LONG2NUM(RSTRING_LEN(f))));
684
685    p = rb_reg_nth_match(5, m);
686
687    if (!NIL_P(p)) {
688	int ih = NUM2INT(h);
689	ih %= 12;
690	if (*RSTRING_PTR(p) == 'P' || *RSTRING_PTR(p) == 'p')
691	    ih += 12;
692	h = INT2FIX(ih);
693    }
694
695    set_hash("hour", h);
696    if (!NIL_P(min))
697	set_hash("min", min);
698    if (!NIL_P(s))
699	set_hash("sec", s);
700    if (!NIL_P(f))
701	set_hash("sec_fraction", f);
702
703    return 1;
704}
705
706static int
707parse_time_cb(VALUE m, VALUE hash)
708{
709    static const char pat_source[] =
710	    "\\A(\\d+)h?"
711	      "(?:\\s*:?\\s*(\\d+)m?"
712		"(?:"
713		  "\\s*:?\\s*(\\d+)(?:[,.](\\d+))?s?"
714		")?"
715	      ")?"
716	    "(?:\\s*([ap])(?:m\\b|\\.m\\.))?";
717    static VALUE pat = Qnil;
718    VALUE s1, s2;
719
720    s1 = rb_reg_nth_match(1, m);
721    s2 = rb_reg_nth_match(2, m);
722
723    if (!NIL_P(s2))
724	set_hash("zone", s2);
725
726    REGCOMP_I(pat);
727
728    {
729	VALUE m = f_match(pat, s1);
730
731	if (NIL_P(m))
732	    return 0;
733	parse_time2_cb(m, hash);
734    }
735
736    return 1;
737}
738
739static int
740parse_time(VALUE str, VALUE hash)
741{
742    static const char pat_source[] =
743		"("
744		   "(?:"
745		     "\\d+\\s*:\\s*\\d+"
746		     "(?:"
747#ifndef TIGHT_PARSER
748		       "\\s*:\\s*\\d+(?:[,.]\\d*)?"
749#else
750		       "\\s*:\\s*\\d+(?:[,.]\\d+)?"
751#endif
752		     ")?"
753		   "|"
754		     "\\d+\\s*h(?:\\s*\\d+m?(?:\\s*\\d+s?)?)?"
755		   ")"
756		   "(?:"
757		     "\\s*"
758		     "[ap](?:m\\b|\\.m\\.)"
759		   ")?"
760		 "|"
761		   "\\d+\\s*[ap](?:m\\b|\\.m\\.)"
762		 ")"
763		 "(?:"
764		   "\\s*"
765		   "("
766		     "(?:gmt|utc?)?[-+]\\d+(?:[,.:]\\d+(?::\\d+)?)?"
767		   "|"
768		     "(?-i:[[:alpha:].\\s]+)(?:standard|daylight)\\stime\\b"
769		   "|"
770		     "(?-i:[[:alpha:]]+)(?:\\sdst)?\\b"
771		   ")"
772		")?";
773    static VALUE pat = Qnil;
774
775    REGCOMP_I(pat);
776#ifndef TIGHT_PARSER
777    SUBS(str, pat, parse_time_cb);
778#else
779    SUBT(str, pat, parse_time_cb);
780#endif
781}
782
783#ifdef TIGHT_PARSER
784static int
785parse_era1_cb(VALUE m, VALUE hash)
786{
787    return 1;
788}
789
790static int
791parse_era1(VALUE str, VALUE hash)
792{
793    static const char pat_source[] =
794	"(a(?:d|\\.d\\.))";
795    static VALUE pat = Qnil;
796
797    REGCOMP_I(pat);
798    SUBA(str, pat, parse_era1_cb);
799}
800
801static int
802parse_era2_cb(VALUE m, VALUE hash)
803{
804    VALUE b;
805
806    b = rb_reg_nth_match(1, m);
807    if (*RSTRING_PTR(b) == 'B' ||
808	*RSTRING_PTR(b) == 'b')
809	set_hash("_bc", Qtrue);
810    return 1;
811}
812
813static int
814parse_era2(VALUE str, VALUE hash)
815{
816    static const char pat_source[] =
817	"(c(?:e|\\.e\\.)|b(?:ce|\\.c\\.e\\.)|b(?:c|\\.c\\.))";
818    static VALUE pat = Qnil;
819
820    REGCOMP_I(pat);
821    SUBB(str, pat, parse_era2_cb);
822}
823
824static int
825parse_era(VALUE str, VALUE hash)
826{
827    if (parse_era1(str, hash)) /* pre */
828	goto ok;
829    if (parse_era2(str, hash)) /* post */
830	goto ok;
831    return 0;
832  ok:
833    return 1;
834}
835#endif
836
837#ifdef TIGHT_PARSER
838static int
839check_year_width(VALUE y)
840{
841    char *s;
842    size_t l;
843
844    s = RSTRING_PTR(y);
845    l = strcspn(s, DECDIGIT);
846    s += l;
847    l = strspn(s, DECDIGIT);
848    if (l != 2)
849	return 0;
850    return 1;
851}
852
853static int
854check_apost(VALUE a, VALUE b, VALUE c)
855{
856    int f = 0;
857
858    if (!NIL_P(a) && *RSTRING_PTR(a) == '\'') {
859	if (!check_year_width(a))
860	    return 0;
861	f++;
862    }
863    if (!NIL_P(b) && *RSTRING_PTR(b) == '\'') {
864	if (!check_year_width(b))
865	    return 0;
866	if (!NIL_P(c))
867	    return 0;
868	f++;
869    }
870    if (!NIL_P(c) && *RSTRING_PTR(c) == '\'') {
871	if (!check_year_width(c))
872	    return 0;
873	f++;
874    }
875    if (f > 1)
876	return 0;
877    return 1;
878}
879#endif
880
881static int
882parse_eu_cb(VALUE m, VALUE hash)
883{
884#ifndef TIGHT_PARSER
885    VALUE y, mon, d, b;
886
887    d = rb_reg_nth_match(1, m);
888    mon = rb_reg_nth_match(2, m);
889    b = rb_reg_nth_match(3, m);
890    y = rb_reg_nth_match(4, m);
891
892    mon = INT2FIX(mon_num(mon));
893
894    s3e(hash, y, mon, d, !NIL_P(b) &&
895	(*RSTRING_PTR(b) == 'B' ||
896	 *RSTRING_PTR(b) == 'b'));
897#else
898    VALUE y, mon, d;
899
900    d = rb_reg_nth_match(1, m);
901    mon = rb_reg_nth_match(2, m);
902    y = rb_reg_nth_match(3, m);
903
904    if (!check_apost(d, mon, y))
905	return 0;
906
907    mon = INT2FIX(mon_num(mon));
908
909    s3e(hash, y, mon, d, 0);
910#endif
911    return 1;
912}
913
914static int
915parse_eu(VALUE str, VALUE hash)
916{
917    static const char pat_source[] =
918#ifdef TIGHT_PARSER
919		BOS
920		FPW_COM FPT_COM
921#endif
922#ifndef TIGHT_PARSER
923		"('?\\d+)[^-\\d\\s]*"
924#else
925		"(\\d+)(?:(?:st|nd|rd|th)\\b)?"
926#endif
927		 "\\s*"
928#ifndef TIGHT_PARSER
929		 "(" ABBR_MONTHS ")[^-\\d\\s']*"
930#else
931		 "(" VALID_MONTHS ")"
932#endif
933		 "(?:"
934		   "\\s*"
935#ifndef TIGHT_PARSER
936		   "(c(?:e|\\.e\\.)|b(?:ce|\\.c\\.e\\.)|a(?:d|\\.d\\.)|b(?:c|\\.c\\.))?"
937		   "\\s*"
938		   "('?-?\\d+(?:(?:st|nd|rd|th)\\b)?)"
939#else
940		   "(?:" FPA ")?"
941		   "\\s*"
942		   "([-']?\\d+)"
943		   "\\s*"
944		   "(?:" FPA "|" FPB ")?"
945#endif
946		")?"
947#ifdef TIGHT_PARSER
948		COM_FPT COM_FPW
949		EOS
950#endif
951		;
952    static VALUE pat = Qnil;
953
954    REGCOMP_I(pat);
955    SUBS(str, pat, parse_eu_cb);
956}
957
958static int
959parse_us_cb(VALUE m, VALUE hash)
960{
961#ifndef TIGHT_PARSER
962    VALUE y, mon, d, b;
963
964    mon = rb_reg_nth_match(1, m);
965    d = rb_reg_nth_match(2, m);
966
967    b = rb_reg_nth_match(3, m);
968    y = rb_reg_nth_match(4, m);
969
970    mon = INT2FIX(mon_num(mon));
971
972    s3e(hash, y, mon, d, !NIL_P(b) &&
973	(*RSTRING_PTR(b) == 'B' ||
974	 *RSTRING_PTR(b) == 'b'));
975#else
976    VALUE y, mon, d;
977
978    mon = rb_reg_nth_match(1, m);
979    d = rb_reg_nth_match(2, m);
980    y = rb_reg_nth_match(3, m);
981
982    if (!check_apost(mon, d, y))
983	return 0;
984
985    mon = INT2FIX(mon_num(mon));
986
987    s3e(hash, y, mon, d, 0);
988#endif
989    return 1;
990}
991
992static int
993parse_us(VALUE str, VALUE hash)
994{
995    static const char pat_source[] =
996#ifdef TIGHT_PARSER
997		BOS
998		FPW_COM FPT_COM
999#endif
1000#ifndef TIGHT_PARSER
1001		"\\b(" ABBR_MONTHS ")[^-\\d\\s']*"
1002#else
1003		"\\b(" VALID_MONTHS ")"
1004#endif
1005		 "\\s*"
1006#ifndef TIGHT_PARSER
1007		 "('?\\d+)[^-\\d\\s']*"
1008#else
1009		 "('?\\d+)(?:(?:st|nd|rd|th)\\b)?"
1010		COM_FPT
1011#endif
1012		 "(?:"
1013		   "\\s*,?"
1014		   "\\s*"
1015#ifndef TIGHT_PARSER
1016		   "(c(?:e|\\.e\\.)|b(?:ce|\\.c\\.e\\.)|a(?:d|\\.d\\.)|b(?:c|\\.c\\.))?"
1017		   "\\s*"
1018		   "('?-?\\d+)"
1019#else
1020		   "(?:" FPA ")?"
1021		   "\\s*"
1022		   "([-']?\\d+)"
1023		   "\\s*"
1024		   "(?:" FPA "|" FPB ")?"
1025#endif
1026		")?"
1027#ifdef TIGHT_PARSER
1028		COM_FPT COM_FPW
1029		EOS
1030#endif
1031		;
1032    static VALUE pat = Qnil;
1033
1034    REGCOMP_I(pat);
1035    SUBS(str, pat, parse_us_cb);
1036}
1037
1038static int
1039parse_iso_cb(VALUE m, VALUE hash)
1040{
1041    VALUE y, mon, d;
1042
1043    y = rb_reg_nth_match(1, m);
1044    mon = rb_reg_nth_match(2, m);
1045    d = rb_reg_nth_match(3, m);
1046
1047#ifdef TIGHT_PARSER
1048    if (!check_apost(y, mon, d))
1049	return 0;
1050#endif
1051
1052    s3e(hash, y, mon, d, 0);
1053    return 1;
1054}
1055
1056static int
1057parse_iso(VALUE str, VALUE hash)
1058{
1059    static const char pat_source[] =
1060#ifndef TIGHT_PARSER
1061	"('?[-+]?\\d+)-(\\d+)-('?-?\\d+)"
1062#else
1063	BOS
1064	FPW_COM FPT_COM
1065	"([-+']?\\d+)-(\\d+)-([-']?\\d+)"
1066	TEE_FPT COM_FPW
1067	EOS
1068#endif
1069	;
1070    static VALUE pat = Qnil;
1071
1072    REGCOMP_0(pat);
1073    SUBS(str, pat, parse_iso_cb);
1074}
1075
1076static int
1077parse_iso21_cb(VALUE m, VALUE hash)
1078{
1079    VALUE y, w, d;
1080
1081    y = rb_reg_nth_match(1, m);
1082    w = rb_reg_nth_match(2, m);
1083    d = rb_reg_nth_match(3, m);
1084
1085    if (!NIL_P(y))
1086	set_hash("cwyear", str2num(y));
1087    set_hash("cweek", str2num(w));
1088    if (!NIL_P(d))
1089	set_hash("cwday", str2num(d));
1090
1091    return 1;
1092}
1093
1094static int
1095parse_iso21(VALUE str, VALUE hash)
1096{
1097    static const char pat_source[] =
1098#ifndef TIGHT_PARSER
1099	"\\b(\\d{2}|\\d{4})?-?w(\\d{2})(?:-?(\\d))?\\b"
1100#else
1101	BOS
1102	FPW_COM FPT_COM
1103	"(\\d{2}|\\d{4})?-?w(\\d{2})(?:-?(\\d))?"
1104	TEE_FPT COM_FPW
1105	EOS
1106#endif
1107	;
1108    static VALUE pat = Qnil;
1109
1110    REGCOMP_I(pat);
1111    SUBS(str, pat, parse_iso21_cb);
1112}
1113
1114static int
1115parse_iso22_cb(VALUE m, VALUE hash)
1116{
1117    VALUE d;
1118
1119    d = rb_reg_nth_match(1, m);
1120    set_hash("cwday", str2num(d));
1121    return 1;
1122}
1123
1124static int
1125parse_iso22(VALUE str, VALUE hash)
1126{
1127    static const char pat_source[] =
1128#ifndef TIGHT_PARSER
1129	"-w-(\\d)\\b"
1130#else
1131	BOS
1132	FPW_COM FPT_COM
1133	"-w-(\\d)"
1134	TEE_FPT COM_FPW
1135	EOS
1136#endif
1137	;
1138    static VALUE pat = Qnil;
1139
1140    REGCOMP_I(pat);
1141    SUBS(str, pat, parse_iso22_cb);
1142}
1143
1144static int
1145parse_iso23_cb(VALUE m, VALUE hash)
1146{
1147    VALUE mon, d;
1148
1149    mon = rb_reg_nth_match(1, m);
1150    d = rb_reg_nth_match(2, m);
1151
1152    if (!NIL_P(mon))
1153	set_hash("mon", str2num(mon));
1154    set_hash("mday", str2num(d));
1155
1156    return 1;
1157}
1158
1159static int
1160parse_iso23(VALUE str, VALUE hash)
1161{
1162    static const char pat_source[] =
1163#ifndef TIGHT_PARSER
1164	"--(\\d{2})?-(\\d{2})\\b"
1165#else
1166	BOS
1167	FPW_COM FPT_COM
1168	"--(\\d{2})?-(\\d{2})"
1169	TEE_FPT COM_FPW
1170	EOS
1171#endif
1172	;
1173    static VALUE pat = Qnil;
1174
1175    REGCOMP_0(pat);
1176    SUBS(str, pat, parse_iso23_cb);
1177}
1178
1179static int
1180parse_iso24_cb(VALUE m, VALUE hash)
1181{
1182    VALUE mon, d;
1183
1184    mon = rb_reg_nth_match(1, m);
1185    d = rb_reg_nth_match(2, m);
1186
1187    set_hash("mon", str2num(mon));
1188    if (!NIL_P(d))
1189	set_hash("mday", str2num(d));
1190
1191    return 1;
1192}
1193
1194static int
1195parse_iso24(VALUE str, VALUE hash)
1196{
1197    static const char pat_source[] =
1198#ifndef TIGHT_PARSER
1199	"--(\\d{2})(\\d{2})?\\b"
1200#else
1201	BOS
1202	FPW_COM FPT_COM
1203	"--(\\d{2})(\\d{2})?"
1204	TEE_FPT COM_FPW
1205	EOS
1206#endif
1207	;
1208    static VALUE pat = Qnil;
1209
1210    REGCOMP_0(pat);
1211    SUBS(str, pat, parse_iso24_cb);
1212}
1213
1214static int
1215parse_iso25_cb(VALUE m, VALUE hash)
1216{
1217    VALUE y, d;
1218
1219    y = rb_reg_nth_match(1, m);
1220    d = rb_reg_nth_match(2, m);
1221
1222    set_hash("year", str2num(y));
1223    set_hash("yday", str2num(d));
1224
1225    return 1;
1226}
1227
1228static int
1229parse_iso25(VALUE str, VALUE hash)
1230{
1231    static const char pat0_source[] =
1232#ifndef TIGHT_PARSER
1233	"[,.](\\d{2}|\\d{4})-\\d{3}\\b"
1234#else
1235	BOS
1236	FPW_COM FPT_COM
1237	"[,.](\\d{2}|\\d{4})-\\d{3}"
1238	TEE_FPT COM_FPW
1239	EOS
1240#endif
1241	;
1242    static VALUE pat0 = Qnil;
1243    static const char pat_source[] =
1244#ifndef TIGHT_PARSER
1245	"\\b(\\d{2}|\\d{4})-(\\d{3})\\b"
1246#else
1247	BOS
1248	FPW_COM FPT_COM
1249	"(\\d{2}|\\d{4})-(\\d{3})"
1250	TEE_FPT COM_FPW
1251	EOS
1252#endif
1253	;
1254    static VALUE pat = Qnil;
1255
1256    REGCOMP_0(pat0);
1257    REGCOMP_0(pat);
1258
1259    if (!NIL_P(f_match(pat0, str)))
1260	return 0;
1261    SUBS(str, pat, parse_iso25_cb);
1262}
1263
1264static int
1265parse_iso26_cb(VALUE m, VALUE hash)
1266{
1267    VALUE d;
1268
1269    d = rb_reg_nth_match(1, m);
1270    set_hash("yday", str2num(d));
1271
1272    return 1;
1273}
1274static int
1275parse_iso26(VALUE str, VALUE hash)
1276{
1277    static const char pat0_source[] =
1278#ifndef TIGHT_PARSER
1279	"\\d-\\d{3}\\b"
1280#else
1281	BOS
1282	FPW_COM FPT_COM
1283	"\\d-\\d{3}"
1284	TEE_FPT COM_FPW
1285	EOS
1286#endif
1287	;
1288    static VALUE pat0 = Qnil;
1289    static const char pat_source[] =
1290#ifndef TIGHT_PARSER
1291	"\\b-(\\d{3})\\b"
1292#else
1293	BOS
1294	FPW_COM FPT_COM
1295	"-(\\d{3})"
1296	TEE_FPT COM_FPW
1297	EOS
1298#endif
1299	;
1300    static VALUE pat = Qnil;
1301
1302    REGCOMP_0(pat0);
1303    REGCOMP_0(pat);
1304
1305    if (!NIL_P(f_match(pat0, str)))
1306	return 0;
1307    SUBS(str, pat, parse_iso26_cb);
1308}
1309
1310static int
1311parse_iso2(VALUE str, VALUE hash)
1312{
1313    if (parse_iso21(str, hash))
1314	goto ok;
1315    if (parse_iso22(str, hash))
1316	goto ok;
1317    if (parse_iso23(str, hash))
1318	goto ok;
1319    if (parse_iso24(str, hash))
1320	goto ok;
1321    if (parse_iso25(str, hash))
1322	goto ok;
1323    if (parse_iso26(str, hash))
1324	goto ok;
1325    return 0;
1326
1327  ok:
1328    return 1;
1329}
1330
1331static int
1332gengo(int c)
1333{
1334    int e;
1335
1336    switch (c) {
1337      case 'M': case 'm': e = 1867; break;
1338      case 'T': case 't': e = 1911; break;
1339      case 'S': case 's': e = 1925; break;
1340      case 'H': case 'h': e = 1988; break;
1341      default:  e = 0; break;
1342    }
1343    return e;
1344}
1345
1346static int
1347parse_jis_cb(VALUE m, VALUE hash)
1348{
1349    VALUE e, y, mon, d;
1350    int ep;
1351
1352    e = rb_reg_nth_match(1, m);
1353    y = rb_reg_nth_match(2, m);
1354    mon = rb_reg_nth_match(3, m);
1355    d = rb_reg_nth_match(4, m);
1356
1357    ep = gengo(*RSTRING_PTR(e));
1358
1359    set_hash("year", f_add(str2num(y), INT2FIX(ep)));
1360    set_hash("mon", str2num(mon));
1361    set_hash("mday", str2num(d));
1362
1363    return 1;
1364}
1365
1366static int
1367parse_jis(VALUE str, VALUE hash)
1368{
1369    static const char pat_source[] =
1370#ifndef TIGHT_PARSER
1371	"\\b([mtsh])(\\d+)\\.(\\d+)\\.(\\d+)"
1372#else
1373	BOS
1374	FPW_COM FPT_COM
1375	"([mtsh])(\\d+)\\.(\\d+)\\.(\\d+)"
1376	TEE_FPT COM_FPW
1377	EOS
1378#endif
1379	;
1380    static VALUE pat = Qnil;
1381
1382    REGCOMP_I(pat);
1383    SUBS(str, pat, parse_jis_cb);
1384}
1385
1386static int
1387parse_vms11_cb(VALUE m, VALUE hash)
1388{
1389    VALUE y, mon, d;
1390
1391    d = rb_reg_nth_match(1, m);
1392    mon = rb_reg_nth_match(2, m);
1393    y = rb_reg_nth_match(3, m);
1394
1395#ifdef TIGHT_PARSER
1396    if (!check_apost(d, mon, y))
1397	return 0;
1398#endif
1399
1400    mon = INT2FIX(mon_num(mon));
1401
1402    s3e(hash, y, mon, d, 0);
1403    return 1;
1404}
1405
1406static int
1407parse_vms11(VALUE str, VALUE hash)
1408{
1409    static const char pat_source[] =
1410#ifndef TIGHT_PARSER
1411	"('?-?\\d+)-(" ABBR_MONTHS ")[^-/.]*"
1412	"-('?-?\\d+)"
1413#else
1414	BOS
1415	FPW_COM FPT_COM
1416	"([-']?\\d+)-(" DOTLESS_VALID_MONTHS ")"
1417	"-([-']?\\d+)"
1418	COM_FPT COM_FPW
1419	EOS
1420#endif
1421	;
1422    static VALUE pat = Qnil;
1423
1424    REGCOMP_I(pat);
1425    SUBS(str, pat, parse_vms11_cb);
1426}
1427
1428static int
1429parse_vms12_cb(VALUE m, VALUE hash)
1430{
1431    VALUE y, mon, d;
1432
1433    mon = rb_reg_nth_match(1, m);
1434    d = rb_reg_nth_match(2, m);
1435    y = rb_reg_nth_match(3, m);
1436
1437#ifdef TIGHT_PARSER
1438    if (!check_apost(mon, d, y))
1439	return 0;
1440#endif
1441
1442    mon = INT2FIX(mon_num(mon));
1443
1444    s3e(hash, y, mon, d, 0);
1445    return 1;
1446}
1447
1448static int
1449parse_vms12(VALUE str, VALUE hash)
1450{
1451    static const char pat_source[] =
1452#ifndef TIGHT_PARSER
1453	"\\b(" ABBR_MONTHS ")[^-/.]*"
1454	"-('?-?\\d+)(?:-('?-?\\d+))?"
1455#else
1456	BOS
1457	FPW_COM FPT_COM
1458	"(" DOTLESS_VALID_MONTHS ")"
1459	"-([-']?\\d+)(?:-([-']?\\d+))?"
1460	COM_FPT COM_FPW
1461	EOS
1462#endif
1463	;
1464    static VALUE pat = Qnil;
1465
1466    REGCOMP_I(pat);
1467    SUBS(str, pat, parse_vms12_cb);
1468}
1469
1470static int
1471parse_vms(VALUE str, VALUE hash)
1472{
1473    if (parse_vms11(str, hash))
1474	goto ok;
1475    if (parse_vms12(str, hash))
1476	goto ok;
1477    return 0;
1478
1479  ok:
1480    return 1;
1481}
1482
1483static int
1484parse_sla_cb(VALUE m, VALUE hash)
1485{
1486    VALUE y, mon, d;
1487
1488    y = rb_reg_nth_match(1, m);
1489    mon = rb_reg_nth_match(2, m);
1490    d = rb_reg_nth_match(3, m);
1491
1492#ifdef TIGHT_PARSER
1493    if (!check_apost(y, mon, d))
1494	return 0;
1495#endif
1496
1497    s3e(hash, y, mon, d, 0);
1498    return 1;
1499}
1500
1501static int
1502parse_sla(VALUE str, VALUE hash)
1503{
1504    static const char pat_source[] =
1505#ifndef TIGHT_PARSER
1506	"('?-?\\d+)/\\s*('?\\d+)(?:\\D\\s*('?-?\\d+))?"
1507#else
1508	BOS
1509	FPW_COM FPT_COM
1510	"([-']?\\d+)/\\s*('?\\d+)(?:(?:[-/]|\\s+)\\s*([-']?\\d+))?"
1511	COM_FPT COM_FPW
1512	EOS
1513#endif
1514	;
1515    static VALUE pat = Qnil;
1516
1517    REGCOMP_I(pat);
1518    SUBS(str, pat, parse_sla_cb);
1519}
1520
1521#ifdef TIGHT_PARSER
1522static int
1523parse_sla2_cb(VALUE m, VALUE hash)
1524{
1525    VALUE y, mon, d;
1526
1527    d = rb_reg_nth_match(1, m);
1528    mon = rb_reg_nth_match(2, m);
1529    y = rb_reg_nth_match(3, m);
1530
1531    if (!check_apost(d, mon, y))
1532	return 0;
1533
1534    mon = INT2FIX(mon_num(mon));
1535
1536    s3e(hash, y, mon, d, 0);
1537    return 1;
1538}
1539
1540static int
1541parse_sla2(VALUE str, VALUE hash)
1542{
1543    static const char pat_source[] =
1544	BOS
1545	FPW_COM FPT_COM
1546	"([-']?\\d+)/\\s*(" DOTLESS_VALID_MONTHS ")(?:(?:[-/]|\\s+)\\s*([-']?\\d+))?"
1547	COM_FPT COM_FPW
1548	EOS
1549	;
1550    static VALUE pat = Qnil;
1551
1552    REGCOMP_I(pat);
1553    SUBS(str, pat, parse_sla2_cb);
1554}
1555
1556static int
1557parse_sla3_cb(VALUE m, VALUE hash)
1558{
1559    VALUE y, mon, d;
1560
1561    mon = rb_reg_nth_match(1, m);
1562    d = rb_reg_nth_match(2, m);
1563    y = rb_reg_nth_match(3, m);
1564
1565    if (!check_apost(mon, d, y))
1566	return 0;
1567
1568    mon = INT2FIX(mon_num(mon));
1569
1570    s3e(hash, y, mon, d, 0);
1571    return 1;
1572}
1573
1574static int
1575parse_sla3(VALUE str, VALUE hash)
1576{
1577    static const char pat_source[] =
1578	BOS
1579	FPW_COM FPT_COM
1580	"(" DOTLESS_VALID_MONTHS ")/\\s*([-']?\\d+)(?:(?:[-/]|\\s+)\\s*([-']?\\d+))?"
1581	COM_FPT COM_FPW
1582	EOS
1583	;
1584    static VALUE pat = Qnil;
1585
1586    REGCOMP_I(pat);
1587    SUBS(str, pat, parse_sla3_cb);
1588}
1589#endif
1590
1591static int
1592parse_dot_cb(VALUE m, VALUE hash)
1593{
1594    VALUE y, mon, d;
1595
1596    y = rb_reg_nth_match(1, m);
1597    mon = rb_reg_nth_match(2, m);
1598    d = rb_reg_nth_match(3, m);
1599
1600#ifdef TIGHT_PARSER
1601    if (!check_apost(y, mon, d))
1602	return 0;
1603#endif
1604
1605    s3e(hash, y, mon, d, 0);
1606    return 1;
1607}
1608
1609static int
1610parse_dot(VALUE str, VALUE hash)
1611{
1612    static const char pat_source[] =
1613#ifndef TIGHT_PARSER
1614	"('?-?\\d+)\\.\\s*('?\\d+)\\.\\s*('?-?\\d+)"
1615#else
1616	BOS
1617	FPW_COM FPT_COM
1618	"([-']?\\d+)\\.\\s*(\\d+)\\.\\s*([-']?\\d+)"
1619	COM_FPT COM_FPW
1620	EOS
1621#endif
1622	;
1623    static VALUE pat = Qnil;
1624
1625    REGCOMP_I(pat);
1626    SUBS(str, pat, parse_dot_cb);
1627}
1628
1629#ifdef TIGHT_PARSER
1630static int
1631parse_dot2_cb(VALUE m, VALUE hash)
1632{
1633    VALUE y, mon, d;
1634
1635    d = rb_reg_nth_match(1, m);
1636    mon = rb_reg_nth_match(2, m);
1637    y = rb_reg_nth_match(3, m);
1638
1639    if (!check_apost(d, mon, y))
1640	return 0;
1641
1642    mon = INT2FIX(mon_num(mon));
1643
1644    s3e(hash, y, mon, d, 0);
1645    return 1;
1646}
1647
1648static int
1649parse_dot2(VALUE str, VALUE hash)
1650{
1651    static const char pat_source[] =
1652	BOS
1653	FPW_COM FPT_COM
1654	"([-']?\\d+)\\.\\s*(" DOTLESS_VALID_MONTHS ")(?:(?:[./])\\s*([-']?\\d+))?"
1655	COM_FPT COM_FPW
1656	EOS
1657	;
1658    static VALUE pat = Qnil;
1659
1660    REGCOMP_I(pat);
1661    SUBS(str, pat, parse_dot2_cb);
1662}
1663
1664static int
1665parse_dot3_cb(VALUE m, VALUE hash)
1666{
1667    VALUE y, mon, d;
1668
1669    mon = rb_reg_nth_match(1, m);
1670    d = rb_reg_nth_match(2, m);
1671    y = rb_reg_nth_match(3, m);
1672
1673    if (!check_apost(mon, d, y))
1674	return 0;
1675
1676    mon = INT2FIX(mon_num(mon));
1677
1678    s3e(hash, y, mon, d, 0);
1679    return 1;
1680}
1681
1682static int
1683parse_dot3(VALUE str, VALUE hash)
1684{
1685    static const char pat_source[] =
1686	BOS
1687	FPW_COM FPT_COM
1688	"(" DOTLESS_VALID_MONTHS ")\\.\\s*([-']?\\d+)(?:(?:[./])\\s*([-']?\\d+))?"
1689	COM_FPT COM_FPW
1690	EOS
1691	;
1692    static VALUE pat = Qnil;
1693
1694    REGCOMP_I(pat);
1695    SUBS(str, pat, parse_dot3_cb);
1696}
1697#endif
1698
1699static int
1700parse_year_cb(VALUE m, VALUE hash)
1701{
1702    VALUE y;
1703
1704    y = rb_reg_nth_match(1, m);
1705    set_hash("year", str2num(y));
1706    return 1;
1707}
1708
1709static int
1710parse_year(VALUE str, VALUE hash)
1711{
1712    static const char pat_source[] =
1713#ifndef TIGHT_PARSER
1714	"'(\\d+)\\b"
1715#else
1716	BOS
1717	FPW_COM FPT_COM
1718	"'(\\d+)"
1719	COM_FPT COM_FPW
1720	EOS
1721#endif
1722	;
1723    static VALUE pat = Qnil;
1724
1725    REGCOMP_0(pat);
1726    SUBS(str, pat, parse_year_cb);
1727}
1728
1729static int
1730parse_mon_cb(VALUE m, VALUE hash)
1731{
1732    VALUE mon;
1733
1734    mon = rb_reg_nth_match(1, m);
1735    set_hash("mon", INT2FIX(mon_num(mon)));
1736    return 1;
1737}
1738
1739static int
1740parse_mon(VALUE str, VALUE hash)
1741{
1742    static const char pat_source[] =
1743#ifndef TIGHT_PARSER
1744	"\\b(" ABBR_MONTHS ")\\S*"
1745#else
1746	BOS
1747	FPW_COM FPT_COM
1748	"(" VALID_MONTHS ")"
1749	COM_FPT COM_FPW
1750	EOS
1751#endif
1752	;
1753    static VALUE pat = Qnil;
1754
1755    REGCOMP_I(pat);
1756    SUBS(str, pat, parse_mon_cb);
1757}
1758
1759static int
1760parse_mday_cb(VALUE m, VALUE hash)
1761{
1762    VALUE d;
1763
1764    d = rb_reg_nth_match(1, m);
1765    set_hash("mday", str2num(d));
1766    return 1;
1767}
1768
1769static int
1770parse_mday(VALUE str, VALUE hash)
1771{
1772    static const char pat_source[] =
1773#ifndef TIGHT_PARSER
1774	"(\\d+)(st|nd|rd|th)\\b"
1775#else
1776	BOS
1777	FPW_COM FPT_COM
1778	"(\\d+)(st|nd|rd|th)"
1779	COM_FPT COM_FPW
1780	EOS
1781#endif
1782	;
1783    static VALUE pat = Qnil;
1784
1785    REGCOMP_I(pat);
1786    SUBS(str, pat, parse_mday_cb);
1787}
1788
1789static int
1790n2i(const char *s, long f, long w)
1791{
1792    long e, i;
1793    int v;
1794
1795    e = f + w;
1796    v = 0;
1797    for (i = f; i < e; i++) {
1798	v *= 10;
1799	v += s[i] - '0';
1800    }
1801    return v;
1802}
1803
1804static int
1805parse_ddd_cb(VALUE m, VALUE hash)
1806{
1807    VALUE s1, s2, s3, s4, s5;
1808    const char *cs2, *cs3, *cs5;
1809    long l2, l3, l4, l5;
1810
1811    s1 = rb_reg_nth_match(1, m);
1812    s2 = rb_reg_nth_match(2, m);
1813    s3 = rb_reg_nth_match(3, m);
1814    s4 = rb_reg_nth_match(4, m);
1815    s5 = rb_reg_nth_match(5, m);
1816
1817    cs2 = RSTRING_PTR(s2);
1818    l2 = RSTRING_LEN(s2);
1819
1820    switch (l2) {
1821      case 2:
1822	if (NIL_P(s3) && !NIL_P(s4))
1823	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1824	else
1825	    set_hash("mday", INT2FIX(n2i(cs2,    0, 2)));
1826	break;
1827      case 4:
1828	if (NIL_P(s3) && !NIL_P(s4)) {
1829	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1830	    set_hash("min",  INT2FIX(n2i(cs2, l2-4, 2)));
1831	}
1832	else {
1833	    set_hash("mon",  INT2FIX(n2i(cs2,    0, 2)));
1834	    set_hash("mday", INT2FIX(n2i(cs2,    2, 2)));
1835	}
1836	break;
1837      case 6:
1838	if (NIL_P(s3) && !NIL_P(s4)) {
1839	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1840	    set_hash("min",  INT2FIX(n2i(cs2, l2-4, 2)));
1841	    set_hash("hour", INT2FIX(n2i(cs2, l2-6, 2)));
1842	}
1843	else {
1844	    int                  y = n2i(cs2,    0, 2);
1845	    if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1846		y = -y;
1847	    set_hash("year", INT2FIX(y));
1848	    set_hash("mon",  INT2FIX(n2i(cs2,    2, 2)));
1849	    set_hash("mday", INT2FIX(n2i(cs2,    4, 2)));
1850	}
1851	break;
1852      case 8:
1853      case 10:
1854      case 12:
1855      case 14:
1856	if (NIL_P(s3) && !NIL_P(s4)) {
1857	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1858	    set_hash("min",  INT2FIX(n2i(cs2, l2-4, 2)));
1859	    set_hash("hour", INT2FIX(n2i(cs2, l2-6, 2)));
1860	    set_hash("mday", INT2FIX(n2i(cs2, l2-8, 2)));
1861	    if (l2 >= 10)
1862		set_hash("mon", INT2FIX(n2i(cs2, l2-10, 2)));
1863	    if (l2 == 12) {
1864		int y = n2i(cs2, l2-12, 2);
1865		if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1866		    y = -y;
1867		set_hash("year", INT2FIX(y));
1868	    }
1869	    if (l2 == 14) {
1870		int y = n2i(cs2, l2-14, 4);
1871		if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1872		    y = -y;
1873		set_hash("year", INT2FIX(y));
1874		set_hash("_comp", Qfalse);
1875	    }
1876	}
1877	else {
1878	    int                  y = n2i(cs2,    0, 4);
1879	    if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1880		y = -y;
1881	    set_hash("year", INT2FIX(y));
1882	    set_hash("mon",  INT2FIX(n2i(cs2,    4, 2)));
1883	    set_hash("mday", INT2FIX(n2i(cs2,    6, 2)));
1884	    if (l2 >= 10)
1885		set_hash("hour", INT2FIX(n2i(cs2,    8, 2)));
1886	    if (l2 >= 12)
1887		set_hash("min",  INT2FIX(n2i(cs2,   10, 2)));
1888	    if (l2 >= 14)
1889		set_hash("sec",  INT2FIX(n2i(cs2,   12, 2)));
1890	    set_hash("_comp", Qfalse);
1891	}
1892	break;
1893      case 3:
1894	if (NIL_P(s3) && !NIL_P(s4)) {
1895	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1896	    set_hash("min",  INT2FIX(n2i(cs2, l2-3, 1)));
1897	}
1898	else
1899	    set_hash("yday", INT2FIX(n2i(cs2,    0, 3)));
1900	break;
1901      case 5:
1902	if (NIL_P(s3) && !NIL_P(s4)) {
1903	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1904	    set_hash("min",  INT2FIX(n2i(cs2, l2-4, 2)));
1905	    set_hash("hour", INT2FIX(n2i(cs2, l2-5, 1)));
1906	}
1907	else {
1908	    int                  y = n2i(cs2,    0, 2);
1909	    if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1910		y = -y;
1911	    set_hash("year", INT2FIX(y));
1912	    set_hash("yday", INT2FIX(n2i(cs2,    2, 3)));
1913	}
1914	break;
1915      case 7:
1916	if (NIL_P(s3) && !NIL_P(s4)) {
1917	    set_hash("sec",  INT2FIX(n2i(cs2, l2-2, 2)));
1918	    set_hash("min",  INT2FIX(n2i(cs2, l2-4, 2)));
1919	    set_hash("hour", INT2FIX(n2i(cs2, l2-6, 2)));
1920	    set_hash("mday", INT2FIX(n2i(cs2, l2-7, 1)));
1921	}
1922	else {
1923	    int                  y = n2i(cs2,    0, 4);
1924	    if (!NIL_P(s1) && *RSTRING_PTR(s1) == '-')
1925		y = -y;
1926	    set_hash("year", INT2FIX(y));
1927	    set_hash("yday", INT2FIX(n2i(cs2,    4, 3)));
1928	}
1929	break;
1930    }
1931    RB_GC_GUARD(s2);
1932    if (!NIL_P(s3)) {
1933	cs3 = RSTRING_PTR(s3);
1934	l3 = RSTRING_LEN(s3);
1935
1936	if (!NIL_P(s4)) {
1937	    switch (l3) {
1938	      case 2:
1939	      case 4:
1940	      case 6:
1941		set_hash("sec", INT2FIX(n2i(cs3, l3-2, 2)));
1942		if (l3 >= 4)
1943		    set_hash("min", INT2FIX(n2i(cs3, l3-4, 2)));
1944		if (l3 >= 6)
1945		    set_hash("hour", INT2FIX(n2i(cs3, l3-6, 2)));
1946		break;
1947	    }
1948	}
1949	else {
1950	    switch (l3) {
1951	      case 2:
1952	      case 4:
1953	      case 6:
1954		set_hash("hour", INT2FIX(n2i(cs3, 0, 2)));
1955		if (l3 >= 4)
1956		    set_hash("min", INT2FIX(n2i(cs3, 2, 2)));
1957		if (l3 >= 6)
1958		    set_hash("sec", INT2FIX(n2i(cs3, 4, 2)));
1959		break;
1960	    }
1961	}
1962	RB_GC_GUARD(s3);
1963    }
1964    if (!NIL_P(s4)) {
1965	l4 = RSTRING_LEN(s4);
1966
1967	set_hash("sec_fraction",
1968		 rb_rational_new2(str2num(s4),
1969				  f_expt(INT2FIX(10), LONG2NUM(l4))));
1970    }
1971    if (!NIL_P(s5)) {
1972	cs5 = RSTRING_PTR(s5);
1973	l5 = RSTRING_LEN(s5);
1974
1975	set_hash("zone", s5);
1976
1977	if (*cs5 == '[') {
1978	    char *buf = ALLOCA_N(char, l5 + 1);
1979	    char *s1, *s2, *s3;
1980	    VALUE zone;
1981
1982	    memcpy(buf, cs5, l5);
1983	    buf[l5 - 1] = '\0';
1984
1985	    s1 = buf + 1;
1986	    s2 = strchr(buf, ':');
1987	    if (s2) {
1988		*s2 = '\0';
1989		s2++;
1990	    }
1991	    if (s2)
1992		s3 = s2;
1993	    else
1994		s3 = s1;
1995	    zone = rb_str_new2(s3);
1996	    set_hash("zone", zone);
1997	    if (isdigit((unsigned char)*s1))
1998		*--s1 = '+';
1999	    set_hash("offset", date_zone_to_diff(rb_str_new2(s1)));
2000	}
2001	RB_GC_GUARD(s5);
2002    }
2003
2004    return 1;
2005}
2006
2007static int
2008parse_ddd(VALUE str, VALUE hash)
2009{
2010    static const char pat_source[] =
2011#ifdef TIGHT_PARSER
2012		BOS
2013#endif
2014		"([-+]?)(\\d{2,14})"
2015		  "(?:"
2016		    "\\s*"
2017		    "t?"
2018		    "\\s*"
2019		    "(\\d{2,6})?(?:[,.](\\d*))?"
2020		  ")?"
2021		  "(?:"
2022		    "\\s*"
2023		    "("
2024		      "z\\b"
2025		    "|"
2026		      "[-+]\\d{1,4}\\b"
2027		    "|"
2028		      "\\[[-+]?\\d[^\\]]*\\]"
2029		    ")"
2030		")?"
2031#ifdef TIGHT_PARSER
2032		EOS
2033#endif
2034		;
2035    static VALUE pat = Qnil;
2036
2037    REGCOMP_I(pat);
2038    SUBS(str, pat, parse_ddd_cb);
2039}
2040
2041#ifndef TIGHT_PARSER
2042static int
2043parse_bc_cb(VALUE m, VALUE hash)
2044{
2045    set_hash("_bc", Qtrue);
2046    return 1;
2047}
2048
2049static int
2050parse_bc(VALUE str, VALUE hash)
2051{
2052    static const char pat_source[] =
2053	"\\b(bc\\b|bce\\b|b\\.c\\.|b\\.c\\.e\\.)";
2054    static VALUE pat = Qnil;
2055
2056    REGCOMP_I(pat);
2057    SUBS(str, pat, parse_bc_cb);
2058}
2059
2060static int
2061parse_frag_cb(VALUE m, VALUE hash)
2062{
2063    VALUE s, n;
2064
2065    s = rb_reg_nth_match(1, m);
2066
2067    if (!NIL_P(ref_hash("hour")) && NIL_P(ref_hash("mday"))) {
2068	n = str2num(s);
2069	if (f_ge_p(n, INT2FIX(1)) &&
2070	    f_le_p(n, INT2FIX(31)))
2071	    set_hash("mday", n);
2072    }
2073    if (!NIL_P(ref_hash("mday")) && NIL_P(ref_hash("hour"))) {
2074	n = str2num(s);
2075	if (f_ge_p(n, INT2FIX(0)) &&
2076	    f_le_p(n, INT2FIX(24)))
2077	    set_hash("hour", n);
2078    }
2079
2080    return 1;
2081}
2082
2083static int
2084parse_frag(VALUE str, VALUE hash)
2085{
2086    static const char pat_source[] = "\\A\\s*(\\d{1,2})\\s*\\z";
2087    static VALUE pat = Qnil;
2088
2089    REGCOMP_I(pat);
2090    SUBS(str, pat, parse_frag_cb);
2091}
2092#endif
2093
2094#ifdef TIGHT_PARSER
2095static int
2096parse_dummy_cb(VALUE m, VALUE hash)
2097{
2098    return 1;
2099}
2100
2101static int
2102parse_wday_only(VALUE str, VALUE hash)
2103{
2104    static const char pat_source[] = "\\A\\s*" FPW "\\s*\\z";
2105    static VALUE pat = Qnil;
2106
2107    REGCOMP_0(pat);
2108    SUBS(str, pat, parse_dummy_cb);
2109}
2110
2111static int
2112parse_time_only(VALUE str, VALUE hash)
2113{
2114    static const char pat_source[] = "\\A\\s*" FPT "\\s*\\z";
2115    static VALUE pat = Qnil;
2116
2117    REGCOMP_0(pat);
2118    SUBS(str, pat, parse_dummy_cb);
2119}
2120
2121static int
2122parse_wday_and_time(VALUE str, VALUE hash)
2123{
2124    static const char pat_source[] = "\\A\\s*(" FPW "\\s+" FPT "|" FPT "\\s+" FPW ")\\s*\\z";
2125    static VALUE pat = Qnil;
2126
2127    REGCOMP_0(pat);
2128    SUBS(str, pat, parse_dummy_cb);
2129}
2130
2131static unsigned
2132have_invalid_char_p(VALUE s)
2133{
2134    long i;
2135
2136    for (i = 0; i < RSTRING_LEN(s); i++)
2137	if (iscntrl((unsigned char)RSTRING_PTR(s)[i]) &&
2138	    !isspace((unsigned char)RSTRING_PTR(s)[i]))
2139	    return 1;
2140    return 0;
2141}
2142#endif
2143
2144#define HAVE_ALPHA (1<<0)
2145#define HAVE_DIGIT (1<<1)
2146#define HAVE_DASH (1<<2)
2147#define HAVE_DOT (1<<3)
2148#define HAVE_SLASH (1<<4)
2149
2150static unsigned
2151check_class(VALUE s)
2152{
2153    unsigned flags;
2154    long i;
2155
2156    flags = 0;
2157    for (i = 0; i < RSTRING_LEN(s); i++) {
2158	if (isalpha((unsigned char)RSTRING_PTR(s)[i]))
2159	    flags |= HAVE_ALPHA;
2160	if (isdigit((unsigned char)RSTRING_PTR(s)[i]))
2161	    flags |= HAVE_DIGIT;
2162	if (RSTRING_PTR(s)[i] == '-')
2163	    flags |= HAVE_DASH;
2164	if (RSTRING_PTR(s)[i] == '.')
2165	    flags |= HAVE_DOT;
2166	if (RSTRING_PTR(s)[i] == '/')
2167	    flags |= HAVE_SLASH;
2168    }
2169    return flags;
2170}
2171
2172#define HAVE_ELEM_P(x) ((check_class(str) & (x)) == (x))
2173
2174#ifdef TIGHT_PARSER
2175#define PARSER_ERROR return rb_hash_new()
2176#endif
2177
2178VALUE
2179date__parse(VALUE str, VALUE comp)
2180{
2181    VALUE backref, hash;
2182
2183#ifdef TIGHT_PARSER
2184    if (have_invalid_char_p(str))
2185	PARSER_ERROR;
2186#endif
2187
2188    backref = rb_backref_get();
2189    rb_match_busy(backref);
2190
2191    {
2192	static const char pat_source[] =
2193#ifndef TIGHT_PARSER
2194	    "[^-+',./:@[:alnum:]\\[\\]]+"
2195#else
2196	    "[^[:graph:]]+"
2197#endif
2198	    ;
2199	static VALUE pat = Qnil;
2200
2201	REGCOMP_0(pat);
2202	str = rb_str_dup(str);
2203	f_gsub_bang(str, pat, asp_string());
2204    }
2205
2206    hash = rb_hash_new();
2207    set_hash("_comp", comp);
2208
2209    if (HAVE_ELEM_P(HAVE_ALPHA))
2210	parse_day(str, hash);
2211    if (HAVE_ELEM_P(HAVE_DIGIT))
2212	parse_time(str, hash);
2213
2214#ifdef TIGHT_PARSER
2215    if (HAVE_ELEM_P(HAVE_ALPHA))
2216	parse_era(str, hash);
2217#endif
2218
2219    if (HAVE_ELEM_P(HAVE_ALPHA|HAVE_DIGIT)) {
2220	if (parse_eu(str, hash))
2221	    goto ok;
2222	if (parse_us(str, hash))
2223	    goto ok;
2224    }
2225    if (HAVE_ELEM_P(HAVE_DIGIT|HAVE_DASH))
2226	if (parse_iso(str, hash))
2227	    goto ok;
2228    if (HAVE_ELEM_P(HAVE_DIGIT|HAVE_DOT))
2229	if (parse_jis(str, hash))
2230	    goto ok;
2231    if (HAVE_ELEM_P(HAVE_ALPHA|HAVE_DIGIT|HAVE_DASH))
2232	if (parse_vms(str, hash))
2233	    goto ok;
2234    if (HAVE_ELEM_P(HAVE_DIGIT|HAVE_SLASH))
2235	if (parse_sla(str, hash))
2236	    goto ok;
2237#ifdef TIGHT_PARSER
2238    if (HAVE_ELEM_P(HAVE_ALPHA|HAVE_DIGIT|HAVE_SLASH)) {
2239	if (parse_sla2(str, hash))
2240	    goto ok;
2241	if (parse_sla3(str, hash))
2242	    goto ok;
2243    }
2244#endif
2245    if (HAVE_ELEM_P(HAVE_DIGIT|HAVE_DOT))
2246	if (parse_dot(str, hash))
2247	    goto ok;
2248#ifdef TIGHT_PARSER
2249    if (HAVE_ELEM_P(HAVE_ALPHA|HAVE_DIGIT|HAVE_DOT)) {
2250	if (parse_dot2(str, hash))
2251	    goto ok;
2252	if (parse_dot3(str, hash))
2253	    goto ok;
2254    }
2255#endif
2256    if (HAVE_ELEM_P(HAVE_DIGIT))
2257	if (parse_iso2(str, hash))
2258	    goto ok;
2259    if (HAVE_ELEM_P(HAVE_DIGIT))
2260	if (parse_year(str, hash))
2261	    goto ok;
2262    if (HAVE_ELEM_P(HAVE_ALPHA))
2263	if (parse_mon(str, hash))
2264	    goto ok;
2265    if (HAVE_ELEM_P(HAVE_DIGIT))
2266	if (parse_mday(str, hash))
2267	    goto ok;
2268    if (HAVE_ELEM_P(HAVE_DIGIT))
2269	if (parse_ddd(str, hash))
2270	    goto ok;
2271
2272#ifdef TIGHT_PARSER
2273    if (parse_wday_only(str, hash))
2274	goto ok;
2275    if (parse_time_only(str, hash))
2276	    goto ok;
2277    if (parse_wday_and_time(str, hash))
2278	goto ok;
2279
2280    PARSER_ERROR; /* not found */
2281#endif
2282
2283  ok:
2284#ifndef TIGHT_PARSER
2285    if (HAVE_ELEM_P(HAVE_ALPHA))
2286	parse_bc(str, hash);
2287    if (HAVE_ELEM_P(HAVE_DIGIT))
2288	parse_frag(str, hash);
2289#endif
2290
2291    {
2292	if (RTEST(ref_hash("_bc"))) {
2293	    VALUE y;
2294
2295	    y = ref_hash("cwyear");
2296	    if (!NIL_P(y)) {
2297		y = f_add(f_negate(y), INT2FIX(1));
2298		set_hash("cwyear", y);
2299	    }
2300	    y = ref_hash("year");
2301	    if (!NIL_P(y)) {
2302		y = f_add(f_negate(y), INT2FIX(1));
2303		set_hash("year", y);
2304	    }
2305	}
2306
2307	if (RTEST(ref_hash("_comp"))) {
2308	    VALUE y;
2309
2310	    y = ref_hash("cwyear");
2311	    if (!NIL_P(y))
2312		if (f_ge_p(y, INT2FIX(0)) && f_le_p(y, INT2FIX(99))) {
2313		    if (f_ge_p(y, INT2FIX(69)))
2314			set_hash("cwyear", f_add(y, INT2FIX(1900)));
2315		    else
2316			set_hash("cwyear", f_add(y, INT2FIX(2000)));
2317		}
2318	    y = ref_hash("year");
2319	    if (!NIL_P(y))
2320		if (f_ge_p(y, INT2FIX(0)) && f_le_p(y, INT2FIX(99))) {
2321		    if (f_ge_p(y, INT2FIX(69)))
2322			set_hash("year", f_add(y, INT2FIX(1900)));
2323		    else
2324			set_hash("year", f_add(y, INT2FIX(2000)));
2325		}
2326	}
2327
2328    }
2329
2330    del_hash("_bc");
2331    del_hash("_comp");
2332
2333    {
2334	VALUE zone = ref_hash("zone");
2335	if (!NIL_P(zone) && NIL_P(ref_hash("offset")))
2336	    set_hash("offset", date_zone_to_diff(zone));
2337    }
2338
2339    rb_backref_set(backref);
2340
2341    return hash;
2342}
2343
2344static VALUE
2345comp_year69(VALUE y)
2346{
2347    if (f_ge_p(y, INT2FIX(69)))
2348	return f_add(y, INT2FIX(1900));
2349    return f_add(y, INT2FIX(2000));
2350}
2351
2352static VALUE
2353comp_year50(VALUE y)
2354{
2355    if (f_ge_p(y, INT2FIX(50)))
2356	return f_add(y, INT2FIX(1900));
2357    return f_add(y, INT2FIX(2000));
2358}
2359
2360static VALUE
2361sec_fraction(VALUE f)
2362{
2363    return rb_rational_new2(str2num(f),
2364			    f_expt(INT2FIX(10),
2365				   LONG2NUM(RSTRING_LEN(f))));
2366}
2367
2368#define SNUM 14
2369
2370static int
2371iso8601_ext_datetime_cb(VALUE m, VALUE hash)
2372{
2373    VALUE s[SNUM + 1], y;
2374
2375    {
2376	int i;
2377	s[0] = Qnil;
2378	for (i = 1; i <= SNUM; i++)
2379	    s[i] = rb_reg_nth_match(i, m);
2380    }
2381
2382    if (!NIL_P(s[3])) {
2383	set_hash("mday", str2num(s[3]));
2384	if (strcmp(RSTRING_PTR(s[1]), "-") != 0) {
2385	    y = str2num(s[1]);
2386	    if (RSTRING_LEN(s[1]) < 4)
2387		y = comp_year69(y);
2388	    set_hash("year", y);
2389	}
2390	if (NIL_P(s[2])) {
2391	    if (strcmp(RSTRING_PTR(s[1]), "-") != 0)
2392		return 0;
2393	}
2394	else
2395	    set_hash("mon", str2num(s[2]));
2396    }
2397    else if (!NIL_P(s[5])) {
2398	set_hash("yday", str2num(s[5]));
2399	if (!NIL_P(s[4])) {
2400	    y = str2num(s[4]);
2401	    if (RSTRING_LEN(s[4]) < 4)
2402		y = comp_year69(y);
2403	    set_hash("year", y);
2404	}
2405    }
2406    else if (!NIL_P(s[8])) {
2407	set_hash("cweek", str2num(s[7]));
2408	set_hash("cwday", str2num(s[8]));
2409	if (!NIL_P(s[6])) {
2410	    y = str2num(s[6]);
2411	    if (RSTRING_LEN(s[6]) < 4)
2412		y = comp_year69(y);
2413	    set_hash("cwyear", y);
2414	}
2415    }
2416    else if (!NIL_P(s[9])) {
2417	set_hash("cwday", str2num(s[9]));
2418    }
2419    if (!NIL_P(s[10])) {
2420	set_hash("hour", str2num(s[10]));
2421	set_hash("min", str2num(s[11]));
2422	if (!NIL_P(s[12]))
2423	    set_hash("sec", str2num(s[12]));
2424    }
2425    if (!NIL_P(s[13])) {
2426	set_hash("sec_fraction", sec_fraction(s[13]));
2427    }
2428    if (!NIL_P(s[14])) {
2429	set_hash("zone", s[14]);
2430	set_hash("offset", date_zone_to_diff(s[14]));
2431    }
2432
2433    return 1;
2434}
2435
2436static int
2437iso8601_ext_datetime(VALUE str, VALUE hash)
2438{
2439    static const char pat_source[] =
2440	"\\A\\s*(?:([-+]?\\d{2,}|-)-(\\d{2})?-(\\d{2})|"
2441		"([-+]?\\d{2,})?-(\\d{3})|"
2442		"(\\d{4}|\\d{2})?-w(\\d{2})-(\\d)|"
2443		"-w-(\\d))"
2444	"(?:t"
2445	"(\\d{2}):(\\d{2})(?::(\\d{2})(?:[,.](\\d+))?)?"
2446	"(z|[-+]\\d{2}(?::?\\d{2})?)?)?\\s*\\z";
2447    static VALUE pat = Qnil;
2448
2449    REGCOMP_I(pat);
2450    MATCH(str, pat, iso8601_ext_datetime_cb);
2451}
2452
2453#undef SNUM
2454#define SNUM 17
2455
2456static int
2457iso8601_bas_datetime_cb(VALUE m, VALUE hash)
2458{
2459    VALUE s[SNUM + 1], y;
2460
2461    {
2462	int i;
2463	s[0] = Qnil;
2464	for (i = 1; i <= SNUM; i++)
2465	    s[i] = rb_reg_nth_match(i, m);
2466    }
2467
2468    if (!NIL_P(s[3])) {
2469	set_hash("mday", str2num(s[3]));
2470	if (strcmp(RSTRING_PTR(s[1]), "--") != 0) {
2471	    y = str2num(s[1]);
2472	    if (RSTRING_LEN(s[1]) < 4)
2473		y = comp_year69(y);
2474	    set_hash("year", y);
2475	}
2476	if (*RSTRING_PTR(s[2]) == '-') {
2477	    if (strcmp(RSTRING_PTR(s[1]), "--") != 0)
2478		return 0;
2479	}
2480	else
2481	    set_hash("mon", str2num(s[2]));
2482    }
2483    else if (!NIL_P(s[5])) {
2484	set_hash("yday", str2num(s[5]));
2485	y = str2num(s[4]);
2486	if (RSTRING_LEN(s[4]) < 4)
2487	    y = comp_year69(y);
2488	set_hash("year", y);
2489    }
2490    else if (!NIL_P(s[6])) {
2491	set_hash("yday", str2num(s[6]));
2492    }
2493    else if (!NIL_P(s[9])) {
2494	set_hash("cweek", str2num(s[8]));
2495	set_hash("cwday", str2num(s[9]));
2496	y = str2num(s[7]);
2497	if (RSTRING_LEN(s[7]) < 4)
2498	    y = comp_year69(y);
2499	set_hash("cwyear", y);
2500    }
2501    else if (!NIL_P(s[11])) {
2502	set_hash("cweek", str2num(s[10]));
2503	set_hash("cwday", str2num(s[11]));
2504    }
2505    else if (!NIL_P(s[12])) {
2506	set_hash("cwday", str2num(s[12]));
2507    }
2508    if (!NIL_P(s[13])) {
2509	set_hash("hour", str2num(s[13]));
2510	set_hash("min", str2num(s[14]));
2511	if (!NIL_P(s[15]))
2512	    set_hash("sec", str2num(s[15]));
2513    }
2514    if (!NIL_P(s[16])) {
2515	set_hash("sec_fraction", sec_fraction(s[16]));
2516    }
2517    if (!NIL_P(s[17])) {
2518	set_hash("zone", s[17]);
2519	set_hash("offset", date_zone_to_diff(s[17]));
2520    }
2521
2522    return 1;
2523}
2524
2525static int
2526iso8601_bas_datetime(VALUE str, VALUE hash)
2527{
2528    static const char pat_source[] =
2529	"\\A\\s*(?:([-+]?(?:\\d{4}|\\d{2})|--)(\\d{2}|-)(\\d{2})|"
2530		   "([-+]?(?:\\d{4}|\\d{2}))(\\d{3})|"
2531		   "-(\\d{3})|"
2532		   "(\\d{4}|\\d{2})w(\\d{2})(\\d)|"
2533		   "-w(\\d{2})(\\d)|"
2534		   "-w-(\\d))"
2535	"(?:t?"
2536	"(\\d{2})(\\d{2})(?:(\\d{2})(?:[,.](\\d+))?)?"
2537	"(z|[-+]\\d{2}(?:\\d{2})?)?)?\\s*\\z";
2538    static VALUE pat = Qnil;
2539
2540    REGCOMP_I(pat);
2541    MATCH(str, pat, iso8601_bas_datetime_cb);
2542}
2543
2544#undef SNUM
2545#define SNUM 5
2546
2547static int
2548iso8601_ext_time_cb(VALUE m, VALUE hash)
2549{
2550    VALUE s[SNUM + 1];
2551
2552    {
2553	int i;
2554	s[0] = Qnil;
2555	for (i = 1; i <= SNUM; i++)
2556	    s[i] = rb_reg_nth_match(i, m);
2557    }
2558
2559    set_hash("hour", str2num(s[1]));
2560    set_hash("min", str2num(s[2]));
2561    if (!NIL_P(s[3]))
2562	set_hash("sec", str2num(s[3]));
2563    if (!NIL_P(s[4]))
2564	set_hash("sec_fraction", sec_fraction(s[4]));
2565    if (!NIL_P(s[5])) {
2566	set_hash("zone", s[5]);
2567	set_hash("offset", date_zone_to_diff(s[5]));
2568    }
2569
2570    return 1;
2571}
2572
2573#define iso8601_bas_time_cb iso8601_ext_time_cb
2574
2575static int
2576iso8601_ext_time(VALUE str, VALUE hash)
2577{
2578    static const char pat_source[] =
2579	"\\A\\s*(\\d{2}):(\\d{2})(?::(\\d{2})(?:[,.](\\d+))?"
2580	"(z|[-+]\\d{2}(:?\\d{2})?)?)?\\s*\\z";
2581    static VALUE pat = Qnil;
2582
2583    REGCOMP_I(pat);
2584    MATCH(str, pat, iso8601_ext_time_cb);
2585}
2586
2587static int
2588iso8601_bas_time(VALUE str, VALUE hash)
2589{
2590    static const char pat_source[] =
2591	"\\A\\s*(\\d{2})(\\d{2})(?:(\\d{2})(?:[,.](\\d+))?"
2592	"(z|[-+]\\d{2}(\\d{2})?)?)?\\s*\\z";
2593    static VALUE pat = Qnil;
2594
2595    REGCOMP_I(pat);
2596    MATCH(str, pat, iso8601_bas_time_cb);
2597}
2598
2599VALUE
2600date__iso8601(VALUE str)
2601{
2602    VALUE backref, hash;
2603
2604    backref = rb_backref_get();
2605    rb_match_busy(backref);
2606
2607    hash = rb_hash_new();
2608
2609    if (iso8601_ext_datetime(str, hash))
2610	goto ok;
2611    if (iso8601_bas_datetime(str, hash))
2612	goto ok;
2613    if (iso8601_ext_time(str, hash))
2614	goto ok;
2615    if (iso8601_bas_time(str, hash))
2616	goto ok;
2617
2618  ok:
2619    rb_backref_set(backref);
2620
2621    return hash;
2622}
2623
2624#undef SNUM
2625#define SNUM 8
2626
2627static int
2628rfc3339_cb(VALUE m, VALUE hash)
2629{
2630    VALUE s[SNUM + 1];
2631
2632    {
2633	int i;
2634	s[0] = Qnil;
2635	for (i = 1; i <= SNUM; i++)
2636	    s[i] = rb_reg_nth_match(i, m);
2637    }
2638
2639    set_hash("year", str2num(s[1]));
2640    set_hash("mon", str2num(s[2]));
2641    set_hash("mday", str2num(s[3]));
2642    set_hash("hour", str2num(s[4]));
2643    set_hash("min", str2num(s[5]));
2644    set_hash("sec", str2num(s[6]));
2645    set_hash("zone", s[8]);
2646    set_hash("offset", date_zone_to_diff(s[8]));
2647    if (!NIL_P(s[7]))
2648	set_hash("sec_fraction", sec_fraction(s[7]));
2649
2650    return 1;
2651}
2652
2653static int
2654rfc3339(VALUE str, VALUE hash)
2655{
2656    static const char pat_source[] =
2657	"\\A\\s*(-?\\d{4})-(\\d{2})-(\\d{2})"
2658	"(?:t|\\s)"
2659	"(\\d{2}):(\\d{2}):(\\d{2})(?:\\.(\\d+))?"
2660	"(z|[-+]\\d{2}:\\d{2})\\s*\\z";
2661    static VALUE pat = Qnil;
2662
2663    REGCOMP_I(pat);
2664    MATCH(str, pat, rfc3339_cb);
2665}
2666
2667VALUE
2668date__rfc3339(VALUE str)
2669{
2670    VALUE backref, hash;
2671
2672    backref = rb_backref_get();
2673    rb_match_busy(backref);
2674
2675    hash = rb_hash_new();
2676    rfc3339(str, hash);
2677    rb_backref_set(backref);
2678    return hash;
2679}
2680
2681#undef SNUM
2682#define SNUM 8
2683
2684static int
2685xmlschema_datetime_cb(VALUE m, VALUE hash)
2686{
2687    VALUE s[SNUM + 1];
2688
2689    {
2690	int i;
2691	s[0] = Qnil;
2692	for (i = 1; i <= SNUM; i++)
2693	    s[i] = rb_reg_nth_match(i, m);
2694    }
2695
2696    set_hash("year", str2num(s[1]));
2697    if (!NIL_P(s[2]))
2698	set_hash("mon", str2num(s[2]));
2699    if (!NIL_P(s[3]))
2700	set_hash("mday", str2num(s[3]));
2701    if (!NIL_P(s[4]))
2702	set_hash("hour", str2num(s[4]));
2703    if (!NIL_P(s[5]))
2704	set_hash("min", str2num(s[5]));
2705    if (!NIL_P(s[6]))
2706	set_hash("sec", str2num(s[6]));
2707    if (!NIL_P(s[7]))
2708	set_hash("sec_fraction", sec_fraction(s[7]));
2709    if (!NIL_P(s[8])) {
2710	set_hash("zone", s[8]);
2711	set_hash("offset", date_zone_to_diff(s[8]));
2712    }
2713
2714    return 1;
2715}
2716
2717static int
2718xmlschema_datetime(VALUE str, VALUE hash)
2719{
2720    static const char pat_source[] =
2721	"\\A\\s*(-?\\d{4,})(?:-(\\d{2})(?:-(\\d{2}))?)?"
2722	"(?:t"
2723	  "(\\d{2}):(\\d{2}):(\\d{2})(?:\\.(\\d+))?)?"
2724	"(z|[-+]\\d{2}:\\d{2})?\\s*\\z";
2725    static VALUE pat = Qnil;
2726
2727    REGCOMP_I(pat);
2728    MATCH(str, pat, xmlschema_datetime_cb);
2729}
2730
2731#undef SNUM
2732#define SNUM 5
2733
2734static int
2735xmlschema_time_cb(VALUE m, VALUE hash)
2736{
2737    VALUE s[SNUM + 1];
2738
2739    {
2740	int i;
2741	s[0] = Qnil;
2742	for (i = 1; i <= SNUM; i++)
2743	    s[i] = rb_reg_nth_match(i, m);
2744    }
2745
2746    set_hash("hour", str2num(s[1]));
2747    set_hash("min", str2num(s[2]));
2748    if (!NIL_P(s[3]))
2749	set_hash("sec", str2num(s[3]));
2750    if (!NIL_P(s[4]))
2751	set_hash("sec_fraction", sec_fraction(s[4]));
2752    if (!NIL_P(s[5])) {
2753	set_hash("zone", s[5]);
2754	set_hash("offset", date_zone_to_diff(s[5]));
2755    }
2756
2757    return 1;
2758}
2759
2760static int
2761xmlschema_time(VALUE str, VALUE hash)
2762{
2763    static const char pat_source[] =
2764	"\\A\\s*(\\d{2}):(\\d{2}):(\\d{2})(?:\\.(\\d+))?"
2765	"(z|[-+]\\d{2}:\\d{2})?\\s*\\z";
2766    static VALUE pat = Qnil;
2767
2768    REGCOMP_I(pat);
2769    MATCH(str, pat, xmlschema_time_cb);
2770}
2771
2772#undef SNUM
2773#define SNUM 4
2774
2775static int
2776xmlschema_trunc_cb(VALUE m, VALUE hash)
2777{
2778    VALUE s[SNUM + 1];
2779
2780    {
2781	int i;
2782	s[0] = Qnil;
2783	for (i = 1; i <= SNUM; i++)
2784	    s[i] = rb_reg_nth_match(i, m);
2785    }
2786
2787    if (!NIL_P(s[1]))
2788	set_hash("mon", str2num(s[1]));
2789    if (!NIL_P(s[2]))
2790	set_hash("mday", str2num(s[2]));
2791    if (!NIL_P(s[3]))
2792	set_hash("mday", str2num(s[3]));
2793    if (!NIL_P(s[4])) {
2794	set_hash("zone", s[4]);
2795	set_hash("offset", date_zone_to_diff(s[4]));
2796    }
2797
2798    return 1;
2799}
2800
2801static int
2802xmlschema_trunc(VALUE str, VALUE hash)
2803{
2804    static const char pat_source[] =
2805	"\\A\\s*(?:--(\\d{2})(?:-(\\d{2}))?|---(\\d{2}))"
2806	"(z|[-+]\\d{2}:\\d{2})?\\s*\\z";
2807    static VALUE pat = Qnil;
2808
2809    REGCOMP_I(pat);
2810    MATCH(str, pat, xmlschema_trunc_cb);
2811}
2812
2813VALUE
2814date__xmlschema(VALUE str)
2815{
2816    VALUE backref, hash;
2817
2818    backref = rb_backref_get();
2819    rb_match_busy(backref);
2820
2821    hash = rb_hash_new();
2822
2823    if (xmlschema_datetime(str, hash))
2824	goto ok;
2825    if (xmlschema_time(str, hash))
2826	goto ok;
2827    if (xmlschema_trunc(str, hash))
2828	goto ok;
2829
2830  ok:
2831    rb_backref_set(backref);
2832
2833    return hash;
2834}
2835
2836#undef SNUM
2837#define SNUM 8
2838
2839static int
2840rfc2822_cb(VALUE m, VALUE hash)
2841{
2842    VALUE s[SNUM + 1], y;
2843
2844    {
2845	int i;
2846	s[0] = Qnil;
2847	for (i = 1; i <= SNUM; i++)
2848	    s[i] = rb_reg_nth_match(i, m);
2849    }
2850
2851    if (!NIL_P(s[1])) {
2852	set_hash("wday", INT2FIX(day_num(s[1])));
2853    }
2854    set_hash("mday", str2num(s[2]));
2855    set_hash("mon", INT2FIX(mon_num(s[3])));
2856    y = str2num(s[4]);
2857    if (RSTRING_LEN(s[4]) < 4)
2858	y = comp_year50(y);
2859    set_hash("year", y);
2860    set_hash("hour", str2num(s[5]));
2861    set_hash("min", str2num(s[6]));
2862    if (!NIL_P(s[7]))
2863	set_hash("sec", str2num(s[7]));
2864    set_hash("zone", s[8]);
2865    set_hash("offset", date_zone_to_diff(s[8]));
2866
2867    return 1;
2868}
2869
2870static int
2871rfc2822(VALUE str, VALUE hash)
2872{
2873    static const char pat_source[] =
2874	"\\A\\s*(?:(" ABBR_DAYS ")\\s*,\\s+)?"
2875	"(\\d{1,2})\\s+"
2876	"(" ABBR_MONTHS ")\\s+"
2877	"(-?\\d{2,})\\s+"
2878	"(\\d{2}):(\\d{2})(?::(\\d{2}))?\\s*"
2879	"([-+]\\d{4}|ut|gmt|e[sd]t|c[sd]t|m[sd]t|p[sd]t|[a-ik-z])\\s*\\z";
2880    static VALUE pat = Qnil;
2881
2882    REGCOMP_I(pat);
2883    MATCH(str, pat, rfc2822_cb);
2884}
2885
2886VALUE
2887date__rfc2822(VALUE str)
2888{
2889    VALUE backref, hash;
2890
2891    backref = rb_backref_get();
2892    rb_match_busy(backref);
2893
2894    hash = rb_hash_new();
2895    rfc2822(str, hash);
2896    rb_backref_set(backref);
2897    return hash;
2898}
2899
2900#undef SNUM
2901#define SNUM 8
2902
2903static int
2904httpdate_type1_cb(VALUE m, VALUE hash)
2905{
2906    VALUE s[SNUM + 1];
2907
2908    {
2909	int i;
2910	s[0] = Qnil;
2911	for (i = 1; i <= SNUM; i++)
2912	    s[i] = rb_reg_nth_match(i, m);
2913    }
2914
2915    set_hash("wday", INT2FIX(day_num(s[1])));
2916    set_hash("mday", str2num(s[2]));
2917    set_hash("mon", INT2FIX(mon_num(s[3])));
2918    set_hash("year", str2num(s[4]));
2919    set_hash("hour", str2num(s[5]));
2920    set_hash("min", str2num(s[6]));
2921    set_hash("sec", str2num(s[7]));
2922    set_hash("zone", s[8]);
2923    set_hash("offset", INT2FIX(0));
2924
2925    return 1;
2926}
2927
2928static int
2929httpdate_type1(VALUE str, VALUE hash)
2930{
2931    static const char pat_source[] =
2932	"\\A\\s*(" ABBR_DAYS ")\\s*,\\s+"
2933	"(\\d{2})\\s+"
2934	"(" ABBR_MONTHS ")\\s+"
2935	"(-?\\d{4})\\s+"
2936	"(\\d{2}):(\\d{2}):(\\d{2})\\s+"
2937	"(gmt)\\s*\\z";
2938    static VALUE pat = Qnil;
2939
2940    REGCOMP_I(pat);
2941    MATCH(str, pat, httpdate_type1_cb);
2942}
2943
2944#undef SNUM
2945#define SNUM 8
2946
2947static int
2948httpdate_type2_cb(VALUE m, VALUE hash)
2949{
2950    VALUE s[SNUM + 1], y;
2951
2952    {
2953	int i;
2954	s[0] = Qnil;
2955	for (i = 1; i <= SNUM; i++)
2956	    s[i] = rb_reg_nth_match(i, m);
2957    }
2958
2959    set_hash("wday", INT2FIX(day_num(s[1])));
2960    set_hash("mday", str2num(s[2]));
2961    set_hash("mon", INT2FIX(mon_num(s[3])));
2962    y = str2num(s[4]);
2963    if (f_ge_p(y, INT2FIX(0)) && f_le_p(y, INT2FIX(99)))
2964	y = comp_year69(y);
2965    set_hash("year", y);
2966    set_hash("hour", str2num(s[5]));
2967    set_hash("min", str2num(s[6]));
2968    set_hash("sec", str2num(s[7]));
2969    set_hash("zone", s[8]);
2970    set_hash("offset", INT2FIX(0));
2971
2972    return 1;
2973}
2974
2975static int
2976httpdate_type2(VALUE str, VALUE hash)
2977{
2978    static const char pat_source[] =
2979	"\\A\\s*(" DAYS ")\\s*,\\s+"
2980	"(\\d{2})\\s*-\\s*"
2981	"(" ABBR_MONTHS ")\\s*-\\s*"
2982	"(\\d{2})\\s+"
2983	"(\\d{2}):(\\d{2}):(\\d{2})\\s+"
2984	"(gmt)\\s*\\z";
2985    static VALUE pat = Qnil;
2986
2987    REGCOMP_I(pat);
2988    MATCH(str, pat, httpdate_type2_cb);
2989}
2990
2991#undef SNUM
2992#define SNUM 7
2993
2994static int
2995httpdate_type3_cb(VALUE m, VALUE hash)
2996{
2997    VALUE s[SNUM + 1];
2998
2999    {
3000	int i;
3001	s[0] = Qnil;
3002	for (i = 1; i <= SNUM; i++)
3003	    s[i] = rb_reg_nth_match(i, m);
3004    }
3005
3006    set_hash("wday", INT2FIX(day_num(s[1])));
3007    set_hash("mon", INT2FIX(mon_num(s[2])));
3008    set_hash("mday", str2num(s[3]));
3009    set_hash("hour", str2num(s[4]));
3010    set_hash("min", str2num(s[5]));
3011    set_hash("sec", str2num(s[6]));
3012    set_hash("year", str2num(s[7]));
3013
3014    return 1;
3015}
3016
3017static int
3018httpdate_type3(VALUE str, VALUE hash)
3019{
3020    static const char pat_source[] =
3021	"\\A\\s*(" ABBR_DAYS ")\\s+"
3022	"(" ABBR_MONTHS ")\\s+"
3023	"(\\d{1,2})\\s+"
3024	"(\\d{2}):(\\d{2}):(\\d{2})\\s+"
3025	"(\\d{4})\\s*\\z";
3026    static VALUE pat = Qnil;
3027
3028    REGCOMP_I(pat);
3029    MATCH(str, pat, httpdate_type3_cb);
3030}
3031
3032VALUE
3033date__httpdate(VALUE str)
3034{
3035    VALUE backref, hash;
3036
3037    backref = rb_backref_get();
3038    rb_match_busy(backref);
3039
3040    hash = rb_hash_new();
3041
3042    if (httpdate_type1(str, hash))
3043	goto ok;
3044    if (httpdate_type2(str, hash))
3045	goto ok;
3046    if (httpdate_type3(str, hash))
3047	goto ok;
3048
3049  ok:
3050    rb_backref_set(backref);
3051
3052    return hash;
3053}
3054
3055#undef SNUM
3056#define SNUM 9
3057
3058static int
3059jisx0301_cb(VALUE m, VALUE hash)
3060{
3061    VALUE s[SNUM + 1];
3062    int ep;
3063
3064    {
3065	int i;
3066	s[0] = Qnil;
3067	for (i = 1; i <= SNUM; i++)
3068	    s[i] = rb_reg_nth_match(i, m);
3069    }
3070
3071    ep = gengo(NIL_P(s[1]) ? 'h' : *RSTRING_PTR(s[1]));
3072    set_hash("year", f_add(str2num(s[2]), INT2FIX(ep)));
3073    set_hash("mon", str2num(s[3]));
3074    set_hash("mday", str2num(s[4]));
3075    if (!NIL_P(s[5])) {
3076	set_hash("hour", str2num(s[5]));
3077	if (!NIL_P(s[6]))
3078	    set_hash("min", str2num(s[6]));
3079	if (!NIL_P(s[7]))
3080	    set_hash("sec", str2num(s[7]));
3081    }
3082    if (!NIL_P(s[8]))
3083	set_hash("sec_fraction", sec_fraction(s[8]));
3084    if (!NIL_P(s[9])) {
3085	set_hash("zone", s[9]);
3086	set_hash("offset", date_zone_to_diff(s[9]));
3087    }
3088
3089    return 1;
3090}
3091
3092static int
3093jisx0301(VALUE str, VALUE hash)
3094{
3095    static const char pat_source[] =
3096	"\\A\\s*([mtsh])?(\\d{2})\\.(\\d{2})\\.(\\d{2})"
3097	"(?:t"
3098	"(?:(\\d{2}):(\\d{2})(?::(\\d{2})(?:[,.](\\d*))?)?"
3099	"(z|[-+]\\d{2}(?::?\\d{2})?)?)?)?\\s*\\z";
3100    static VALUE pat = Qnil;
3101
3102    REGCOMP_I(pat);
3103    MATCH(str, pat, jisx0301_cb);
3104}
3105
3106VALUE
3107date__jisx0301(VALUE str)
3108{
3109    VALUE backref, hash;
3110
3111    backref = rb_backref_get();
3112    rb_match_busy(backref);
3113
3114    hash = rb_hash_new();
3115    if (jisx0301(str, hash))
3116	goto ok;
3117    hash = date__iso8601(str);
3118
3119  ok:
3120    rb_backref_set(backref);
3121    return hash;
3122}
3123
3124/*
3125Local variables:
3126c-file-style: "ruby"
3127End:
3128*/
3129