(* HCoop Domtool (http://hcoop.sourceforge.net/) * Copyright (c) 2006, Adam Chlipala * * This program is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License * as published by the Free Software Foundation; either version 2 * of the License, or (at your option) any later version. * * This program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program; if not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. *) (* Pretty-printing Domtool configuration file ASTs for HTML *) structure HtmlPrint :> HTML_PRINT = struct open Ast Order val prov : providers option ref = ref NONE fun setProviders p = prov := SOME p structure TextToken = struct type token = string type style = HTMLDev.style fun string t = t fun style t = HTMLDev.styleTT fun size t = String.size t end structure SM = PPStreamFn(structure Token = TextToken structure Device = HTMLDev) structure PD = PPDescFn(SM) open PD fun dBox ds = hovBox (PPS.Rel 1, ds) fun dvBox ds = vBox (PPS.Rel 0, ds) fun ivBox ds = vBox (PPS.Rel 1, ds) fun keyword s = style (HTMLDev.styleB, [string s]) val punct = string fun modify file = let val file' = #file (OS.Path.splitDirFile file) val file' = #base (OS.Path.splitBaseExt file') in file' end fun context s = case providesContext (valOf (!prov), s) of NONE => string s | SOME m => style (HTMLDev.link (modify m ^ ".html#C_" ^ s), [string s]) fun typ s = case providesType (valOf (!prov), s) of NONE => string s | SOME m => style (HTMLDev.link (modify m ^ ".html#T_" ^ s), [string s]) fun exp s = case providesValue (valOf (!prov), s) of NONE => string s | SOME m => style (HTMLDev.link (modify m ^ ".html#V_" ^ s), [string s]) val field = string val lit = string val ident = string fun parenIf pn ds = if pn then dBox (punct "(" :: ds @ [punct ")"]) else dBox ds fun p_pred' pn (p, _) = case p of CRoot => keyword "Root" | CConst s => context s | CPrefix p => dBox [punct "^", p_pred' true p] | CNot p => dBox [punct "!", p_pred' true p] | CAnd (p1, p2) => parenIf pn [p_pred' true p1, space 1, punct "&", space 1, p_pred' true p2] val p_pred = p_pred' false fun p_predBoxed p = dBox [punct "[", p_pred p, punct "]"] fun p_typ' pn (t, _) = case t of TBase s => typ s | TList t => dBox [punct "[", p_typ' false t, punct "]"] | TArrow (t1, t2) => parenIf pn [p_typ' true t1, space 1, punct "->", space 1, p_typ' true t2] | TAction (p, r1, r2) => parenIf pn [p_predBoxed p, space 1, p_record r1, space 1, punct "=>", space 1, p_record r2] | TNested (p, t) => parenIf pn [p_pred' false p, space 1, punct "=>", space 1, p_typ' false t] | TError => keyword "" | TUnif (_, ref (SOME t)) => p_typ' pn t | TUnif (name, ref NONE) => string ("<" ^ name ^ ">") and p_record r = case StringMap.foldri (fn (name, t, d) => SOME (case d of NONE => dBox [field name, space 1, punct ":", space 1, p_typ t] | SOME d => dBox [dBox [field name, space 1, punct ":", space 1, p_typ t], punct ",", space 1, d])) NONE r of NONE => punct "{}" | SOME d => dBox [punct "{", d, punct "}"] and p_typ t = p_typ' false t fun p_exp (e, _) = case e of EInt n => lit (Int.toString n) | EString s => lit (String.concat ["\"", String.toString s, "\""]) | EList es => (case foldr (fn (e, d) => SOME (case d of NONE => p_exp e | SOME d => dBox [p_exp e, punct ",", space 1, d])) NONE es of NONE => punct "[]" | SOME d => dBox [punct "[", d, punct "]"]) | ELam (x, NONE, e) => dBox [punct "(\\", space 1, exp x, space 1, punct "->", space 1, p_exp e, punct ")"] | ELam (x, SOME t, e) => dBox [punct "(\\", space 1, exp x, space 1, punct ":", space 1, dBox [punct "(", p_typ t, punct ")"], space 1, punct "->", space 1, p_exp e, punct ")"] | EALam (x, p, e) => dBox [punct "(\\", space 1, exp x, space 1, punct ":", space 1, p_pred p, space 1, punct "->", space 1, p_exp e, punct ")"] | EVar x => exp x | EApp (e1, e2) => dBox [punct "(", p_exp e1, break {nsp = 1, offset = 0}, p_exp e2, punct ")"] | ESkip => keyword "_" | ESet (x, e) => dBox [exp x, space 1, punct "=", space 1, p_exp e] | EGet (x1, x2, e) => dBox [dBox [exp x1, space 1, punct "<-", space 1, exp x2, punct ";", space 1], p_exp e] | ESeq es => dBox (valOf (foldr (fn (e, NONE) => SOME [p_exp e] | (e, SOME ds) => SOME (dBox [p_exp e, punct ";", newline] :: ds)) NONE es)) | ELocal (e1, e2) => dBox [keyword "let", space 1, p_exp e1, space 1, keyword "in", space 1, p_exp e2, space 1, keyword "end"] | EWith (e1, (ESkip, _)) => dBox [p_exp e1, space 1, keyword "with", space 1, keyword "end"] | EWith (e1, e2) => dBox [p_exp e1, space 1, keyword "with", p_exp e2, space 1, keyword "end"] fun p_decl d = case d of DExternType name => style (HTMLDev.anchor ("T_" ^ name), [dBox [keyword "extern", space 1, keyword "type", space 1, ident name]]) | DExternVal (name, t) => style (HTMLDev.anchor ("V_" ^ name), [dBox [keyword "extern", space 1, keyword "val", space 1, ident name, space 1, string ":", space 1, p_typ t]]) | DVal (name, NONE, _) => string "Unannotated val declaration!" | DVal (name, SOME t, _) => style (HTMLDev.anchor ("V_" ^ name), [dBox [keyword "val", space 1, ident name, space 1, punct ":", space 1, p_typ t]]) | DContext name => style (HTMLDev.anchor ("C_" ^ name), [dBox [keyword "context", space 1, ident name]]) fun p_decl_fref d = case d of DExternType name => dBox [keyword "extern", space 1, keyword "type", space 1, style (HTMLDev.link ("#T_" ^ name), [ident name])] | DExternVal (name, t) => dBox [keyword "extern", space 1, keyword "val", space 1, style (HTMLDev.link ("#V_" ^ name), [ident name]), space 1, string ":", space 1, p_typ t] | DVal (name, NONE, _) => string "Unannotated val declaration!" | DVal (name, SOME t, _) => dBox [keyword "val", space 1, style (HTMLDev.link ("#V_" ^ name), [ident name]), space 1, punct ":", space 1, p_typ t] | DContext name => dBox [keyword "context", space 1, style (HTMLDev.link ("#C_" ^ name), [ident name])] fun output d = let val dev = HTMLDev.openDev {wid = 80, textWid = NONE} val myStream = SM.openStream dev in description (myStream, d); SM.flushStream myStream; HTMLDev.done dev end end