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

Annotation of /factorcss/CSS.hs

Parent Directory Parent Directory | Revision Log Revision Log


Revision 61 - (hide annotations) (download) (as text)
Sun Dec 19 22:10:41 2004 UTC (19 years, 4 months ago) by james
File MIME type: text/x-haskell
File size: 3269 byte(s)
Initial version. Tokeniser, parser, and functions to output as CSS.

1 james 61 -- 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     show_stylesheet :: Stylesheet -> [String]
66     show_stylesheet (Stylesheet c is ss) = show_charset c ++
67     map show_import (reverse is) ++
68     map show_statement ss
69    
70     show_charset :: Maybe String -> [String]
71     show_charset Nothing = []
72     show_charset (Just c) = ["@charset " ++ c ++ ";"]
73    
74     show_import :: (String, [String]) -> String
75     show_import (url, media) = "@import " ++ url ++ " " ++
76     (concat . intersperse ", ") media ++ ";"
77    
78     show_statement :: Statement -> String
79     show_statement (Ruleset ss ds) =
80     (concat . intersperse ", " . map show_selector) ss ++
81     " { " ++
82     (concat . intersperse "; " . map show_declaration) ds ++
83     " }"
84     show_statement z = "(statement)"
85    
86     show_selector :: Selector -> String
87     show_selector [] = ""
88     show_selector ((ss, c):zs) = show_simple_selector ss ++
89     show_combinator c ++
90     show_selector zs
91    
92     show_simple_selector :: SimpleSelector -> String
93     show_simple_selector (Just s, ds) = s ++ (concat . map show_detail) ds
94     show_simple_selector (Nothing, ds) = (concat . map show_detail) ds
95    
96     show_detail :: Detail -> String
97     show_detail (Id i) = i
98     show_detail (Class c) = "." ++ c
99     show_detail (Attrib a) = "[" ++ a ++ "]"
100     show_detail (AttribEq a v) = "[" ++ a ++ "=" ++ v ++ "]"
101     show_detail (AttribInc a v) = "[" ++ a ++ "~=" ++ v ++ "]"
102     show_detail (AttribDM a v) = "[" ++ a ++ "|=" ++ v ++ "]"
103     show_detail (Pseudo p) = ":" ++ p
104     show_detail (PseudoFunc f p) = ":" ++ f ++ p ++ ")"
105    
106     show_combinator :: Combinator -> String
107     show_combinator Ancestor = " "
108     show_combinator Preceded = " + "
109     show_combinator Parent = " > "
110     show_combinator NoMore = ""
111    
112     show_declaration :: Declaration -> String
113     show_declaration (p, vs, i) = p ++ ": " ++ show_values vs ++
114     if i then " !important" else ""
115    
116     show_values :: [Value] -> String
117     show_values = concat . intersperse " " . map show_value
118    
119     show_value :: Value -> String
120     show_value (Number n) = show n
121     show_value (Percentage p) = show p ++ "%"
122     show_value (Length l) = l
123     show_value (Ems e) = show e ++ "em"
124     show_value (Exs x) = show x ++ "ex"
125     show_value (Angle a) = a
126     show_value (Time t) = t
127     show_value (Freq f) = f
128     show_value (StringV s) = s
129     show_value (Ident i) = i
130     show_value (Uri u) = u
131     show_value (HexColour c) = c
132     show_value Slash = "/"
133     show_value Comma = ","
134     show_value (Function f vs) = f ++ show_values vs ++ ")"

  ViewVC Help
Powered by ViewVC 1.1.26