Commit 8bc10a48 authored by Taddeüs Kroes's avatar Taddeüs Kroes

Added support for @font-face, @namespace, @keyframes + some general lexer/parser improvements

parent 79865573
......@@ -44,6 +44,34 @@ let name = nmchar+
let num = ['0'-'9']+ | ['0'-'9']*'.'['0'-'9']+
let url = (['!' '#' '$' '%' '&' '*'-'~'] | nonascii | escape)*
let A = ['a' 'A']
let B = ['b' 'B']
let C = ['c' 'C']
let D = ['d' 'D']
let E = ['e' 'E']
let F = ['f' 'F']
let G = ['g' 'G']
let H = ['h' 'H']
let I = ['i' 'I']
let J = ['j' 'J']
let K = ['k' 'K']
let L = ['l' 'L']
let M = ['m' 'M']
let N = ['n' 'N']
let O = ['o' 'O']
let P = ['p' 'P']
let Q = ['q' 'Q']
let R = ['r' 'R']
let S = ['s' 'S']
let T = ['t' 'T']
let U = ['u' 'U']
let V = ['v' 'V']
let W = ['w' 'W']
let X = ['x' 'X']
let Y = ['y' 'Y']
let Z = ['z' 'Z']
rule token = parse
| s { S }
......@@ -60,21 +88,27 @@ rule token = parse
| '#' (name as nm) { HASH nm }
| "@import" { IMPORT_SYM }
| "@page" { PAGE_SYM }
| "@media" { MEDIA_SYM }
| "@charset" { CHARSET_SYM }
| '@' I M P O R T { IMPORT_SYM }
| '@' P A G E { PAGE_SYM }
| '@' M E D I A { MEDIA_SYM }
| "@charset " { CHARSET_SYM }
| '@' F O N T '-' F A C E { FONT_FACE_SYM }
| '@' N A M E S P A C E { NAMESPACE_SYM }
| '@' K E Y F R A M E S { KEYFRAMES_SYM }
| "only" { ONLY }
| "not" { NOT }
| "and" { AND }
| O N L Y { ONLY }
| N O T { NOT }
| A N D { AND }
| F R O M { FROM }
| T O { TO }
| ident as id { IDENT id }
| '!' (w | comment)* "important" { IMPORTANT_SYM }
| '!' (w | comment)* I M P O R T A N T { IMPORTANT_SYM }
| (num as n) ("em"|"ex"|"px"|"cm"|"mm"|"in"|"pt"|"pc"|"deg"|"rad"|"grad"|
"ms"|"s"|"hz"|"khz"|"%"|"dpi"|"dpcm"|ident as u)
| (num as n) '%' { PERCENTAGE (float_of_string n) }
| (num as n) (E M | E X | P X | C M | M M | I N | P T | P C | D E G |
G? R A D | M? S | K? H Z | D P (I | C M) | ident as u)
{ UNIT_VALUE (float_of_string n, u) }
| num as n { NUMBER (float_of_string n) }
......
......@@ -32,7 +32,7 @@ let parse_args () =
let main () =
let args = parse_args () in
try
let css =
let stylesheet =
match args.infiles with
| [] ->
let input = Util.input_buffered stdin 512 in
......@@ -42,12 +42,14 @@ let main () =
| [] -> []
| filename :: tl ->
let input = Util.input_all (open_in filename) in
let css = Parse.parse_input filename input in
css @ loop tl
let stylesheet = Parse.parse_input filename input in
stylesheet @ loop tl
in
loop files
in
Util.print_css css;
print_endline (Stringify.string_of_stylesheet stylesheet);
print_endline "\n";
print_endline (Stringify.minify_stylesheet stylesheet);
exit 0
with
| LocError (loc, msg) ->
......
......@@ -43,13 +43,13 @@
%}
(* Tokens *)
%token S CDO CDC IMPORT_SYM PAGE_SYM MEDIA_SYM CHARSET_SYM
%token IMPORTANT_SYM
%token <float> NUMBER
%token S CDO CDC IMPORT_SYM PAGE_SYM MEDIA_SYM CHARSET_SYM FONT_FACE_SYM
%token NAMESPACE_SYM KEYFRAMES_SYM IMPORTANT_SYM
%token <float> PERCENTAGE NUMBER
%token <float * string> UNIT_VALUE
%token <string> COMBINATOR RELATION STRING IDENT HASH URI FUNCTION
%token LPAREN RPAREN LBRACE RBRACE LBRACK RBRACK SEMICOL COLON COMMA DOT PLUS
%token MINUS SLASH STAR ONLY AND NOT EOF
%token MINUS SLASH STAR ONLY AND NOT FROM TO EOF
(* Start symbol *)
%type <Types.stylesheet> stylesheet
......@@ -66,17 +66,18 @@ cd: CDO S? | CDC S? {}
stylesheet:
| charset = charset? S? cd*
imports = terminated(import, cd*)*
namespaces = terminated(namespace, cd*)*
statements = terminated(statement, cd*)*
EOF
{ let charset = match charset with None -> [] | Some c -> [c] in
charset @ imports @ statements }
charset @ imports @ namespaces @ statements }
statement:
| s=ruleset | s=media | s=page
| s=ruleset | s=media | s=page | s=font_face | s=keyframes
{ s }
charset:
| CHARSET_SYM S? name=STRING S? SEMICOL
| CHARSET_SYM name=STRING S? SEMICOL
{ Charset name }
import:
......@@ -86,6 +87,13 @@ import:
| str=STRING { Strlit str }
| uri=URI { Uri uri }
namespace:
| NAMESPACE_SYM S? prefix=terminated(namespace_prefix, S?)? ns=string_or_uri S? SEMICOL S?
{ Namespace (prefix, ns) }
%inline namespace_prefix:
| prefix=IDENT
{ prefix }
media:
| MEDIA_SYM queries=media_query_list LBRACE S? rulesets=ruleset* RBRACE S?
{ Media (queries, rulesets) }
......@@ -113,11 +121,29 @@ media_expr:
page:
| PAGE_SYM S? pseudo=pseudo_page? decls=decls_block
{ Page (pseudo, decls) }
pseudo_page:
| COLON pseudo=IDENT S?
{ pseudo }
font_face:
| FONT_FACE_SYM S? LBRACE S? hd=descriptor_declaration?
tl=wspreceded(SEMICOL, descriptor_declaration?)* RBRACE S?
{ Font_face (filter_none (hd :: tl)) }
descriptor_declaration:
| name=property COLON S? value=expr
{ (name, value) }
keyframes:
| KEYFRAMES_SYM S? id=IDENT S? LBRACE S? rules=keyframe_ruleset* RBRACE S?
{ Keyframes (id, rules) }
keyframe_ruleset:
| selector=keyframe_selector S? decls=decls_block
{ (selector, decls) }
keyframe_selector:
| FROM { Ident "from" }
| TO { Ident "to" }
| n=PERCENTAGE { Number (n, Some "%") }
%inline decls_block:
| LBRACE S? hd=declaration? tl=wspreceded(SEMICOL, declaration?)* RBRACE S?
{ filter_none (hd :: tl) }
......@@ -172,8 +198,9 @@ pseudo:
":" ^ f ^ "(" ^ arg ^ ")" }
declaration:
| name=IDENT S? COLON S? value=expr important=boption(pair(IMPORTANT_SYM, S?))
| name=property S? COLON S? value=expr important=boption(pair(IMPORTANT_SYM, S?))
{ (String.lowercase name, value, important) }
%inline property: name=IDENT { name }
expr:
| l=exprl { concat_terms l }
......@@ -187,28 +214,21 @@ expr:
| COMMA S? { "," }
term:
| op=unary_operator n=NUMBER S?
{ Unary (op, Number (n, None)) }
| op=unary_operator v=UNIT_VALUE S?
{ let (n, u) = v in Unary (op, Number (n, Some u)) }
| n=NUMBER S?
{ Number (n, None) }
| v=UNIT_VALUE S?
{ let (n, u) = v in Number (n, Some u) }
| str=STRING S?
{ Strlit str }
| id=IDENT S?
{ Ident id }
| uri=URI S?
{ Uri uri }
| fn=FUNCTION arg=expr RPAREN S?
{ Function (fn, arg) }
| op=unary_operator v=numval S? { Unary (op, v) }
| v=numval S? { v }
| str=STRING S? { Strlit str }
| id=IDENT S? { Ident id }
| uri=URI S? { Uri uri }
| fn=FUNCTION arg=expr RPAREN S? { Function (fn, arg) }
| hex=HASH S?
{ let h = "[0-9a-fA-F][0-9a-fA-F][0-9a-fA-F]" in
if Str.string_match (Str.regexp ("^" ^ h ^ "\\(" ^ h ^ "\\)?$")) hex 0
then Hexcolor (String.lowercase hex)
else raise (SyntaxError ("invalid color #" ^ hex)) }
unary_operator:
| MINUS { "-" }
| PLUS { "+" }
%inline numval:
| n=NUMBER { Number (n, None) }
| v=UNIT_VALUE { let n, u = v in Number (n, Some u) }
| n=PERCENTAGE { Number (n, Some "%") }
......@@ -68,7 +68,7 @@ let string_of_media_query query =
| (Some pre, None, _) ->
failwith "unexpected media query prefix \"" ^ pre ^ "\""
let block body = " {\n" ^ indent body ^ "\n}"
let block = function "" -> " {}" | body -> " {\n" ^ indent body ^ "\n}"
let rec string_of_statement = function
| Ruleset (selectors, decls) ->
......@@ -87,12 +87,20 @@ let rec string_of_statement = function
"@page" ^ block (cat "\n" string_of_declaration decls)
| Page (Some pseudo, decls) ->
"@page :" ^ pseudo ^ block (cat "\n" string_of_declaration decls)
| Fontface decls ->
"@font-face " ^ block (cat "\n" string_of_declaration decls)
| Font_face decls ->
let string_of_descriptor_declaration (name, value) =
name ^ ": " ^ string_of_expr value ^ ";"
in
"@font-face" ^ block (cat "\n" string_of_descriptor_declaration decls)
| Namespace (None, uri) ->
"@namespace \"" ^ uri ^ "\";"
"@namespace " ^ string_of_expr uri ^ ";"
| Namespace (Some prefix, uri) ->
"@namespace " ^ prefix ^ " \"" ^ uri ^ "\";"
"@namespace " ^ prefix ^ " " ^ string_of_expr uri ^ ";"
| Keyframes (id, rules) ->
let string_of_keyframe_ruleset (expr, decls) =
string_of_expr expr ^ block (cat "\n" string_of_declaration decls)
in
"@keyframes " ^ id ^ block (cat "\n\n" string_of_keyframe_ruleset rules)
let string_of_stylesheet = cat "\n\n" string_of_statement
......@@ -133,10 +141,10 @@ let minify_media_query query =
let rec minify_statement = function
| Ruleset (selectors, decls) ->
cat "," minify_selector selectors ^
"{" ^ (cat ";" minify_declaration decls) ^ "}"
"{" ^ cat ";" minify_declaration decls ^ "}"
| Media (queries, rulesets) ->
"@media" ^ prefix_space (cat "," minify_media_query queries) ^
"{" ^ (cat "" minify_statement rulesets) ^ "}"
"{" ^ cat "" minify_statement rulesets ^ "}"
| Import (target, []) ->
"@import " ^ string_of_expr target ^ ";"
| Import (target, queries) ->
......@@ -145,8 +153,16 @@ let rec minify_statement = function
"@page{" ^ cat "" minify_declaration decls ^ "}"
| Page (Some pseudo, decls) ->
"@page :" ^ pseudo ^ "{" ^ cat "" minify_declaration decls ^ "}"
| Fontface decls ->
"@font-face{" ^ cat "" minify_declaration decls ^ "}"
| Font_face decls ->
let minify_descriptor_declaration (name, value) =
name ^ ":" ^ string_of_expr value
in
"@font-face{" ^ cat ";" minify_descriptor_declaration decls ^ "}"
| Keyframes (id, rules) ->
let minify_keyframe_ruleset (expr, decls) =
minify_expr expr ^ "{" ^ cat ";" minify_declaration decls ^ "}"
in
"@keyframes " ^ id ^ "{" ^ cat "" minify_keyframe_ruleset rules ^ "}"
| statement -> string_of_statement statement
let minify_stylesheet = cat "" minify_statement
......@@ -18,6 +18,10 @@ type selector =
type media_expr = string * expr option
type media_query = string option * string option * media_expr list
type descriptor_declaration = string * expr
type keyframe_ruleset = expr * declaration list
type statement =
| Ruleset of selector list * declaration list
(* <selectors> { <declarations> } *)
......@@ -29,11 +33,12 @@ type statement =
(* @charset "<charset>"; *)
| Page of string option * declaration list
(* @page [<pseudo_page>] { <declarations> } *)
| Fontface of declaration list
| Font_face of descriptor_declaration list
(* @font-face { <declarations> } *)
| Namespace of string option * string
| Namespace of string option * expr
(* @namespace [<prefix>] "<uri>"; *)
(* TODO: @document, @keyframes, @supports *)
| Keyframes of string * keyframe_ruleset list
(* TODO: @document, @supports *)
type stylesheet = statement list
......
Markdown is supported
0%
or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment