adamc@38
|
1 (* Copyright (c) 2008, Adam Chlipala
|
adamc@38
|
2 * All rights reserved.
|
adamc@38
|
3 *
|
adamc@38
|
4 * Redistribution and use in source and binary forms, with or without
|
adamc@38
|
5 * modification, are permitted provided that the following conditions are met:
|
adamc@38
|
6 *
|
adamc@38
|
7 * - Redistributions of source code must retain the above copyright notice,
|
adamc@38
|
8 * this list of conditions and the following disclaimer.
|
adamc@38
|
9 * - Redistributions in binary form must reproduce the above copyright notice,
|
adamc@38
|
10 * this list of conditions and the following disclaimer in the documentation
|
adamc@38
|
11 * and/or other materials provided with the distribution.
|
adamc@38
|
12 * - The names of contributors may not be used to endorse or promote products
|
adamc@38
|
13 * derived from this software without specific prior written permission.
|
adamc@38
|
14 *
|
adamc@38
|
15 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
|
adamc@38
|
16 * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
|
adamc@38
|
17 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
|
adamc@38
|
18 * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
|
adamc@38
|
19 * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
|
adamc@38
|
20 * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
|
adamc@38
|
21 * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
|
adamc@38
|
22 * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
|
adamc@38
|
23 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
|
adamc@38
|
24 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
adamc@38
|
25 * POSSIBILITY OF SUCH DAMAGE.
|
adamc@38
|
26 *)
|
adamc@38
|
27
|
adamc@38
|
28 structure Explify :> EXPLIFY = struct
|
adamc@38
|
29
|
adamc@38
|
30 structure EM = ErrorMsg
|
adamc@38
|
31 structure L = Elab
|
adamc@38
|
32 structure L' = Expl
|
adamc@38
|
33
|
adamc@38
|
34 fun explifyKind (k, loc) =
|
adamc@38
|
35 case k of
|
adamc@38
|
36 L.KType => (L'.KType, loc)
|
adamc@38
|
37 | L.KArrow (k1, k2) => (L'.KArrow (explifyKind k1, explifyKind k2), loc)
|
adamc@38
|
38 | L.KName => (L'.KName, loc)
|
adamc@38
|
39 | L.KRecord k => (L'.KRecord (explifyKind k), loc)
|
adamc@38
|
40
|
adamc@87
|
41 | L.KUnit => (L'.KUnit, loc)
|
adamc@213
|
42 | L.KTuple ks => (L'.KTuple (map explifyKind ks), loc)
|
adamc@82
|
43
|
adamc@38
|
44 | L.KError => raise Fail ("explifyKind: KError at " ^ EM.spanToString loc)
|
adamc@76
|
45 | L.KUnif (_, _, ref (SOME k)) => explifyKind k
|
adamc@38
|
46 | L.KUnif _ => raise Fail ("explifyKind: KUnif at " ^ EM.spanToString loc)
|
adamc@38
|
47
|
adamc@38
|
48 fun explifyCon (c, loc) =
|
adamc@38
|
49 case c of
|
adamc@38
|
50 L.TFun (t1, t2) => (L'.TFun (explifyCon t1, explifyCon t2), loc)
|
adamc@38
|
51 | L.TCFun (_, x, k, t) => (L'.TCFun (x, explifyKind k, explifyCon t), loc)
|
adamc@334
|
52 | L.TDisjoint (_, _, _, c) => explifyCon c
|
adamc@38
|
53 | L.TRecord c => (L'.TRecord (explifyCon c), loc)
|
adamc@38
|
54
|
adamc@38
|
55 | L.CRel n => (L'.CRel n, loc)
|
adamc@38
|
56 | L.CNamed n => (L'.CNamed n, loc)
|
adamc@38
|
57 | L.CModProj (m, ms, x) => (L'.CModProj (m, ms, x), loc)
|
adamc@38
|
58
|
adamc@38
|
59 | L.CApp (c1, c2) => (L'.CApp (explifyCon c1, explifyCon c2), loc)
|
adamc@38
|
60 | L.CAbs (x, k, c) => (L'.CAbs (x, explifyKind k, explifyCon c), loc)
|
adamc@85
|
61 | L.CDisjoint (_, _, c) => explifyCon c
|
adamc@38
|
62
|
adamc@38
|
63 | L.CName s => (L'.CName s, loc)
|
adamc@38
|
64
|
adamc@38
|
65 | L.CRecord (k, xcs) => (L'.CRecord (explifyKind k, map (fn (c1, c2) => (explifyCon c1, explifyCon c2)) xcs), loc)
|
adamc@38
|
66 | L.CConcat (c1, c2) => (L'.CConcat (explifyCon c1, explifyCon c2), loc)
|
adamc@68
|
67 | L.CFold (dom, ran) => (L'.CFold (explifyKind dom, explifyKind ran), loc)
|
adamc@38
|
68
|
adamc@87
|
69 | L.CUnit => (L'.CUnit, loc)
|
adamc@82
|
70
|
adamc@213
|
71 | L.CTuple cs => (L'.CTuple (map explifyCon cs), loc)
|
adamc@213
|
72 | L.CProj (c, n) => (L'.CProj (explifyCon c, n), loc)
|
adamc@208
|
73
|
adamc@38
|
74 | L.CError => raise Fail ("explifyCon: CError at " ^ EM.spanToString loc)
|
adamc@76
|
75 | L.CUnif (_, _, _, ref (SOME c)) => explifyCon c
|
adamc@38
|
76 | L.CUnif _ => raise Fail ("explifyCon: CUnif at " ^ EM.spanToString loc)
|
adamc@38
|
77
|
adamc@176
|
78 fun explifyPatCon pc =
|
adamc@176
|
79 case pc of
|
adamc@176
|
80 L.PConVar n => L'.PConVar n
|
adamc@176
|
81 | L.PConProj x => L'.PConProj x
|
adamc@176
|
82
|
adamc@176
|
83 fun explifyPat (p, loc) =
|
adamc@176
|
84 case p of
|
adamc@176
|
85 L.PWild => (L'.PWild, loc)
|
adamc@182
|
86 | L.PVar (x, t) => (L'.PVar (x, explifyCon t), loc)
|
adamc@176
|
87 | L.PPrim p => (L'.PPrim p, loc)
|
adamc@191
|
88 | L.PCon (dk, pc, cs, po) => (L'.PCon (dk, explifyPatCon pc, map explifyCon cs, Option.map explifyPat po), loc)
|
adamc@182
|
89 | L.PRecord xps => (L'.PRecord (map (fn (x, p, t) => (x, explifyPat p, explifyCon t)) xps), loc)
|
adamc@176
|
90
|
adamc@38
|
91 fun explifyExp (e, loc) =
|
adamc@38
|
92 case e of
|
adamc@38
|
93 L.EPrim p => (L'.EPrim p, loc)
|
adamc@38
|
94 | L.ERel n => (L'.ERel n, loc)
|
adamc@38
|
95 | L.ENamed n => (L'.ENamed n, loc)
|
adamc@38
|
96 | L.EModProj (m, ms, x) => (L'.EModProj (m, ms, x), loc)
|
adamc@38
|
97 | L.EApp (e1, e2) => (L'.EApp (explifyExp e1, explifyExp e2), loc)
|
adamc@38
|
98 | L.EAbs (x, dom, ran, e1) => (L'.EAbs (x, explifyCon dom, explifyCon ran, explifyExp e1), loc)
|
adamc@38
|
99 | L.ECApp (e1, c) => (L'.ECApp (explifyExp e1, explifyCon c), loc)
|
adamc@38
|
100 | L.ECAbs (_, x, k, e1) => (L'.ECAbs (x, explifyKind k, explifyExp e1), loc)
|
adamc@38
|
101
|
adamc@38
|
102 | L.ERecord xes => (L'.ERecord (map (fn (c, e, t) => (explifyCon c, explifyExp e, explifyCon t)) xes), loc)
|
adamc@38
|
103 | L.EField (e1, c, {field, rest}) => (L'.EField (explifyExp e1, explifyCon c,
|
adamc@38
|
104 {field = explifyCon field, rest = explifyCon rest}), loc)
|
adamc@149
|
105 | L.ECut (e1, c, {field, rest}) => (L'.ECut (explifyExp e1, explifyCon c,
|
adamc@149
|
106 {field = explifyCon field, rest = explifyCon rest}), loc)
|
adamc@72
|
107 | L.EFold k => (L'.EFold (explifyKind k), loc)
|
adamc@38
|
108
|
adamc@182
|
109 | L.ECase (e, pes, {disc, result}) =>
|
adamc@182
|
110 (L'.ECase (explifyExp e,
|
adamc@182
|
111 map (fn (p, e) => (explifyPat p, explifyExp e)) pes,
|
adamc@182
|
112 {disc = explifyCon disc, result = explifyCon result}), loc)
|
adamc@171
|
113
|
adamc@38
|
114 | L.EError => raise Fail ("explifyExp: EError at " ^ EM.spanToString loc)
|
adamc@228
|
115 | L.EUnif (ref (SOME e)) => explifyExp e
|
adamc@228
|
116 | L.EUnif _ => raise Fail ("explifyExp: Undetermined EUnif at " ^ EM.spanToString loc)
|
adamc@38
|
117
|
adamc@38
|
118 fun explifySgi (sgi, loc) =
|
adamc@38
|
119 case sgi of
|
adamc@88
|
120 L.SgiConAbs (x, n, k) => SOME (L'.SgiConAbs (x, n, explifyKind k), loc)
|
adamc@88
|
121 | L.SgiCon (x, n, k, c) => SOME (L'.SgiCon (x, n, explifyKind k, explifyCon c), loc)
|
adamc@191
|
122 | L.SgiDatatype (x, n, xs, xncs) => SOME (L'.SgiDatatype (x, n, xs,
|
adamc@191
|
123 map (fn (x, n, co) =>
|
adamc@191
|
124 (x, n, Option.map explifyCon co)) xncs), loc)
|
adamc@191
|
125 | L.SgiDatatypeImp (x, n, m1, ms, s, xs, xncs) =>
|
adamc@191
|
126 SOME (L'.SgiDatatypeImp (x, n, m1, ms, s, xs, map (fn (x, n, co) =>
|
adamc@191
|
127 (x, n, Option.map explifyCon co)) xncs), loc)
|
adamc@88
|
128 | L.SgiVal (x, n, c) => SOME (L'.SgiVal (x, n, explifyCon c), loc)
|
adamc@88
|
129 | L.SgiStr (x, n, sgn) => SOME (L'.SgiStr (x, n, explifySgn sgn), loc)
|
adamc@88
|
130 | L.SgiSgn (x, n, sgn) => SOME (L'.SgiSgn (x, n, explifySgn sgn), loc)
|
adamc@88
|
131 | L.SgiConstraint _ => NONE
|
adamc@246
|
132 | L.SgiTable (nt, x, n, c) => SOME (L'.SgiTable (nt, x, n, explifyCon c), loc)
|
adamc@211
|
133 | L.SgiClassAbs (x, n) => SOME (L'.SgiConAbs (x, n, (L'.KArrow ((L'.KType, loc), (L'.KType, loc)), loc)), loc)
|
adamc@211
|
134 | L.SgiClass (x, n, c) => SOME (L'.SgiCon (x, n, (L'.KArrow ((L'.KType, loc), (L'.KType, loc)), loc),
|
adamc@211
|
135 explifyCon c), loc)
|
adamc@38
|
136
|
adamc@38
|
137 and explifySgn (sgn, loc) =
|
adamc@38
|
138 case sgn of
|
adamc@88
|
139 L.SgnConst sgis => (L'.SgnConst (List.mapPartial explifySgi sgis), loc)
|
adamc@38
|
140 | L.SgnVar n => (L'.SgnVar n, loc)
|
adamc@45
|
141 | L.SgnFun (m, n, dom, ran) => (L'.SgnFun (m, n, explifySgn dom, explifySgn ran), loc)
|
adamc@45
|
142 | L.SgnWhere (sgn, x, c) => (L'.SgnWhere (explifySgn sgn, x, explifyCon c), loc)
|
adamc@64
|
143 | L.SgnProj x => (L'.SgnProj x, loc)
|
adamc@38
|
144 | L.SgnError => raise Fail ("explifySgn: SgnError at " ^ EM.spanToString loc)
|
adamc@38
|
145
|
adamc@38
|
146 fun explifyDecl (d, loc : EM.span) =
|
adamc@38
|
147 case d of
|
adamc@88
|
148 L.DCon (x, n, k, c) => SOME (L'.DCon (x, n, explifyKind k, explifyCon c), loc)
|
adamc@191
|
149 | L.DDatatype (x, n, xs, xncs) => SOME (L'.DDatatype (x, n, xs,
|
adamc@191
|
150 map (fn (x, n, co) =>
|
adamc@191
|
151 (x, n, Option.map explifyCon co)) xncs), loc)
|
adamc@191
|
152 | L.DDatatypeImp (x, n, m1, ms, s, xs, xncs) =>
|
adamc@191
|
153 SOME (L'.DDatatypeImp (x, n, m1, ms, s, xs,
|
adamc@191
|
154 map (fn (x, n, co) =>
|
adamc@191
|
155 (x, n, Option.map explifyCon co)) xncs), loc)
|
adamc@88
|
156 | L.DVal (x, n, t, e) => SOME (L'.DVal (x, n, explifyCon t, explifyExp e), loc)
|
adamc@124
|
157 | L.DValRec vis => SOME (L'.DValRec (map (fn (x, n, t, e) => (x, n, explifyCon t, explifyExp e)) vis), loc)
|
adamc@38
|
158
|
adamc@88
|
159 | L.DSgn (x, n, sgn) => SOME (L'.DSgn (x, n, explifySgn sgn), loc)
|
adamc@88
|
160 | L.DStr (x, n, sgn, str) => SOME (L'.DStr (x, n, explifySgn sgn, explifyStr str), loc)
|
adamc@88
|
161 | L.DFfiStr (x, n, sgn) => SOME (L'.DFfiStr (x, n, explifySgn sgn), loc)
|
adamc@88
|
162 | L.DConstraint (c1, c2) => NONE
|
adamc@109
|
163 | L.DExport (en, sgn, str) => SOME (L'.DExport (en, explifySgn sgn, explifyStr str), loc)
|
adamc@246
|
164 | L.DTable (nt, x, n, c) => SOME (L'.DTable (nt, x, n, explifyCon c), loc)
|
adamc@213
|
165 | L.DClass (x, n, c) => SOME (L'.DCon (x, n,
|
adamc@213
|
166 (L'.KArrow ((L'.KType, loc), (L'.KType, loc)), loc), explifyCon c), loc)
|
adamc@271
|
167 | L.DDatabase s => SOME (L'.DDatabase s, loc)
|
adamc@38
|
168
|
adamc@38
|
169 and explifyStr (str, loc) =
|
adamc@38
|
170 case str of
|
adamc@88
|
171 L.StrConst ds => (L'.StrConst (List.mapPartial explifyDecl ds), loc)
|
adamc@38
|
172 | L.StrVar n => (L'.StrVar n, loc)
|
adamc@38
|
173 | L.StrProj (str, s) => (L'.StrProj (explifyStr str, s), loc)
|
adamc@45
|
174 | L.StrFun (m, n, dom, ran, str) => (L'.StrFun (m, n, explifySgn dom, explifySgn ran, explifyStr str), loc)
|
adamc@45
|
175 | L.StrApp (str1, str2) => (L'.StrApp (explifyStr str1, explifyStr str2), loc)
|
adamc@38
|
176 | L.StrError => raise Fail ("explifyStr: StrError at " ^ EM.spanToString loc)
|
adamc@38
|
177
|
adamc@88
|
178 val explify = List.mapPartial explifyDecl
|
adamc@38
|
179
|
adamc@38
|
180 end
|