adamc@16
|
1 (* Copyright (c) 2008, Adam Chlipala
|
adamc@16
|
2 * All rights reserved.
|
adamc@16
|
3 *
|
adamc@16
|
4 * Redistribution and use in source and binary forms, with or without
|
adamc@16
|
5 * modification, are permitted provided that the following conditions are met:
|
adamc@16
|
6 *
|
adamc@16
|
7 * - Redistributions of source code must retain the above copyright notice,
|
adamc@16
|
8 * this list of conditions and the following disclaimer.
|
adamc@16
|
9 * - Redistributions in binary form must reproduce the above copyright notice,
|
adamc@16
|
10 * this list of conditions and the following disclaimer in the documentation
|
adamc@16
|
11 * and/or other materials provided with the distribution.
|
adamc@16
|
12 * - The names of contributors may not be used to endorse or promote products
|
adamc@16
|
13 * derived from this software without specific prior written permission.
|
adamc@16
|
14 *
|
adamc@16
|
15 * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
|
adamc@16
|
16 * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
|
adamc@16
|
17 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
|
adamc@16
|
18 * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
|
adamc@16
|
19 * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
|
adamc@16
|
20 * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
|
adamc@16
|
21 * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
|
adamc@16
|
22 * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
|
adamc@16
|
23 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
|
adamc@16
|
24 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
adamc@16
|
25 * POSSIBILITY OF SUCH DAMAGE.
|
adamc@16
|
26 *)
|
adamc@16
|
27
|
adamc@16
|
28 structure Corify :> CORIFY = struct
|
adamc@16
|
29
|
adamc@16
|
30 structure EM = ErrorMsg
|
adamc@39
|
31 structure L = Expl
|
adamc@16
|
32 structure L' = Core
|
adamc@16
|
33
|
adamc@39
|
34 structure IM = IntBinaryMap
|
adamc@39
|
35 structure SM = BinaryMapFn(struct
|
adamc@39
|
36 type ord_key = string
|
adamc@39
|
37 val compare = String.compare
|
adamc@39
|
38 end)
|
adamc@39
|
39
|
adamc@39
|
40 local
|
adamc@39
|
41 val count = ref 0
|
adamc@39
|
42 in
|
adamc@39
|
43
|
adamc@39
|
44 fun reset v = count := v
|
adamc@39
|
45
|
adamc@39
|
46 fun alloc () =
|
adamc@39
|
47 let
|
adamc@39
|
48 val r = !count
|
adamc@39
|
49 in
|
adamc@39
|
50 count := r + 1;
|
adamc@39
|
51 r
|
adamc@39
|
52 end
|
adamc@39
|
53
|
adamc@39
|
54 end
|
adamc@39
|
55
|
adamc@39
|
56 structure St : sig
|
adamc@39
|
57 type t
|
adamc@39
|
58
|
adamc@39
|
59 val empty : t
|
adamc@39
|
60
|
adamc@39
|
61 val enter : t -> t
|
adamc@39
|
62 val leave : t -> {outer : t, inner : t}
|
adamc@39
|
63
|
adamc@39
|
64 val bindCore : t -> string -> int -> t * int
|
adamc@39
|
65 val lookupCoreById : t -> int -> int option
|
adamc@39
|
66 val lookupCoreByName : t -> string -> int
|
adamc@39
|
67
|
adamc@39
|
68 val bindStr : t -> string -> int -> t -> t
|
adamc@39
|
69 val lookupStrById : t -> int -> t
|
adamc@39
|
70 val lookupStrByName : string * t -> t
|
adamc@46
|
71
|
adamc@46
|
72 val bindFunctor : t -> string -> int -> int -> L.str -> t
|
adamc@46
|
73 val lookupFunctorById : t -> int -> int * L.str
|
adamc@46
|
74 val lookupFunctorByName : string * t -> int * L.str
|
adamc@39
|
75 end = struct
|
adamc@39
|
76
|
adamc@39
|
77 datatype flattening = F of {
|
adamc@39
|
78 core : int SM.map,
|
adamc@46
|
79 strs : flattening SM.map,
|
adamc@46
|
80 funs : (int * L.str) SM.map
|
adamc@39
|
81 }
|
adamc@39
|
82
|
adamc@39
|
83 type t = {
|
adamc@39
|
84 core : int IM.map,
|
adamc@39
|
85 strs : flattening IM.map,
|
adamc@46
|
86 funs : (int * L.str) IM.map,
|
adamc@39
|
87 current : flattening,
|
adamc@39
|
88 nested : flattening list
|
adamc@39
|
89 }
|
adamc@39
|
90
|
adamc@39
|
91 val empty = {
|
adamc@39
|
92 core = IM.empty,
|
adamc@39
|
93 strs = IM.empty,
|
adamc@46
|
94 funs = IM.empty,
|
adamc@46
|
95 current = F { core = SM.empty, strs = SM.empty, funs = SM.empty },
|
adamc@39
|
96 nested = []
|
adamc@39
|
97 }
|
adamc@39
|
98
|
adamc@46
|
99 fun bindCore {core, strs, funs, current, nested} s n =
|
adamc@39
|
100 let
|
adamc@39
|
101 val n' = alloc ()
|
adamc@39
|
102
|
adamc@39
|
103 val current =
|
adamc@39
|
104 let
|
adamc@46
|
105 val F {core, strs, funs} = current
|
adamc@39
|
106 in
|
adamc@39
|
107 F {core = SM.insert (core, s, n'),
|
adamc@46
|
108 strs = strs,
|
adamc@46
|
109 funs = funs}
|
adamc@39
|
110 end
|
adamc@39
|
111 in
|
adamc@39
|
112 ({core = IM.insert (core, n, n'),
|
adamc@39
|
113 strs = strs,
|
adamc@46
|
114 funs = funs,
|
adamc@39
|
115 current = current,
|
adamc@39
|
116 nested = nested},
|
adamc@39
|
117 n')
|
adamc@39
|
118 end
|
adamc@39
|
119
|
adamc@39
|
120 fun lookupCoreById ({core, ...} : t) n = IM.find (core, n)
|
adamc@39
|
121
|
adamc@39
|
122 fun lookupCoreByName ({current = F {core, ...}, ...} : t) x =
|
adamc@39
|
123 case SM.find (core, x) of
|
adamc@39
|
124 NONE => raise Fail "Corify.St.lookupCoreByName"
|
adamc@39
|
125 | SOME n => n
|
adamc@39
|
126
|
adamc@46
|
127 fun enter {core, strs, funs, current, nested} =
|
adamc@39
|
128 {core = core,
|
adamc@39
|
129 strs = strs,
|
adamc@46
|
130 funs = funs,
|
adamc@39
|
131 current = F {core = SM.empty,
|
adamc@46
|
132 strs = SM.empty,
|
adamc@46
|
133 funs = SM.empty},
|
adamc@39
|
134 nested = current :: nested}
|
adamc@39
|
135
|
adamc@39
|
136 fun dummy f = {core = IM.empty,
|
adamc@39
|
137 strs = IM.empty,
|
adamc@46
|
138 funs = IM.empty,
|
adamc@39
|
139 current = f,
|
adamc@39
|
140 nested = []}
|
adamc@39
|
141
|
adamc@46
|
142 fun leave {core, strs, funs, current, nested = m1 :: rest} =
|
adamc@39
|
143 {outer = {core = core,
|
adamc@39
|
144 strs = strs,
|
adamc@46
|
145 funs = funs,
|
adamc@39
|
146 current = m1,
|
adamc@39
|
147 nested = rest},
|
adamc@39
|
148 inner = dummy current}
|
adamc@39
|
149 | leave _ = raise Fail "Corify.St.leave"
|
adamc@39
|
150
|
adamc@46
|
151 fun bindStr ({core, strs, funs, current = F {core = mcore, strs = mstrs, funs = mfuns}, nested} : t)
|
adamc@46
|
152 x n ({current = f, ...} : t) =
|
adamc@39
|
153 {core = core,
|
adamc@39
|
154 strs = IM.insert (strs, n, f),
|
adamc@46
|
155 funs = funs,
|
adamc@39
|
156 current = F {core = mcore,
|
adamc@46
|
157 strs = SM.insert (mstrs, x, f),
|
adamc@46
|
158 funs = mfuns},
|
adamc@39
|
159 nested = nested}
|
adamc@39
|
160
|
adamc@39
|
161 fun lookupStrById ({strs, ...} : t) n =
|
adamc@39
|
162 case IM.find (strs, n) of
|
adamc@46
|
163 NONE => raise Fail "Corify.St.lookupStrById"
|
adamc@39
|
164 | SOME f => dummy f
|
adamc@39
|
165
|
adamc@39
|
166 fun lookupStrByName (m, {current = F {strs, ...}, ...} : t) =
|
adamc@39
|
167 case SM.find (strs, m) of
|
adamc@39
|
168 NONE => raise Fail "Corify.St.lookupStrByName"
|
adamc@39
|
169 | SOME f => dummy f
|
adamc@39
|
170
|
adamc@46
|
171 fun bindFunctor ({core, strs, funs, current = F {core = mcore, strs = mstrs, funs = mfuns}, nested} : t)
|
adamc@46
|
172 x n na str =
|
adamc@46
|
173 {core = core,
|
adamc@46
|
174 strs = strs,
|
adamc@46
|
175 funs = IM.insert (funs, n, (na, str)),
|
adamc@46
|
176 current = F {core = mcore,
|
adamc@46
|
177 strs = mstrs,
|
adamc@46
|
178 funs = SM.insert (mfuns, x, (na, str))},
|
adamc@46
|
179 nested = nested}
|
adamc@46
|
180
|
adamc@46
|
181 fun lookupFunctorById ({funs, ...} : t) n =
|
adamc@46
|
182 case IM.find (funs, n) of
|
adamc@46
|
183 NONE => raise Fail "Corify.St.lookupFunctorById"
|
adamc@46
|
184 | SOME v => v
|
adamc@46
|
185
|
adamc@46
|
186 fun lookupFunctorByName (m, {current = F {funs, ...}, ...} : t) =
|
adamc@46
|
187 case SM.find (funs, m) of
|
adamc@46
|
188 NONE => raise Fail "Corify.St.lookupFunctorByName"
|
adamc@46
|
189 | SOME v => v
|
adamc@46
|
190
|
adamc@39
|
191 end
|
adamc@39
|
192
|
adamc@39
|
193
|
adamc@16
|
194 fun corifyKind (k, loc) =
|
adamc@16
|
195 case k of
|
adamc@16
|
196 L.KType => (L'.KType, loc)
|
adamc@16
|
197 | L.KArrow (k1, k2) => (L'.KArrow (corifyKind k1, corifyKind k2), loc)
|
adamc@16
|
198 | L.KName => (L'.KName, loc)
|
adamc@16
|
199 | L.KRecord k => (L'.KRecord (corifyKind k), loc)
|
adamc@16
|
200
|
adamc@39
|
201 fun corifyCon st (c, loc) =
|
adamc@16
|
202 case c of
|
adamc@39
|
203 L.TFun (t1, t2) => (L'.TFun (corifyCon st t1, corifyCon st t2), loc)
|
adamc@39
|
204 | L.TCFun (x, k, t) => (L'.TCFun (x, corifyKind k, corifyCon st t), loc)
|
adamc@39
|
205 | L.TRecord c => (L'.TRecord (corifyCon st c), loc)
|
adamc@16
|
206
|
adamc@16
|
207 | L.CRel n => (L'.CRel n, loc)
|
adamc@39
|
208 | L.CNamed n =>
|
adamc@39
|
209 (case St.lookupCoreById st n of
|
adamc@39
|
210 NONE => (L'.CNamed n, loc)
|
adamc@39
|
211 | SOME n => (L'.CNamed n, loc))
|
adamc@39
|
212 | L.CModProj (m, ms, x) =>
|
adamc@39
|
213 let
|
adamc@39
|
214 val st = St.lookupStrById st m
|
adamc@39
|
215 val st = foldl St.lookupStrByName st ms
|
adamc@39
|
216 val n = St.lookupCoreByName st x
|
adamc@39
|
217 in
|
adamc@39
|
218 (L'.CNamed n, loc)
|
adamc@39
|
219 end
|
adamc@34
|
220
|
adamc@39
|
221 | L.CApp (c1, c2) => (L'.CApp (corifyCon st c1, corifyCon st c2), loc)
|
adamc@39
|
222 | L.CAbs (x, k, c) => (L'.CAbs (x, corifyKind k, corifyCon st c), loc)
|
adamc@16
|
223
|
adamc@16
|
224 | L.CName s => (L'.CName s, loc)
|
adamc@16
|
225
|
adamc@39
|
226 | L.CRecord (k, xcs) =>
|
adamc@39
|
227 (L'.CRecord (corifyKind k, map (fn (c1, c2) => (corifyCon st c1, corifyCon st c2)) xcs), loc)
|
adamc@39
|
228 | L.CConcat (c1, c2) => (L'.CConcat (corifyCon st c1, corifyCon st c2), loc)
|
adamc@16
|
229
|
adamc@39
|
230 fun corifyExp st (e, loc) =
|
adamc@16
|
231 case e of
|
adamc@16
|
232 L.EPrim p => (L'.EPrim p, loc)
|
adamc@16
|
233 | L.ERel n => (L'.ERel n, loc)
|
adamc@39
|
234 | L.ENamed n =>
|
adamc@39
|
235 (case St.lookupCoreById st n of
|
adamc@39
|
236 NONE => (L'.ENamed n, loc)
|
adamc@39
|
237 | SOME n => (L'.ENamed n, loc))
|
adamc@39
|
238 | L.EModProj (m, ms, x) =>
|
adamc@39
|
239 let
|
adamc@39
|
240 val st = St.lookupStrById st m
|
adamc@39
|
241 val st = foldl St.lookupStrByName st ms
|
adamc@39
|
242 val n = St.lookupCoreByName st x
|
adamc@39
|
243 in
|
adamc@39
|
244 (L'.ENamed n, loc)
|
adamc@39
|
245 end
|
adamc@39
|
246 | L.EApp (e1, e2) => (L'.EApp (corifyExp st e1, corifyExp st e2), loc)
|
adamc@39
|
247 | L.EAbs (x, dom, ran, e1) => (L'.EAbs (x, corifyCon st dom, corifyCon st ran, corifyExp st e1), loc)
|
adamc@39
|
248 | L.ECApp (e1, c) => (L'.ECApp (corifyExp st e1, corifyCon st c), loc)
|
adamc@39
|
249 | L.ECAbs (x, k, e1) => (L'.ECAbs (x, corifyKind k, corifyExp st e1), loc)
|
adamc@16
|
250
|
adamc@39
|
251 | L.ERecord xes => (L'.ERecord (map (fn (c, e, t) => (corifyCon st c, corifyExp st e, corifyCon st t)) xes), loc)
|
adamc@39
|
252 | L.EField (e1, c, {field, rest}) => (L'.EField (corifyExp st e1, corifyCon st c,
|
adamc@39
|
253 {field = corifyCon st field, rest = corifyCon st rest}), loc)
|
adamc@16
|
254
|
adamc@39
|
255 fun corifyDecl ((d, loc : EM.span), st) =
|
adamc@39
|
256 case d of
|
adamc@39
|
257 L.DCon (x, n, k, c) =>
|
adamc@39
|
258 let
|
adamc@39
|
259 val (st, n) = St.bindCore st x n
|
adamc@39
|
260 in
|
adamc@39
|
261 ([(L'.DCon (x, n, corifyKind k, corifyCon st c), loc)], st)
|
adamc@39
|
262 end
|
adamc@39
|
263 | L.DVal (x, n, t, e) =>
|
adamc@39
|
264 let
|
adamc@39
|
265 val (st, n) = St.bindCore st x n
|
adamc@39
|
266 in
|
adamc@39
|
267 ([(L'.DVal (x, n, corifyCon st t, corifyExp st e), loc)], st)
|
adamc@39
|
268 end
|
adamc@39
|
269
|
adamc@39
|
270 | L.DSgn _ => ([], st)
|
adamc@16
|
271
|
adamc@46
|
272 | L.DStr (x, n, _, (L.StrFun (_, na, _, _, str), _)) =>
|
adamc@46
|
273 ([], St.bindFunctor st x n na str)
|
adamc@46
|
274
|
adamc@39
|
275 | L.DStr (x, n, _, str) =>
|
adamc@39
|
276 let
|
adamc@39
|
277 val (ds, {inner, outer}) = corifyStr (str, st)
|
adamc@39
|
278 val st = St.bindStr outer x n inner
|
adamc@39
|
279 in
|
adamc@39
|
280 (ds, st)
|
adamc@39
|
281 end
|
adamc@16
|
282
|
adamc@39
|
283 and corifyStr ((str, _), st) =
|
adamc@39
|
284 case str of
|
adamc@39
|
285 L.StrConst ds =>
|
adamc@39
|
286 let
|
adamc@39
|
287 val st = St.enter st
|
adamc@39
|
288 val (ds, st) = ListUtil.foldlMapConcat corifyDecl st ds
|
adamc@39
|
289 in
|
adamc@39
|
290 (ds, St.leave st)
|
adamc@39
|
291 end
|
adamc@39
|
292 | L.StrVar n => ([], {inner = St.lookupStrById st n, outer = st})
|
adamc@39
|
293 | L.StrProj (str, x) =>
|
adamc@39
|
294 let
|
adamc@39
|
295 val (ds, {inner, outer}) = corifyStr (str, st)
|
adamc@39
|
296 in
|
adamc@39
|
297 (ds, {inner = St.lookupStrByName (x, inner), outer = outer})
|
adamc@39
|
298 end
|
adamc@46
|
299 | L.StrFun _ => raise Fail "Corify of nested functor definition"
|
adamc@46
|
300 | L.StrApp (str1, str2) =>
|
adamc@46
|
301 let
|
adamc@46
|
302 fun unwind' (str, _) =
|
adamc@46
|
303 case str of
|
adamc@46
|
304 L.StrVar n => St.lookupStrById st n
|
adamc@46
|
305 | L.StrProj (str, x) => St.lookupStrByName (x, unwind' str)
|
adamc@46
|
306 | _ => raise Fail "Corify of fancy functor application [1]"
|
adamc@46
|
307
|
adamc@46
|
308 fun unwind (str, _) =
|
adamc@46
|
309 case str of
|
adamc@46
|
310 L.StrVar n => St.lookupFunctorById st n
|
adamc@46
|
311 | L.StrProj (str, x) => St.lookupFunctorByName (x, unwind' str)
|
adamc@46
|
312 | _ => raise Fail "Corify of fancy functor application [2]"
|
adamc@46
|
313
|
adamc@46
|
314 val (na, body) = unwind str1
|
adamc@46
|
315
|
adamc@46
|
316 val (ds1, {inner, outer}) = corifyStr (str2, st)
|
adamc@46
|
317 val (ds2, sts) = corifyStr (body, St.bindStr outer "ARG" na inner)
|
adamc@46
|
318 in
|
adamc@46
|
319 (ds1 @ ds2, sts)
|
adamc@46
|
320 end
|
adamc@31
|
321
|
adamc@39
|
322 fun maxName ds = foldl (fn ((d, _), n) =>
|
adamc@39
|
323 case d of
|
adamc@39
|
324 L.DCon (_, n', _, _) => Int.max (n, n')
|
adamc@39
|
325 | L.DVal (_, n', _ , _) => Int.max (n, n')
|
adamc@39
|
326 | L.DSgn (_, n', _) => Int.max (n, n')
|
adamc@39
|
327 | L.DStr (_, n', _, str) => Int.max (n, Int.max (n', maxNameStr str)))
|
adamc@39
|
328 0 ds
|
adamc@39
|
329
|
adamc@39
|
330 and maxNameStr (str, _) =
|
adamc@39
|
331 case str of
|
adamc@39
|
332 L.StrConst ds => maxName ds
|
adamc@39
|
333 | L.StrVar n => n
|
adamc@39
|
334 | L.StrProj (str, _) => maxNameStr str
|
adamc@45
|
335 | L.StrFun (_, _, _, _, str) => maxNameStr str
|
adamc@45
|
336 | L.StrApp (str1, str2) => Int.max (maxNameStr str1, maxNameStr str2)
|
adamc@39
|
337
|
adamc@39
|
338 fun corify ds =
|
adamc@39
|
339 let
|
adamc@39
|
340 val () = reset (maxName ds + 1)
|
adamc@39
|
341 val (ds, _) = ListUtil.foldlMapConcat corifyDecl St.empty ds
|
adamc@39
|
342 in
|
adamc@39
|
343 ds
|
adamc@39
|
344 end
|
adamc@16
|
345
|
adamc@16
|
346 end
|