/[james]/factorcss/Tokeniser.x
ViewVC logotype

Contents of /factorcss/Tokeniser.x

Parent Directory Parent Directory | Revision Log Revision Log


Revision 73 - (show annotations) (download)
Sun Feb 27 13:53:48 2005 UTC (19 years, 2 months ago) by james
File size: 3663 byte(s)
Fix some parsing bugs related to parsing numbers, and improve error handling. No longer use scientific notation for output of floats.

1 --
2 -- This file is part of FactorCSS
3 -- Licensed under the MIT License,
4 -- http://www.opensource.org/licenses/mit-license
5 -- Copyright 2005 James Bursa <james@semichrome.net>
6 --
7
8 -- Tokeniser for CSS 2.1
9 -- See CSS 2.1 G.2
10
11 {
12 module Tokeniser where
13 }
14
15 %wrapper "posn"
16
17 $h = [0-9a-f]
18 $nonascii = [\x80-\xff]
19 @unicode = \\$h{1,6}(\r\n|[\ \t\r\n\f])?
20 @escape = @unicode|\\[\x20-\x7e\x80-\xff]
21 @nmstart = [_a-zA-Z]|$nonascii|@escape
22 @nmchar = [\-_a-zA-Z0-9]|$nonascii|@escape
23 @nl = \n|\r\n|\r|\f
24 @string1 = \"([\t\ \!\#\x24\x25&\x28-\x7e]|\\@nl|\'|$nonascii|@escape|\.)*\"
25 @string2 = \'([\t\ \!\#\x24\x25&\x28-\x7e]|\\@nl|\"|$nonascii|@escape|\.)*\'
26 @ident = @nmstart@nmchar*
27 @name = @nmchar+
28 @num = [\-\053]?([0-9]+|[0-9]*"."[0-9]+)
29 @string = @string1|@string2
30 @url = ([\!\#\x24\x25&\x2a-\x7e]|$nonascii|@escape)*
31 $s = [\ \t\r\n\f]
32 @w = $s*
33 @range = \?{1,6}|$h(\?{0,5}|$h(\?{0,4}|$h(\?{0,3}|$h(\?{0,2}|$h(\??|$h)))))
34 $all = \x00-\xff
35 @comment = \/\*$all#\x2a*\*+($all#[\/\x2a]$all#\x2a*\*+)*\/
36
37 tokens :-
38
39 $s+ { \p s -> (S, p) }
40 @comment ;
41
42 "<!--" ;
43 "-->" ;
44 "~=" { \p s -> (INCLUDES, p) }
45 "|=" { \p s -> (DASHMATCH, p) }
46
47 @w"{" { \p s -> (LBRACE, p) }
48 @w"}" { \p s -> (RBRACE, p) }
49 @w"+" { \p s -> (PLUS, p) }
50 @w">" { \p s -> (GREATER, p) }
51 @w"," { \p s -> (COMMA, p) }
52
53 @string { \p s -> (STRING s, p) }
54
55 @ident { \p s -> (IDENT s, p) }
56
57 "#"@name { \p s -> (HASH s, p) }
58
59 "@import" { \p s -> (IMPORT_SYM, p) }
60 "@page" { \p s -> (PAGE_SYM, p) }
61 "@media" { \p s -> (MEDIA_SYM, p) }
62 "@charset" { \p s -> (CHARSET_SYM, p) }
63
64 "!"@w"important" { \p s -> (IMPORTANT_SYM, p) }
65
66 @num em { \p s -> (EMS (readz (take (length s - 2) s) p), p) }
67 @num ex { \p s -> (EXS (readz (take (length s - 2) s) p), p) }
68 @num px { \p s -> (LENGTH s, p) }
69 @num cm { \p s -> (LENGTH s, p) }
70 @num mm { \p s -> (LENGTH s, p) }
71 @num in { \p s -> (LENGTH s, p) }
72 @num pt { \p s -> (LENGTH s, p) }
73 @num pc { \p s -> (LENGTH s, p) }
74 @num deg { \p s -> (ANGLE s, p) }
75 @num rad { \p s -> (ANGLE s, p) }
76 @num grad { \p s -> (ANGLE s, p) }
77 @num ms { \p s -> (TIME s, p) }
78 @num s { \p s -> (TIME s, p) }
79 @num Hz { \p s -> (FREQ s, p) }
80 @num kHz { \p s -> (FREQ s, p) }
81 @num @ident { \p s -> (DIMEN s, p) }
82 @num "%" { \p s -> (PERCENTAGE (readz (take (length s - 1) s) p), p) }
83 @num { \p s -> (NUMBER (readz s p), p) }
84
85 "url("@w@string@w")" { \p s -> (URI s, p) }
86 "url("@w@url@w")" { \p s -> (URI s, p) }
87 @ident"(" { \p s -> (FUNCTION s, p) }
88
89 ";" { \p s -> (SEMI, p) }
90 ":" { \p s -> (COLON, p) }
91 "/" { \p s -> (SLASH, p) }
92 "-" { \p s -> (MINUS, p) }
93 "." { \p s -> (DOT, p) }
94 "*" { \p s -> (ASTERISK, p) }
95 "[" { \p s -> (LBRAC, p) }
96 "]" { \p s -> (RBRAC, p) }
97 "=" { \p s -> (EQUALS, p) }
98 ")" { \p s -> (RPAREN, p) }
99 . { \p s -> (DELIM (head s), p) }
100
101
102 {
103 type TokenPosn = (Token, AlexPosn)
104
105 data Token =
106 S |
107 INCLUDES |
108 DASHMATCH |
109 LBRACE |
110 PLUS |
111 GREATER |
112 COMMA |
113 STRING String |
114 IDENT String |
115 HASH String |
116 IMPORT_SYM |
117 PAGE_SYM |
118 MEDIA_SYM |
119 CHARSET_SYM |
120 IMPORTANT_SYM |
121 EMS Float |
122 EXS Float |
123 LENGTH String |
124 ANGLE String |
125 TIME String |
126 FREQ String |
127 DIMEN String |
128 PERCENTAGE Float |
129 NUMBER Float |
130 URI String |
131 FUNCTION String |
132 SEMI |
133 RBRACE |
134 COLON |
135 SLASH |
136 MINUS |
137 DOT |
138 ASTERISK |
139 LBRAC |
140 RBRAC |
141 EQUALS |
142 RPAREN |
143 DELIM Char
144 deriving (Eq, Show)
145
146 readz :: Read a => String -> AlexPosn -> a
147 readz s (AlexPn _ l c) =
148 if (null xs) || not (null (snd (head xs)))
149 then error ("Parse error at " ++ "line " ++ show l ++
150 ", column " ++ show c ++
151 " (when parsing \"" ++ s ++ "\")")
152 else fst (head xs)
153 where xs = reads s
154
155 }

  ViewVC Help
Powered by ViewVC 1.1.26