/[james]/factorcss/CSS.hs
ViewVC logotype

Annotation of /factorcss/CSS.hs

Parent Directory Parent Directory | Revision Log Revision Log


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

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

  ViewVC Help
Powered by ViewVC 1.1.26