xref: /inferno-os/appl/lib/w3c/css.b (revision d0e1d143ef6f03c75c008c7ec648859dd260cbab)
1implement CSS;
2
3#
4# CSS2 parsing module
5#
6# CSS2.1 style sheets
7#
8# Copyright © 2001, 2005 Vita Nuova Holdings Limited.  All rights reserved.
9#
10
11include "sys.m";
12	sys: Sys;
13
14include "css.m";
15
16B, NUMBER, IDENT, STRING, URL, PERCENTAGE, UNIT,
17	HASH, ATKEYWORD, IMPORTANT, IMPORT, PSEUDO, CLASS, INCLUDES,
18	DASHMATCH, FUNCTION: con 16rE000+iota;
19
20toknames := array[] of{
21	B-B => "Zero",
22	NUMBER-B => "NUMBER",
23	IDENT-B => "IDENT",
24	STRING-B => "STRING",
25	URL-B => "URL",
26	PERCENTAGE-B => "PERCENTAGE",
27	UNIT-B => "UNIT",
28	HASH-B => "HASH",
29	ATKEYWORD-B => "ATKEYWORD",
30	IMPORTANT-B => "IMPORTANT",
31	CLASS-B => "CLASS",
32	INCLUDES-B => "INCLUDES",
33	DASHMATCH-B => "DASHMATCH",
34	PSEUDO-B => "PSEUDO",
35	FUNCTION-B => "FUNCTION",
36};
37
38printdiag := 0;
39
40init(d: int)
41{
42	sys = load Sys Sys->PATH;
43	printdiag = d;
44}
45
46parse(s: string): (ref Stylesheet, string)
47{
48	return stylesheet(ref Cparse(-1, 0, nil, nil, Clex.new(s,1)));
49}
50
51parsedecl(s: string): (list of ref Decl, string)
52{
53	return (declarations(ref Cparse(-1, 0, nil, nil, Clex.new(s,0))), nil);
54}
55
56ptok(c: int): string
57{
58	if(c < 0)
59		return "eof";
60	if(c == 0)
61		return "zero?";
62	if(c >= B)
63		return sys->sprint("%s", toknames[c-B]);
64	return sys->sprint("%c", c);
65}
66
67Cparse: adt {
68	lookahead:	int;
69	eof:	int;
70	value:	string;
71	suffix:	string;
72	cs:	ref Clex;
73
74	get:	fn(nil: self ref Cparse): int;
75	look:	fn(nil: self ref Cparse): int;
76	unget:	fn(nil: self ref Cparse, tok: int);
77	skipto:	fn(nil: self ref Cparse, followset: string): int;
78	synerr:	fn(nil: self ref Cparse, s: string);
79};
80
81Cparse.get(p: self ref Cparse): int
82{
83	if((c := p.lookahead) >= 0){
84		p.lookahead = -1;
85		return c;
86	}
87	if(p.eof)
88		return -1;
89	(c, p.value, p.suffix) = csslex(p.cs);
90	if(c < 0)
91		p.eof = 1;
92	if(printdiag > 1)
93		sys->print("lex: %s v=%s s=%s\n", ptok(c), p.value, p.suffix);
94	return c;
95}
96
97Cparse.look(p: self ref Cparse): int
98{
99	c := p.get();
100	p.unget(c);
101	return c;
102}
103
104Cparse.unget(p: self ref Cparse, c: int)
105{
106	if(p.lookahead >= 0)
107		raise "css: internal error: Cparse.unget";
108	p.lookahead = c;	# note that p.value and p.suffix are assumed to be those of c
109}
110
111Cparse.skipto(p: self ref Cparse, followset: string): int
112{
113	while((c := p.get()) >= 0)
114		for(i := 0; i < len followset; i++)
115			if(followset[i] == c){
116				p.unget(c);
117				return c;
118			}
119	return -1;
120}
121
122Cparse.synerr(p: self ref Cparse, s: string)
123{
124	p.cs.synerr(s);
125}
126
127#
128# stylesheet:
129#	["@charset" STRING ';']?
130#	[CDO|CDC]* [import [CDO|CDC]*]*
131#	[[ruleset | media | page ] [CDO|CDC]*]*
132# import:
133#	"@import" [STRING|URL] [ medium [',' medium]*]? ';'
134# media:
135#	"@media" medium [',' medium]* '{' ruleset* '}'
136# medium:
137#	IDENT
138# page:
139#	"@page" pseudo_page? '{' declaration [';' declaration]* '}'
140# pseudo_page:
141#	':' IDENT
142#
143
144stylesheet(p: ref Cparse): (ref Stylesheet, string)
145{
146	charset: string;
147	if(atkeywd(p, "@charset")){
148		if(itisa(p, STRING)){
149			charset = p.value;
150			itisa(p, ';');
151		}else
152			p.synerr("bad @charset declaration");
153	}
154	imports: list of ref Import;
155	while(atkeywd(p, "@import")){
156		c := p.get();
157		if(c == STRING || c == URL){
158			name := p.value;
159			media: list of string;
160			c = p.get();
161			if(c == IDENT){	# optional medium [, ...]
162				p.unget(c);
163				media = medialist(p);
164			}
165			imports = ref Import(name, media) :: imports;
166		}else
167			p.synerr("bad @import");
168		if(c != ';'){
169			p.synerr("missing ; in @import");
170			p.unget(c);
171			if(p.skipto(";}") < 0)
172				break;
173		}
174	}
175	imports = rev(imports);
176
177	stmts: list of ref Statement;
178	do{
179		while((c := p.get()) == ATKEYWORD)
180			case p.value {
181			"@media" =>	# medium[,medium]* { ruleset*}
182				media := medialist(p);
183				if(!itisa(p, '{')){
184					p.synerr("bad @media");
185					skipatrule("@media", p);
186					continue;
187				}
188				rules: list of ref Statement.Ruleset;
189				do{
190					rule := checkrule(p);
191					if(rule != nil)
192						rules = rule :: rules;
193				}while(!itisa(p, '}') && !p.eof);
194				stmts = ref Statement.Media(media, rev(rules)) :: stmts;
195			"@page" =>	# [:ident]? { declaration [; declaration]* }
196				pseudo: string;
197				if(itisa(p, PSEUDO))
198					pseudo = p.value;
199				if(!itisa(p, '{')){
200					p.synerr("bad @page");
201					skipatrule("@page", p);
202					continue;
203				}
204				decls := declarations(p);
205				if(!itisa(p, '}')){
206					p.synerr("unclosed @page declaration block");
207					skipatrule("@page", p);
208					continue;
209				}
210				stmts = ref Statement.Page(pseudo, decls) :: stmts;
211			* =>
212				skipatrule(p.value, p);	# skip unknown or misplaced at-rule
213			}
214		p.unget(c);
215		rule := checkrule(p);
216		if(rule != nil)
217			stmts = rule :: stmts;
218	}while(!p.eof);
219	rl := stmts;
220	stmts = nil;
221	for(; rl != nil; rl = tl rl)
222		stmts = hd rl :: stmts;
223	return (ref Stylesheet(charset, imports, stmts), nil);
224}
225
226checkrule(p: ref Cparse): ref Statement.Ruleset
227{
228	(rule, err) := ruleset(p);
229	if(rule == nil){
230		if(err != nil){
231			p.synerr(sys->sprint("bad ruleset: %s", err));
232			p.get();	# make some progress
233		}
234	}
235	return rule;
236}
237
238medialist(p: ref Cparse): list of string
239{
240	media: list of string;
241	do{
242		c := p.get();
243		if(c != IDENT){
244			p.unget(c);
245			p.synerr("missing medium identifier");
246			break;
247		}
248		media = p.value :: media;
249	}while(itisa(p, ','));
250	return rev(media);
251}
252
253itisa(p: ref Cparse, expect: int): int
254{
255	if((c := p.get()) == expect)
256		return 1;
257	p.unget(c);
258	return 0;
259}
260
261atkeywd(p: ref Cparse, expect: string): int
262{
263	if((c := p.get()) == ATKEYWORD && p.value == expect)
264		return 1;
265	p.unget(c);
266	return 0;
267}
268
269skipatrule(name: string, p: ref Cparse)
270{
271	if(printdiag)
272		sys->print("skip unimplemented or misplaced %s\n", name);
273	if((c := p.get()) == '{'){	# block
274		for(nesting := '}' :: nil; nesting != nil && c >= 0; nesting = tl nesting){
275			while((c = p.cs.getc()) >= 0 && c != hd nesting)
276				case c {
277				'{' =>
278					nesting = '}' :: nesting;
279				'(' =>
280					nesting = ')' :: nesting;
281				'[' =>
282					nesting = ']' :: nesting;
283				'"' or '\'' =>
284					quotedstring(p.cs, c);
285				}
286		}
287	}else{
288		while(c >= 0 && c != ';')
289			c = p.get();
290	}
291}
292
293# ruleset:
294#	selector [','  S* selector]* '{' S* declaration [';' S* declaration]* '}' S*
295
296ruleset(p: ref Cparse): (ref Statement.Ruleset, string)
297{
298	selectors: list of list of (int, list of ref Select);
299	c := -1;
300	do{
301		s := selector(p);
302		if(s == nil){
303			if(p.eof)
304				return (nil, nil);
305			p.synerr("expected selector");
306			if(p.skipto(",{}") < 0)
307				return (nil, nil);
308			c = p.look();
309		}else
310			selectors = s :: selectors;
311	}while((c = p.get()) == ',');
312	if(c != '{')
313		return (nil, "expected declaration block");
314	sl := selectors;
315	selectors = nil;
316	for(; sl != nil; sl = tl sl)
317		selectors = hd sl :: selectors;
318	decls := declarations(p);
319	if(!itisa(p, '}')){
320		p.synerr("unclosed declaration block");
321	}
322	return (ref Statement.Ruleset(selectors, decls), nil);
323}
324
325declarations(p: ref Cparse): list of ref Decl
326{
327	decls: list of ref Decl;
328	c: int;
329	do{
330		(d, e) := declaration(p);
331		if(d != nil)
332			decls = d :: decls;
333		else if(e != nil){
334			p.synerr("ruleset declaration: "+e);
335			if((c = p.skipto(";}")) < 0)
336				break;
337		}
338	}while((c = p.get()) == ';');
339	p.unget(c);
340	l := decls;
341	for(decls = nil; l != nil; l = tl l)
342		decls = hd l :: decls;
343	return decls;
344}
345
346# selector:
347#	simple_selector [combinator simple_selector]*
348# combinator:
349#	'+' S* | '>' S* | /* empty */
350#
351
352selector(p: ref Cparse): list of (int, list of ref Select)
353{
354	sel: list of (int, list of ref Select);
355	op := ' ';
356	while((s := selector1(p)) != nil){
357		sel = (op, s) :: sel;
358		if((c := p.look()) == '+' || c == '>')
359			op = p.get();
360		else
361			op = ' ';
362	}
363	l: list of (int, list of ref Select);
364	for(; sel != nil; sel = tl sel)
365		l = hd sel :: l;
366	return l;
367}
368
369#
370# simple_selector:
371#	element_name? [HASH | class | attrib | pseudo]* S*
372# element_name:
373#	IDENT | '*'
374# class:
375#	'.' IDENT
376# attrib:
377#	'[' S* IDENT S* [ [ '=' | INCLUDES | DASHMATCH ] S* [IDENT | STRING] S* ]? ']'
378# pseudo
379#	':' [ IDENT | FUNCTION S* IDENT? S* ')' ]
380
381selector1(p: ref Cparse): list of ref Select
382{
383	sel: list of ref Select;
384	c := p.get();
385	if(c == IDENT)
386		sel = ref Select.Element(p.value) :: sel;
387	else if(c== '*')
388		sel = ref Select.Any("*") :: sel;
389	else
390		p.unget(c);
391Sel:
392	for(;;){
393		c = p.get();
394		case c {
395		HASH =>
396			sel = ref Select.ID(p.value) :: sel;
397		CLASS =>
398			sel = ref Select.Class(p.value) :: sel;
399		'[' =>
400			if(!itisa(p, IDENT))
401				break;
402			name := p.value;
403			case c = p.get() {
404			'=' =>
405				sel = ref Select.Attrib(name, "=", optaval(p)) :: sel;
406			INCLUDES =>
407				sel = ref Select.Attrib(name, "~=", optaval(p)) :: sel;
408			DASHMATCH =>
409				sel = ref Select.Attrib(name, "|=", optaval(p)) :: sel;
410			* =>
411				sel = ref Select.Attrib(name, nil, nil) :: sel;
412				p.unget(c);
413			}
414			if((c = p.get()) != ']'){
415				p.synerr("bad attribute syntax");
416				p.unget(c);
417				break Sel;
418			}
419		PSEUDO =>
420			case c = p.get() {
421			IDENT =>
422				sel = ref Select.Pseudo(p.value) :: sel;
423			FUNCTION =>
424				name := p.value;
425				case c = p.get() {
426				IDENT =>
427					sel = ref Select.Pseudofn(name, lowercase(p.value)) :: sel;
428				')' =>
429					p.unget(c);
430					sel = ref Select.Pseudofn(name, nil) :: sel;
431				* =>
432					p.synerr("bad pseudo-function syntax");
433					p.unget(c);
434					break Sel;
435				}
436				if((c = p.get()) != ')'){
437					p.synerr("missing ')' for pseudo-function");
438					p.unget(c);
439					break Sel;
440				}
441			* =>
442				p.synerr(sys->sprint("unexpected :pseudo: %s:%s", ptok(c), p.value));
443				p.unget(c);
444				break Sel;
445			}
446		* =>
447			p.unget(c);
448			break Sel;
449		}
450		# qualifiers must be adjacent to the first item, and each other
451		c = p.cs.getc();
452		p.cs.ungetc(c);
453		if(isspace(c))
454			break;
455	}
456	sl := sel;
457	for(sel = nil; sl != nil; sl = tl sl)
458		sel = hd sl :: sel;
459	return sel;
460}
461
462optaval(p: ref Cparse): ref Value
463{
464	case c := p.get() {
465	IDENT =>
466		return ref Value.Ident(' ', p.value);
467	STRING =>
468		return ref Value.String(' ', p.value);
469	* =>
470		p.unget(c);
471		return nil;
472	}
473}
474
475# declaration:
476#	property ':' S* expr prio?
477#  |	/* empty */
478# property:
479#	IDENT
480# prio:
481#	IMPORTANT S*	/* ! important */
482
483declaration(p: ref Cparse): (ref Decl, string)
484{
485	c := p.get();
486	if(c != IDENT){
487		p.unget(c);
488		return (nil, nil);
489	}
490	prop := lowercase(p.value);
491	c = p.get();
492	if(c != ':'){
493		p.unget(c);
494		return (nil, "missing :");
495	}
496	values := expr(p);
497	if(values == nil)
498		return (nil, "missing expression(s)");
499	prio := 0;
500	if(p.look() == IMPORTANT){
501		p.get();
502		prio = 1;
503	}
504	return (ref Decl(prop, values, prio), nil);
505}
506
507# expr:
508#	term [operator term]*
509# operator:
510#	'/' | ',' | /* empty */
511
512expr(p: ref Cparse): list of ref Value
513{
514	values: list of ref Value;
515	sep := ' ';
516	while((t := term(p, sep)) != nil){
517		values = t :: values;
518		if((c := p.look()) == '/' || c == ',')
519			sep = p.get();		# need something fancier here?
520		else
521			sep = ' ';
522	}
523	vl := values;
524	for(values = nil; vl != nil; vl = tl vl)
525		values = hd vl :: values;
526	return values;
527}
528
529#
530# term:
531#	unary_operator? [NUMBER | PERCENTAGE | LENGTH | EMS | EXS | ANGLE | TIME | FREQ | function]
532#	| STRING | IDENT | URI | RGB | UNICODERANGE | hexcolour
533# function:
534#	FUNCTION expr ')'
535# unary_operator:
536#	'-' | '+'
537# hexcolour:
538#	HASH S*
539#
540# LENGTH, EMS, ... FREQ have been combined into UNIT here
541#
542# TO DO: UNICODERANGE
543
544term(p: ref Cparse, sep: int): ref Value
545{
546	prefix: string;
547	case p.look(){
548	'+' or '-' =>
549		prefix[0] = p.get();
550	}
551	c := p.get();
552	case c {
553	NUMBER =>
554		return ref Value.Number(sep, prefix+p.value);
555	PERCENTAGE =>
556		return ref Value.Percentage(sep, prefix+p.value);
557	UNIT =>
558		return ref Value.Unit(sep, prefix+p.value, p.suffix);
559	}
560	if(prefix != nil)
561		p.synerr("+/- before non-numeric");
562	case c {
563	STRING =>
564		return ref Value.String(sep, p.value);
565	IDENT =>
566		return ref Value.Ident(sep, lowercase(p.value));
567	URL =>
568		return ref Value.Url(sep, p.value);
569	HASH =>
570		# could check value: 3 or 6 hex digits
571		(r, g, b) := torgb(p.value);
572		if(r < 0)
573			return nil;
574		return ref Value.Hexcolour(sep, p.value, (r,g,b));
575	FUNCTION =>
576		name := p.value;
577		args := expr(p);
578		c = p.get();
579		if(c != ')'){
580			p.synerr(sys->sprint("missing ')' for function %s", name));
581			return nil;
582		}
583		if(name == "rgb"){
584			if(len args != 3){
585				p.synerr("wrong number of arguments to rgb()");
586				return nil;
587			}
588			r := colourof(hd args);
589			g := colourof(hd tl args);
590			b := colourof(hd tl tl args);
591			if(r < 0 || g < 0 || b < 0){
592				p.synerr("invalid rgb() parameters");
593				return nil;
594			}
595			return ref Value.RGB(sep, args, (r,g,b));
596		}
597		return ref Value.Function(sep, name, args);
598	* =>
599		p.unget(c);
600		return nil;
601	}
602}
603
604torgb(s: string): (int, int, int)
605{
606	case len s {
607	3 =>
608		r := hex(s[0]);
609		g := hex(s[1]);
610		b := hex(s[2]);
611		if(r >= 0 && g >= 0 && b >= 0)
612			return ((r<<4)|r, (g<<4)|g, (b<<4)|b);
613	6 =>
614		v := 0;
615		for(i := 0; i < 6; i++){
616			n := hex(s[i]);
617			if(n < 0)
618				return (-1, 0, 0);
619			v = (v<<4) | n;
620		}
621		return (v>>16, (v>>8)&16rFF, v&16rFF);
622	}
623	return (-1, 0, 0);
624}
625
626colourof(v: ref Value): int
627{
628	pick r := v {
629	Number =>
630		return clip(int r.value, 0, 255);
631	Percentage =>
632		# just the integer part
633		return clip((int r.value*255 + 50)/100, 0, 255);
634	* =>
635		return -1;
636	}
637}
638
639clip(v: int, l: int, u: int): int
640{
641	if(v < l)
642		return l;
643	if(v > u)
644		return u;
645	return v;
646}
647
648rev[T](l: list of T): list of T
649{
650	t: list of T;
651	for(; l != nil; l = tl l)
652		t = hd l :: t;
653	return t;
654}
655
656Clex: adt {
657	context:	list of int;	# characters
658	input:	string;
659	lim:	int;
660	n:	int;
661	lineno:	int;
662
663	new:	fn(s: string, lno: int): ref Clex;
664	getc:	fn(cs: self ref Clex): int;
665	ungetc:	fn(cs: self ref Clex, c: int);
666	synerr:	fn(nil: self ref Clex, s: string);
667};
668
669Clex.new(s: string, lno: int): ref Clex
670{
671	return ref Clex(nil, s, len s, 0, lno);
672}
673
674Clex.getc(cs: self ref Clex): int
675{
676	if(cs.context != nil){
677		c := hd cs.context;
678		cs.context = tl cs.context;
679		return c;
680	}
681	if(cs.n >= cs.lim)
682		return -1;
683	c := cs.input[cs.n++];
684	if(c == '\n')
685		cs.lineno++;
686	return c;
687}
688
689Clex.ungetc(cs: self ref Clex, c: int)
690{
691	cs.context = c :: cs.context;
692}
693
694Clex.synerr(cs: self ref Clex, s: string)
695{
696	if(printdiag)
697		sys->fprint(sys->fildes(2), "%d: err: %s\n", cs.lineno, s);
698}
699
700csslex(cs: ref Clex): (int, string, string)
701{
702	for(;;){
703		c := skipws(cs);
704		if(c < 0)
705			return (-1, nil, nil);
706		case c {
707		'<' =>
708			if(seq(cs, "!--"))
709				break;		# <!-- ignore HTML comment start (CDO)
710			return (c, nil, nil);
711		'-' =>
712			if(seq(cs, "->"))
713				break;		# --> ignore HTML comment end (CDC)
714			return (c, nil, nil);
715		':' =>
716			c = cs.getc();
717			cs.ungetc(c);
718			if(isnamec(c, 0))
719				return (PSEUDO, nil, nil);
720			return (':', nil, nil);
721		'#' =>
722			c = cs.getc();
723			if(isnamec(c, 1))
724				return (HASH, name(cs, c), nil);
725			cs.ungetc(c);
726			return ('#', nil, nil);
727		'/' =>
728			if(subseq(cs, '*', 1, 0)){
729				comment(cs);
730				break;
731			}
732			return (c, nil, nil);
733		'\'' or '"' =>
734			return (STRING, quotedstring(cs, c), nil);
735		'0' to '9' or '.' =>
736			if(c == '.'){
737				d := cs.getc();
738				cs.ungetc(d);
739				if(!isdigit(d)){
740					if(isnamec(d, 1))
741						return (CLASS, name(cs, cs.getc()), nil);
742					return ('.', nil, nil);
743				}
744				# apply CSS2 treatment: .55 is a number not a class
745			}
746			val := number(cs, c);
747			c = cs.getc();
748			if(c == '%')
749				return (PERCENTAGE, val, "%");
750			if(isnamec(c, 0))	# use CSS2 interpetation
751				return (UNIT, val, lowercase(name(cs, c)));
752			cs.ungetc(c);
753			return (NUMBER, val, nil);
754		'\\' =>
755			d := cs.getc();
756			if(d >= ' ' && d <= '~' || islatin1(d)){	# probably should handle it in name
757				wd := name(cs, d);
758				return (IDENT, "\\"+wd, nil);
759			}
760			cs.ungetc(d);
761			return ('\\', nil, nil);
762		'@' =>
763			c = cs.getc();
764			if(isnamec(c, 0))	# @something
765				return (ATKEYWORD, "@"+lowercase(name(cs,c)), nil);
766			cs.ungetc(c);
767			return ('@', nil, nil);
768		'!' =>
769			c = skipws(cs);
770			if(isnamec(c, 0)){	# !something
771				wd := name(cs, c);
772				if(lowercase(wd) == "important")
773					return (IMPORTANT, nil, nil);
774				pushback(cs, wd);
775			}else
776				cs.ungetc(c);
777			return ('!', nil, nil);
778		'~' =>
779			if(subseq(cs, '=', 1, 0))
780				return (INCLUDES, "~=", nil);
781			return ('~', nil, nil);
782		'|' =>
783			if(subseq(cs, '=', 1, 0))
784				return (DASHMATCH, "|=", nil);
785			return ('|', nil, nil);
786		* =>
787			if(isnamec(c, 0)){
788				wd := name(cs, c);
789				d := cs.getc();
790				if(d != '('){
791					cs.ungetc(d);
792					return (IDENT, wd, nil);
793				}
794				val := lowercase(wd);
795				if(val == "url")
796					return (URL, url(cs), nil);	# bizarre special case
797				return (FUNCTION, val, nil);
798			}
799			return (c, nil, nil);
800		}
801
802	}
803}
804
805skipws(cs: ref Clex): int
806{
807	for(;;){
808		while((c := cs.getc()) == ' ' || c == '\t' || c == '\n'  || c == '\r' || c == '\f')
809			;
810		if(c != '/')
811			return c;
812		c = cs.getc();
813		if(c != '*'){
814			cs.ungetc(c);
815			return '/';
816		}
817		comment(cs);
818	}
819}
820
821seq(cs: ref Clex, s: string): int
822{
823	for(i := 0; i < len s; i++)
824		if((c := cs.getc()) != s[i])
825			break;
826	if(i == len s)
827		return 1;
828	cs.ungetc(c);
829	while(i > 0)
830		cs.ungetc(s[--i]);
831	if(c < 0)
832		return -1;
833	return 0;
834}
835
836subseq(cs: ref Clex, a: int, t: int, e: int): int
837{
838	if((c := cs.getc()) != a){
839		cs.ungetc(c);
840		return e;
841	}
842	return t;
843}
844
845pushback(cs: ref Clex, wd: string)
846{
847	for(i := len wd; --i >= 0;)
848		cs.ungetc(wd[i]);
849}
850
851comment(cs: ref Clex)
852{
853	while((c := cs.getc()) != '*' || (c = cs.getc()) != '/')
854		if(c < 0) {
855			# end of file in comment
856			break;
857		}
858}
859
860number(cs: ref Clex, c: int): string
861{
862	s: string;
863	for(; isdigit(c); c = cs.getc())
864		s[len s] = c;
865	if(c != '.'){
866		cs.ungetc(c);
867		return s;
868	}
869	if(!isdigit(c = cs.getc())){
870		cs.ungetc(c);
871		cs.ungetc('.');
872		return s;
873	}
874	s[len s] = '.';
875	do{
876		s[len s] = c;
877	}while(isdigit(c = cs.getc()));
878	cs.ungetc(c);
879	return s;
880}
881
882name(cs: ref Clex, c: int): string
883{
884	s: string;
885	for(; isnamec(c, 1); c = cs.getc()){
886		s[len s] = c;
887		if(c == '\\'){
888			c = cs.getc();
889			if(isescapable(c))
890				s[len s] = c;
891		}
892	}
893	cs.ungetc(c);
894	return s;
895}
896
897isescapable(c: int): int
898{
899	return c >= ' ' && c <= '~' || isnamec(c, 1);
900}
901
902islatin1(c: int): int
903{
904	return c >= 16rA1 && c <= 16rFF;	# printable latin-1
905}
906
907isnamec(c: int, notfirst: int): int
908{
909	return c >= 'A' && c <= 'Z' || c >= 'a' && c <= 'z' || c == '\\' ||
910		notfirst && (c >= '0' && c <= '9' || c == '-') ||
911		c >= 16rA1 && c <= 16rFF;	# printable latin-1
912}
913
914isxdigit(c: int): int
915{
916	return c>='0' && c<='9' || c>='a'&&c<='f' || c>='A'&&c<='F';
917}
918
919isdigit(c: int): int
920{
921	return c >= '0' && c <= '9';
922}
923
924isspace(c: int): int
925{
926	return c == ' ' || c == '\t' || c == '\n' || c == '\r' || c == '\f';
927}
928
929hex(c: int): int
930{
931	if(c >= '0' && c <= '9')
932		return c-'0';
933	if(c >= 'A' && c <= 'F')
934		return c-'A' + 10;
935	if(c >= 'a' && c <= 'f')
936		return c-'a' + 10;
937	return -1;
938}
939
940quotedstring(cs: ref Clex, delim: int): string
941{
942	s: string;
943	while((c := cs.getc()) != delim){
944		if(c < 0){
945			cs.synerr("end-of-file in string");
946			return s;
947		}
948		if(c == '\\'){
949			c = cs.getc();
950			if(c < 0){
951				cs.synerr("end-of-file in string");
952				return s;
953			}
954			if(isxdigit(c)){
955				# unicode escape
956				n := 0;
957				for(i := 0;;){
958					n = (n<<4) | hex(c);
959					c = cs.getc();
960					if(!isxdigit(c) || ++i >= 6){
961						if(!isspace(c))
962							cs.ungetc(c);	# CSS2 ignores the first white space following
963						break;
964					}
965				}
966				s[len s] = n;
967			}else if(c == '\n'){
968				;	# escaped newline
969			}else if(isescapable(c))
970				s[len s] = c;
971		}else if(c)
972			s[len s] = c;
973	}
974	return s;
975}
976
977url(cs: ref Clex): string
978{
979	s: string;
980	c := skipws(cs);
981	if(c != '"' && c != '\''){	# not a quoted string
982		while(c != ' ' && c != '\n' && c != '\'' && c != '"' && c != ')'){
983			s[len s] = c;
984			c = cs.getc();
985			if(c == '\\'){
986				c = cs.getc();
987				if(c < 0){
988					cs.synerr("end of file in url parameter");
989					break;
990				}
991				if(c == ' ' || c == '\'' || c == '"' || c == ')')
992					s[len s] = c;
993				else{
994					cs.synerr("invalid escape sequence in url");
995					s[len s] = '\\';
996					s[len s] = c;
997				}
998				c = cs.getc();
999			}
1000		}
1001		cs.ungetc(c);
1002#		if(s == nil)
1003#			p.synerr("empty parameter to url");
1004	}else
1005		s = quotedstring(cs, c);
1006	if((c = skipws(cs)) != ')'){
1007		cs.synerr("unclosed parameter to url");
1008		cs.ungetc(c);
1009	}
1010	return s;
1011}
1012
1013lowercase(s: string): string
1014{
1015	for(i := 0; i < len s; i++)
1016		if((c := s[i]) >= 'A' && c <= 'Z')
1017			s[i] = c-'A' + 'a';
1018	return s;
1019}
1020