Typechecking for basic language done
[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,
61 string "->", space 1, p_record r2]
27d9de59
AC
62
63 | TError => string "<error>"
64 | TUnif (_, ref (SOME t)) => p_typ' pn t
65 | TUnif (name, ref NONE) => string ("<" ^ name ^ ">")
66
63920aa5
AC
67and p_record r =
68 case StringMap.foldri (fn (name, t, d) =>
69 SOME (case d of
70 NONE => dBox [string name, space 1,
71 string ":", space 1, p_typ t]
72 | SOME d => dBox [dBox [string name, space 1,
73 string ":", space 1, p_typ t],
74 string ",", space 1, d]))
75 NONE r of
76 NONE => string "{}"
77 | SOME d => dBox [string "{", d, string "}"]
78
79and p_typ t = p_typ' false t
80
81fun p_exp (e, _) =
82 case e of
83 EInt n => string (Int.toString n)
84 | EString s => string (String.concat ["\"", String.toString s, "\""])
85 | EList es =>
86 (case foldr (fn (e, d) =>
87 SOME (case d of
88 NONE => p_exp e
89 | SOME d => dBox [p_exp e, string ",", space 1, d]))
90 NONE es of
91 NONE => string "[]"
92 | SOME d => dBox [string "[", d, string "]"])
93
27d9de59
AC
94 | ELam (x, NONE, e) => dBox [string "(\\", space 1, string x, space 1,
95 string "->", space 1, p_exp e, string ")"]
96 | ELam (x, SOME t, e) => dBox [string "(\\", space 1, string x, space 1,
63920aa5
AC
97 string ":", space 1,
98 dBox [string "(", p_typ t, string ")"],
99 space 1, string "->", space 1, p_exp e, string ")"]
27d9de59 100
63920aa5
AC
101 | EVar x => string x
102 | EApp (e1, e2) => dBox [string "(", p_exp e1, break {nsp = 1, offset = 0}, p_exp e2, string ")"]
103
104 | ESet (x, e) => dBox [string x, space 1, string "=", space 1, p_exp e]
105 | EGet (x1, x2, e) => dBox [dBox [string x1, space 1, string "<-",
106 space 1, string x2, string ";", space 1],
107 p_exp e]
108 | ESeq es => dBox (valOf (foldr (fn (e, NONE) => SOME [p_exp e]
109 | (e, SOME ds) => SOME (dBox [p_exp e, string ";", space 1] :: ds))
110 NONE es))
111 | ELocal (ESeq [e1, e2], _) => dBox [string "let", space 1,
112 p_exp e1, space 1,
113 string "in", space 1,
114 p_exp e2, space 1,
115 string "end"]
116 | ELocal _ => raise Fail "Unexpected ELocal form"
117
27d9de59 118fun printd d =
63920aa5
AC
119 let
120 val myStream = SM.openOut {dst = TextIO.stdOut,
121 wid = 80}
122 in
123 description (myStream, d);
124 SM.newline myStream;
125 SM.closeStream myStream
126 end
127
128end