Type-checking goodies in place
[hcoop/domtool2.git] / src / print.sml
CommitLineData
63920aa5
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 *)
20
21structure Print :> PRINT = struct
22
23open Ast
24
25structure SM = TextIOPP
26
27structure PD = PPDescFn(SM)
28open PD
29
30fun dBox ds = hovBox (PPS.Rel 1, ds)
31fun dvBox ds = vBox (PPS.Rel 0, ds)
32fun ivBox ds = vBox (PPS.Rel 1, ds)
33
34fun parenIf pn ds =
35 if pn then
36 dBox (string "(" :: ds @ [string ")"])
37 else
38 dBox ds
39
40fun p_pred' pn (p, _) =
41 case p of
42 CRoot => string "Root"
43 | CConst s => string s
44 | CPrefix p => dBox [string "^", p_pred' true p]
45 | CNot p => dBox [string "!", p_pred' true p]
46 | CAnd (p1, p2) =>
47 parenIf pn [p_pred' true p1, space 1, string "&", space 1, p_pred' true p2]
48
49val p_pred = p_pred' false
50
51fun p_predBoxed p = dBox [string "[", p_pred p, string "]"]
52
53fun p_typ' pn (t, _) =
54 case t of
55 TBase s => string s
56 | TList t => dBox [string "[", p_typ' false t, string "]"]
57 | TArrow (t1, t2) =>
58 parenIf pn [p_typ' true t1, space 1, string "->", space 1, p_typ' true t2]
59 | TAction (p, r1, r2) =>
60 parenIf pn [p_predBoxed p, space 1, p_record r1, space 1,
234b917a
AC
61 string "=>", space 1, p_record r2]
62 | TNested (p1, p2) =>
63 parenIf pn [p_pred' false p1, space 1, string "=>", space 1, p_pred' false p2]
27d9de59
AC
64
65 | TError => string "<error>"
66 | TUnif (_, ref (SOME t)) => p_typ' pn t
67 | TUnif (name, ref NONE) => string ("<" ^ name ^ ">")
68
63920aa5
AC
69and p_record r =
70 case StringMap.foldri (fn (name, t, d) =>
71 SOME (case d of
72 NONE => dBox [string name, space 1,
73 string ":", space 1, p_typ t]
74 | SOME d => dBox [dBox [string name, space 1,
75 string ":", space 1, p_typ t],
76 string ",", space 1, d]))
77 NONE r of
78 NONE => string "{}"
79 | SOME d => dBox [string "{", d, string "}"]
80
81and p_typ t = p_typ' false t
82
83fun p_exp (e, _) =
84 case e of
85 EInt n => string (Int.toString n)
86 | EString s => string (String.concat ["\"", String.toString s, "\""])
87 | EList es =>
88 (case foldr (fn (e, d) =>
89 SOME (case d of
90 NONE => p_exp e
91 | SOME d => dBox [p_exp e, string ",", space 1, d]))
92 NONE es of
93 NONE => string "[]"
94 | SOME d => dBox [string "[", d, string "]"])
95
27d9de59
AC
96 | ELam (x, NONE, e) => dBox [string "(\\", space 1, string x, space 1,
97 string "->", space 1, p_exp e, string ")"]
98 | ELam (x, SOME t, e) => dBox [string "(\\", space 1, string x, space 1,
63920aa5
AC
99 string ":", space 1,
100 dBox [string "(", p_typ t, string ")"],
101 space 1, string "->", space 1, p_exp e, string ")"]
27d9de59 102
63920aa5
AC
103 | EVar x => string x
104 | EApp (e1, e2) => dBox [string "(", p_exp e1, break {nsp = 1, offset = 0}, p_exp e2, string ")"]
105
234b917a 106 | ESkip => string "_"
63920aa5
AC
107 | ESet (x, e) => dBox [string x, space 1, string "=", space 1, p_exp e]
108 | EGet (x1, x2, e) => dBox [dBox [string x1, space 1, string "<-",
109 space 1, string x2, string ";", space 1],
110 p_exp e]
111 | ESeq es => dBox (valOf (foldr (fn (e, NONE) => SOME [p_exp e]
112 | (e, SOME ds) => SOME (dBox [p_exp e, string ";", space 1] :: ds))
113 NONE es))
114 | ELocal (ESeq [e1, e2], _) => dBox [string "let", space 1,
115 p_exp e1, space 1,
116 string "in", space 1,
117 p_exp e2, space 1,
118 string "end"]
234b917a
AC
119 | ELocal e => dBox [string "local(", space 1, p_exp e, string ")"]
120 | EWith (e1, (ESkip, _)) => dBox [p_exp e1, space 1, string "with", space 1, string "end"]
121 | EWith (e1, e2) => dBox [p_exp e1, space 1, string "with", p_exp e2, space 1, string "end"]
63920aa5 122
27d9de59 123fun printd d =
63920aa5
AC
124 let
125 val myStream = SM.openOut {dst = TextIO.stdOut,
126 wid = 80}
127 in
128 description (myStream, d);
129 SM.newline myStream;
130 SM.closeStream myStream
131 end
132
133end