1 |
james |
63 |
-- |
2 |
|
|
-- This file is part of FactorCSS |
3 |
|
|
-- Licensed under the MIT License, |
4 |
|
|
-- http://www.opensource.org/licenses/mit-license |
5 |
|
|
-- Copyright 2004 James Bursa <james@semichrome.net> |
6 |
|
|
-- |
7 |
|
|
|
8 |
james |
61 |
-- Datatypes for CSS |
9 |
|
|
|
10 |
|
|
module CSS where |
11 |
|
|
import List |
12 |
|
|
|
13 |
|
|
data Stylesheet |
14 |
|
|
= Stylesheet |
15 |
|
|
(Maybe String) -- charset |
16 |
|
|
[(String, [String])] -- imports (url, media) |
17 |
|
|
[Statement] |
18 |
|
|
deriving Show |
19 |
|
|
|
20 |
|
|
data Statement |
21 |
|
|
= Ruleset [Selector] [Declaration] |
22 |
|
|
| Media [String] [Statement] |
23 |
|
|
| Page (Maybe String) [Declaration] |
24 |
|
|
deriving Show |
25 |
|
|
|
26 |
|
|
type Selector |
27 |
|
|
= [(SimpleSelector, Combinator)] |
28 |
|
|
|
29 |
|
|
type SimpleSelector |
30 |
|
|
= (Maybe String, [Detail]) |
31 |
|
|
|
32 |
|
|
data Detail |
33 |
|
|
= Id String |
34 |
|
|
| Class String |
35 |
|
|
| Attrib String |
36 |
|
|
| AttribEq String String |
37 |
|
|
| AttribInc String String |
38 |
|
|
| AttribDM String String |
39 |
|
|
| Pseudo String |
40 |
|
|
| PseudoFunc String String |
41 |
|
|
deriving Show |
42 |
|
|
|
43 |
|
|
data Combinator |
44 |
|
|
= Ancestor |
45 |
|
|
| Preceded |
46 |
|
|
| Parent |
47 |
|
|
| NoMore |
48 |
|
|
deriving Show |
49 |
|
|
|
50 |
|
|
type Declaration |
51 |
|
|
= (String, [Value], Bool) |
52 |
|
|
|
53 |
|
|
data Value |
54 |
|
|
= Number Float |
55 |
|
|
| Percentage Float |
56 |
|
|
| Length String |
57 |
|
|
| Ems Float |
58 |
|
|
| Exs Float |
59 |
|
|
| Angle String |
60 |
|
|
| Time String |
61 |
|
|
| Freq String |
62 |
|
|
| StringV String |
63 |
|
|
| Ident String |
64 |
|
|
| Uri String |
65 |
|
|
| HexColour String |
66 |
|
|
| Slash |
67 |
|
|
| Comma |
68 |
|
|
| Function String [Value] |
69 |
|
|
deriving Show |
70 |
|
|
|
71 |
|
|
|
72 |
james |
62 |
is_ruleset :: Statement -> Bool |
73 |
|
|
is_ruleset (Ruleset sels decls) = True |
74 |
|
|
is_ruleset _ = False |
75 |
|
|
|
76 |
|
|
is_media :: Statement -> Bool |
77 |
|
|
is_media (Media media stmts) = True |
78 |
|
|
is_media _ = False |
79 |
|
|
|
80 |
|
|
is_page :: Statement -> Bool |
81 |
|
|
is_page (Page page decls) = True |
82 |
|
|
is_page _ = False |
83 |
|
|
|
84 |
|
|
|
85 |
james |
61 |
show_stylesheet :: Stylesheet -> [String] |
86 |
|
|
show_stylesheet (Stylesheet c is ss) = show_charset c ++ |
87 |
|
|
map show_import (reverse is) ++ |
88 |
|
|
map show_statement ss |
89 |
|
|
|
90 |
|
|
show_charset :: Maybe String -> [String] |
91 |
|
|
show_charset Nothing = [] |
92 |
|
|
show_charset (Just c) = ["@charset " ++ c ++ ";"] |
93 |
|
|
|
94 |
|
|
show_import :: (String, [String]) -> String |
95 |
|
|
show_import (url, media) = "@import " ++ url ++ " " ++ |
96 |
|
|
(concat . intersperse ", ") media ++ ";" |
97 |
|
|
|
98 |
|
|
show_statement :: Statement -> String |
99 |
|
|
show_statement (Ruleset ss ds) = |
100 |
james |
62 |
show_selectors ss ++ |
101 |
james |
61 |
" { " ++ |
102 |
|
|
(concat . intersperse "; " . map show_declaration) ds ++ |
103 |
|
|
" }" |
104 |
james |
62 |
show_statement (Media media stmts) = |
105 |
|
|
"@media " ++ (concat . intersperse ", ") media ++ |
106 |
|
|
" {\n" ++ |
107 |
|
|
(unlines . map ('\t':) . map show_statement) stmts ++ |
108 |
|
|
"}" |
109 |
james |
61 |
show_statement z = "(statement)" |
110 |
|
|
|
111 |
james |
62 |
show_selectors :: [Selector] -> String |
112 |
|
|
show_selectors = concat . intersperse ", " . map show_selector |
113 |
|
|
|
114 |
james |
61 |
show_selector :: Selector -> String |
115 |
|
|
show_selector [] = "" |
116 |
|
|
show_selector ((ss, c):zs) = show_simple_selector ss ++ |
117 |
|
|
show_combinator c ++ |
118 |
|
|
show_selector zs |
119 |
|
|
|
120 |
|
|
show_simple_selector :: SimpleSelector -> String |
121 |
|
|
show_simple_selector (Just s, ds) = s ++ (concat . map show_detail) ds |
122 |
james |
72 |
show_simple_selector (Nothing, []) = "*" |
123 |
james |
61 |
show_simple_selector (Nothing, ds) = (concat . map show_detail) ds |
124 |
|
|
|
125 |
|
|
show_detail :: Detail -> String |
126 |
|
|
show_detail (Id i) = i |
127 |
|
|
show_detail (Class c) = "." ++ c |
128 |
|
|
show_detail (Attrib a) = "[" ++ a ++ "]" |
129 |
|
|
show_detail (AttribEq a v) = "[" ++ a ++ "=" ++ v ++ "]" |
130 |
|
|
show_detail (AttribInc a v) = "[" ++ a ++ "~=" ++ v ++ "]" |
131 |
|
|
show_detail (AttribDM a v) = "[" ++ a ++ "|=" ++ v ++ "]" |
132 |
|
|
show_detail (Pseudo p) = ":" ++ p |
133 |
|
|
show_detail (PseudoFunc f p) = ":" ++ f ++ p ++ ")" |
134 |
|
|
|
135 |
|
|
show_combinator :: Combinator -> String |
136 |
|
|
show_combinator Ancestor = " " |
137 |
|
|
show_combinator Preceded = " + " |
138 |
|
|
show_combinator Parent = " > " |
139 |
|
|
show_combinator NoMore = "" |
140 |
|
|
|
141 |
|
|
show_declaration :: Declaration -> String |
142 |
|
|
show_declaration (p, vs, i) = p ++ ": " ++ show_values vs ++ |
143 |
|
|
if i then " !important" else "" |
144 |
|
|
|
145 |
|
|
show_values :: [Value] -> String |
146 |
|
|
show_values = concat . intersperse " " . map show_value |
147 |
|
|
|
148 |
|
|
show_value :: Value -> String |
149 |
|
|
show_value (Number n) = show n |
150 |
|
|
show_value (Percentage p) = show p ++ "%" |
151 |
|
|
show_value (Length l) = l |
152 |
|
|
show_value (Ems e) = show e ++ "em" |
153 |
|
|
show_value (Exs x) = show x ++ "ex" |
154 |
|
|
show_value (Angle a) = a |
155 |
|
|
show_value (Time t) = t |
156 |
|
|
show_value (Freq f) = f |
157 |
|
|
show_value (StringV s) = s |
158 |
|
|
show_value (Ident i) = i |
159 |
|
|
show_value (Uri u) = u |
160 |
|
|
show_value (HexColour c) = c |
161 |
|
|
show_value Slash = "/" |
162 |
|
|
show_value Comma = "," |
163 |
|
|
show_value (Function f vs) = f ++ show_values vs ++ ")" |