Make HTML pretty-printing prettier
[hcoop/domtool2.git] / src / htmlPrint.sml
CommitLineData
3196000d
AC
1(* HCoop Domtool (http://hcoop.sourceforge.net/)
2 * Copyright (c) 2006, Adam Chlipala
3 *
4 * This program is free software; you can redistribute it and/or
5 * modify it under the terms of the GNU General Public License
6 * as published by the Free Software Foundation; either version 2
7 * of the License, or (at your option) any later version.
8 *
9 * This program is distributed in the hope that it will be useful,
10 * but WITHOUT ANY WARRANTY; without even the implied warranty of
11 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 * GNU General Public License for more details.
13 *
14 * You should have received a copy of the GNU General Public License
15 * along with this program; if not, write to the Free Software
16 * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
17 *)
18
19(* Pretty-printing Domtool configuration file ASTs for HTML *)
20
21structure HtmlPrint :> HTML_PRINT = struct
22
23open Ast Order
24
25val prov : providers option ref = ref NONE
26fun setProviders p = prov := SOME p
27
28structure TextToken = struct
29type token = string
30type style = HTMLDev.style
31fun string t = t
32fun style t = HTMLDev.styleTT
33fun size t = String.size t
34end
35
36structure SM = PPStreamFn(structure Token = TextToken
37 structure Device = HTMLDev)
38
39structure PD = PPDescFn(SM)
40open PD
41
42fun dBox ds = hovBox (PPS.Rel 1, ds)
43fun dvBox ds = vBox (PPS.Rel 0, ds)
44fun ivBox ds = vBox (PPS.Rel 1, ds)
45
46fun keyword s = style (HTMLDev.styleB, [string s])
47val punct = string
48
49fun modify file =
50 let
51 val file' = #file (OS.Path.splitDirFile file)
52 val file' = #base (OS.Path.splitBaseExt file')
53 in
54 file'
55 end
56
57fun context s =
58 case providesContext (valOf (!prov), s) of
59 NONE => string s
60 | SOME m => style (HTMLDev.link (modify m ^ ".html#C_" ^ s), [string s])
61fun typ s =
62 case providesType (valOf (!prov), s) of
63 NONE => string s
64 | SOME m => style (HTMLDev.link (modify m ^ ".html#T_" ^ s), [string s])
65fun exp s =
66 case providesValue (valOf (!prov), s) of
67 NONE => string s
68 | SOME m => style (HTMLDev.link (modify m ^ ".html#V_" ^ s), [string s])
69
70val field = string
71val lit = string
72val ident = string
73
74fun parenIf pn ds =
75 if pn then
76 dBox (punct "(" :: ds @ [punct ")"])
77 else
78 dBox ds
79
80fun p_pred' pn (p, _) =
81 case p of
82 CRoot => keyword "Root"
83 | CConst s => context s
84 | CPrefix p => dBox [punct "^", p_pred' true p]
85 | CNot p => dBox [punct "!", p_pred' true p]
86 | CAnd (p1, p2) =>
87 parenIf pn [p_pred' true p1, space 1, punct "&", space 1, p_pred' true p2]
88
89val p_pred = p_pred' false
90
91fun p_predBoxed p = dBox [punct "[", p_pred p, punct "]"]
92
93fun p_typ' pn (t, _) =
94 case t of
95 TBase s => typ s
96 | TList t => dBox [punct "[", p_typ' false t, punct "]"]
97 | TArrow (t1, t2) =>
8c57a89d 98 parenIf pn [p_typ' true t1, space 1, punct "->", space 1, p_typ' false t2]
3196000d 99 | TAction (p, r1, r2) =>
8c57a89d
AC
100 (case (StringMap.numItems r1, StringMap.numItems r2) of
101 (0, 0) => parenIf pn [p_predBoxed p]
102 | (_, 0) => parenIf pn [p_predBoxed p, space 1, p_record r1]
103 | _ => parenIf pn [p_predBoxed p, space 1, p_record r1, space 1,
104 punct "=>", space 1, p_record r2])
3196000d
AC
105 | TNested (p, t) =>
106 parenIf pn [p_pred' false p, space 1, punct "=>", space 1, p_typ' false t]
107
108 | TError => keyword "<error>"
109 | TUnif (_, ref (SOME t)) => p_typ' pn t
110 | TUnif (name, ref NONE) => string ("<" ^ name ^ ">")
111
112and p_record r =
113 case StringMap.foldri (fn (name, t, d) =>
114 SOME (case d of
115 NONE => dBox [field name, space 1,
116 punct ":", space 1, p_typ t]
117 | SOME d => dBox [dBox [field name, space 1,
118 punct ":", space 1, p_typ t],
119 punct ",", space 1, d]))
120 NONE r of
121 NONE => punct "{}"
122 | SOME d => dBox [punct "{", d, punct "}"]
123
124and p_typ t = p_typ' false t
125
126fun p_exp (e, _) =
127 case e of
128 EInt n => lit (Int.toString n)
129 | EString s => lit (String.concat ["\"", String.toString s, "\""])
130 | EList es =>
131 (case foldr (fn (e, d) =>
132 SOME (case d of
133 NONE => p_exp e
134 | SOME d => dBox [p_exp e, punct ",", space 1, d]))
135 NONE es of
136 NONE => punct "[]"
137 | SOME d => dBox [punct "[", d, punct "]"])
138
139 | ELam (x, NONE, e) => dBox [punct "(\\", space 1, exp x, space 1,
140 punct "->", space 1, p_exp e, punct ")"]
141 | ELam (x, SOME t, e) => dBox [punct "(\\", space 1, exp x, space 1,
142 punct ":", space 1,
143 dBox [punct "(", p_typ t, punct ")"],
144 space 1, punct "->", space 1, p_exp e, punct ")"]
6bb366c5
AC
145 | EALam (x, p, e) => dBox [punct "(\\", space 1, exp x, space 1,
146 punct ":", space 1, p_pred p,
147 space 1, punct "->", space 1, p_exp e, punct ")"]
3196000d
AC
148
149 | EVar x => exp x
150 | EApp (e1, e2) => dBox [punct "(", p_exp e1, break {nsp = 1, offset = 0}, p_exp e2, punct ")"]
151
152 | ESkip => keyword "_"
153 | ESet (x, e) => dBox [exp x, space 1, punct "=", space 1, p_exp e]
154 | EGet (x1, x2, e) => dBox [dBox [exp x1, space 1, punct "<-",
155 space 1, exp x2, punct ";", space 1],
156 p_exp e]
157 | ESeq es => dBox (valOf (foldr (fn (e, NONE) => SOME [p_exp e]
158 | (e, SOME ds) => SOME (dBox [p_exp e, punct ";", newline] :: ds))
159 NONE es))
160 | ELocal (e1, e2) => dBox [keyword "let", space 1,
161 p_exp e1, space 1,
162 keyword "in", space 1,
163 p_exp e2, space 1,
164 keyword "end"]
165 | EWith (e1, (ESkip, _)) => dBox [p_exp e1, space 1, keyword "with", space 1, keyword "end"]
166 | EWith (e1, e2) => dBox [p_exp e1, space 1, keyword "with", p_exp e2, space 1, keyword "end"]
167
168fun p_decl d =
169 case d of
170 DExternType name => style (HTMLDev.anchor ("T_" ^ name),
171 [dBox [keyword "extern", space 1,
172 keyword "type", space 1,
173 ident name]])
174 | DExternVal (name, t) => style (HTMLDev.anchor ("V_" ^ name),
175 [dBox [keyword "extern", space 1,
176 keyword "val", space 1,
177 ident name, space 1,
178 string ":", space 1,
179 p_typ t]])
180 | DVal (name, NONE, _) => string "Unannotated val declaration!"
181 | DVal (name, SOME t, _) => style (HTMLDev.anchor ("V_" ^ name),
182 [dBox [keyword "val", space 1,
183 ident name, space 1,
184 punct ":", space 1,
185 p_typ t]])
186 | DContext name => style (HTMLDev.anchor ("C_" ^ name),
187 [dBox [keyword "context", space 1,
188 ident name]])
189
c2ce01bd
AC
190fun p_decl_fref d =
191 case d of
192 DExternType name => dBox [keyword "extern", space 1,
193 keyword "type", space 1,
194 style (HTMLDev.link ("#T_" ^ name), [ident name])]
195 | DExternVal (name, t) => dBox [keyword "extern", space 1,
196 keyword "val", space 1,
197 style (HTMLDev.link ("#V_" ^ name), [ident name]),
198 space 1,
199 string ":", space 1,
200 p_typ t]
201 | DVal (name, NONE, _) => string "Unannotated val declaration!"
202 | DVal (name, SOME t, _) => dBox [keyword "val", space 1,
203 style (HTMLDev.link ("#V_" ^ name), [ident name]),
204 space 1,
205 punct ":", space 1,
206 p_typ t]
207 | DContext name => dBox [keyword "context", space 1,
208 style (HTMLDev.link ("#C_" ^ name), [ident name])]
209
3196000d
AC
210fun output d =
211 let
212 val dev = HTMLDev.openDev {wid = 80,
213 textWid = NONE}
214 val myStream = SM.openStream dev
215 in
216 description (myStream, d);
217 SM.flushStream myStream;
218 HTMLDev.done dev
219 end
220
221end