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