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@49
|
63 val ffi : string -> L'.con SM.map -> t
|
adamc@39
|
64
|
adamc@39
|
65 val bindCore : t -> string -> int -> t * int
|
adamc@39
|
66 val lookupCoreById : t -> int -> int option
|
adamc@48
|
67
|
adamc@48
|
68 datatype core =
|
adamc@48
|
69 Normal of int
|
adamc@49
|
70 | Ffi of string * L'.con option
|
adamc@48
|
71 val lookupCoreByName : t -> string -> core
|
adamc@39
|
72
|
adamc@39
|
73 val bindStr : t -> string -> int -> t -> t
|
adamc@39
|
74 val lookupStrById : t -> int -> t
|
adamc@39
|
75 val lookupStrByName : string * t -> t
|
adamc@46
|
76
|
adamc@46
|
77 val bindFunctor : t -> string -> int -> int -> L.str -> t
|
adamc@46
|
78 val lookupFunctorById : t -> int -> int * L.str
|
adamc@46
|
79 val lookupFunctorByName : string * t -> int * L.str
|
adamc@39
|
80 end = struct
|
adamc@39
|
81
|
adamc@48
|
82 datatype flattening =
|
adamc@48
|
83 FNormal of {core : int SM.map,
|
adamc@48
|
84 strs : flattening SM.map,
|
adamc@48
|
85 funs : (int * L.str) SM.map}
|
adamc@49
|
86 | FFfi of string * L'.con SM.map
|
adamc@39
|
87
|
adamc@39
|
88 type t = {
|
adamc@39
|
89 core : int IM.map,
|
adamc@39
|
90 strs : flattening IM.map,
|
adamc@46
|
91 funs : (int * L.str) IM.map,
|
adamc@39
|
92 current : flattening,
|
adamc@39
|
93 nested : flattening list
|
adamc@39
|
94 }
|
adamc@39
|
95
|
adamc@39
|
96 val empty = {
|
adamc@39
|
97 core = IM.empty,
|
adamc@39
|
98 strs = IM.empty,
|
adamc@46
|
99 funs = IM.empty,
|
adamc@48
|
100 current = FNormal { core = SM.empty, strs = SM.empty, funs = SM.empty },
|
adamc@39
|
101 nested = []
|
adamc@39
|
102 }
|
adamc@39
|
103
|
adamc@48
|
104 datatype core =
|
adamc@48
|
105 Normal of int
|
adamc@49
|
106 | Ffi of string * L'.con option
|
adamc@48
|
107
|
adamc@46
|
108 fun bindCore {core, strs, funs, current, nested} s n =
|
adamc@39
|
109 let
|
adamc@39
|
110 val n' = alloc ()
|
adamc@39
|
111
|
adamc@39
|
112 val current =
|
adamc@48
|
113 case current of
|
adamc@48
|
114 FFfi _ => raise Fail "Binding inside FFfi"
|
adamc@48
|
115 | FNormal {core, strs, funs} =>
|
adamc@48
|
116 FNormal {core = SM.insert (core, s, n'),
|
adamc@48
|
117 strs = strs,
|
adamc@48
|
118 funs = funs}
|
adamc@39
|
119 in
|
adamc@39
|
120 ({core = IM.insert (core, n, n'),
|
adamc@39
|
121 strs = strs,
|
adamc@46
|
122 funs = funs,
|
adamc@39
|
123 current = current,
|
adamc@39
|
124 nested = nested},
|
adamc@39
|
125 n')
|
adamc@39
|
126 end
|
adamc@39
|
127
|
adamc@39
|
128 fun lookupCoreById ({core, ...} : t) n = IM.find (core, n)
|
adamc@39
|
129
|
adamc@48
|
130 fun lookupCoreByName ({current, ...} : t) x =
|
adamc@48
|
131 case current of
|
adamc@49
|
132 FFfi (m, cmap) => Ffi (m, SM.find (cmap, x))
|
adamc@48
|
133 | FNormal {core, ...} =>
|
adamc@48
|
134 case SM.find (core, x) of
|
adamc@48
|
135 NONE => raise Fail "Corify.St.lookupCoreByName"
|
adamc@48
|
136 | SOME n => Normal n
|
adamc@39
|
137
|
adamc@46
|
138 fun enter {core, strs, funs, current, nested} =
|
adamc@39
|
139 {core = core,
|
adamc@39
|
140 strs = strs,
|
adamc@46
|
141 funs = funs,
|
adamc@48
|
142 current = FNormal {core = SM.empty,
|
adamc@48
|
143 strs = SM.empty,
|
adamc@48
|
144 funs = SM.empty},
|
adamc@39
|
145 nested = current :: nested}
|
adamc@39
|
146
|
adamc@39
|
147 fun dummy f = {core = IM.empty,
|
adamc@39
|
148 strs = IM.empty,
|
adamc@46
|
149 funs = IM.empty,
|
adamc@39
|
150 current = f,
|
adamc@39
|
151 nested = []}
|
adamc@39
|
152
|
adamc@46
|
153 fun leave {core, strs, funs, current, nested = m1 :: rest} =
|
adamc@39
|
154 {outer = {core = core,
|
adamc@39
|
155 strs = strs,
|
adamc@46
|
156 funs = funs,
|
adamc@39
|
157 current = m1,
|
adamc@39
|
158 nested = rest},
|
adamc@39
|
159 inner = dummy current}
|
adamc@39
|
160 | leave _ = raise Fail "Corify.St.leave"
|
adamc@39
|
161
|
adamc@49
|
162 fun ffi m cmap = dummy (FFfi (m, cmap))
|
adamc@48
|
163
|
adamc@48
|
164 fun bindStr ({core, strs, funs, current = FNormal {core = mcore, strs = mstrs, funs = mfuns}, nested} : t)
|
adamc@46
|
165 x n ({current = f, ...} : t) =
|
adamc@39
|
166 {core = core,
|
adamc@39
|
167 strs = IM.insert (strs, n, f),
|
adamc@46
|
168 funs = funs,
|
adamc@48
|
169 current = FNormal {core = mcore,
|
adamc@46
|
170 strs = SM.insert (mstrs, x, f),
|
adamc@46
|
171 funs = mfuns},
|
adamc@39
|
172 nested = nested}
|
adamc@48
|
173 | bindStr _ _ _ _ = raise Fail "Corify.St.bindStr"
|
adamc@39
|
174
|
adamc@39
|
175 fun lookupStrById ({strs, ...} : t) n =
|
adamc@39
|
176 case IM.find (strs, n) of
|
adamc@46
|
177 NONE => raise Fail "Corify.St.lookupStrById"
|
adamc@39
|
178 | SOME f => dummy f
|
adamc@39
|
179
|
adamc@48
|
180 fun lookupStrByName (m, {current = FNormal {strs, ...}, ...} : t) =
|
adamc@48
|
181 (case SM.find (strs, m) of
|
adamc@48
|
182 NONE => raise Fail "Corify.St.lookupStrByName"
|
adamc@48
|
183 | SOME f => dummy f)
|
adamc@48
|
184 | lookupStrByName _ = raise Fail "Corify.St.lookupStrByName"
|
adamc@39
|
185
|
adamc@48
|
186 fun bindFunctor ({core, strs, funs, current = FNormal {core = mcore, strs = mstrs, funs = mfuns}, nested} : t)
|
adamc@46
|
187 x n na str =
|
adamc@46
|
188 {core = core,
|
adamc@46
|
189 strs = strs,
|
adamc@46
|
190 funs = IM.insert (funs, n, (na, str)),
|
adamc@48
|
191 current = FNormal {core = mcore,
|
adamc@48
|
192 strs = mstrs,
|
adamc@48
|
193 funs = SM.insert (mfuns, x, (na, str))},
|
adamc@46
|
194 nested = nested}
|
adamc@48
|
195 | bindFunctor _ _ _ _ _ = raise Fail "Corify.St.bindFunctor"
|
adamc@46
|
196
|
adamc@46
|
197 fun lookupFunctorById ({funs, ...} : t) n =
|
adamc@46
|
198 case IM.find (funs, n) of
|
adamc@46
|
199 NONE => raise Fail "Corify.St.lookupFunctorById"
|
adamc@46
|
200 | SOME v => v
|
adamc@46
|
201
|
adamc@48
|
202 fun lookupFunctorByName (m, {current = FNormal {funs, ...}, ...} : t) =
|
adamc@48
|
203 (case SM.find (funs, m) of
|
adamc@48
|
204 NONE => raise Fail "Corify.St.lookupFunctorByName"
|
adamc@48
|
205 | SOME v => v)
|
adamc@48
|
206 | lookupFunctorByName _ = raise Fail "Corify.St.lookupFunctorByName"
|
adamc@46
|
207
|
adamc@39
|
208 end
|
adamc@39
|
209
|
adamc@39
|
210
|
adamc@16
|
211 fun corifyKind (k, loc) =
|
adamc@16
|
212 case k of
|
adamc@16
|
213 L.KType => (L'.KType, loc)
|
adamc@16
|
214 | L.KArrow (k1, k2) => (L'.KArrow (corifyKind k1, corifyKind k2), loc)
|
adamc@16
|
215 | L.KName => (L'.KName, loc)
|
adamc@16
|
216 | L.KRecord k => (L'.KRecord (corifyKind k), loc)
|
adamc@16
|
217
|
adamc@39
|
218 fun corifyCon st (c, loc) =
|
adamc@16
|
219 case c of
|
adamc@39
|
220 L.TFun (t1, t2) => (L'.TFun (corifyCon st t1, corifyCon st t2), loc)
|
adamc@39
|
221 | L.TCFun (x, k, t) => (L'.TCFun (x, corifyKind k, corifyCon st t), loc)
|
adamc@39
|
222 | L.TRecord c => (L'.TRecord (corifyCon st c), loc)
|
adamc@16
|
223
|
adamc@16
|
224 | L.CRel n => (L'.CRel n, loc)
|
adamc@39
|
225 | L.CNamed n =>
|
adamc@39
|
226 (case St.lookupCoreById st n of
|
adamc@39
|
227 NONE => (L'.CNamed n, loc)
|
adamc@39
|
228 | SOME n => (L'.CNamed n, loc))
|
adamc@39
|
229 | L.CModProj (m, ms, x) =>
|
adamc@39
|
230 let
|
adamc@39
|
231 val st = St.lookupStrById st m
|
adamc@39
|
232 val st = foldl St.lookupStrByName st ms
|
adamc@39
|
233 in
|
adamc@48
|
234 case St.lookupCoreByName st x of
|
adamc@48
|
235 St.Normal n => (L'.CNamed n, loc)
|
adamc@49
|
236 | St.Ffi (m, _) => (L'.CFfi (m, x), loc)
|
adamc@39
|
237 end
|
adamc@34
|
238
|
adamc@39
|
239 | L.CApp (c1, c2) => (L'.CApp (corifyCon st c1, corifyCon st c2), loc)
|
adamc@39
|
240 | L.CAbs (x, k, c) => (L'.CAbs (x, corifyKind k, corifyCon st c), loc)
|
adamc@16
|
241
|
adamc@16
|
242 | L.CName s => (L'.CName s, loc)
|
adamc@16
|
243
|
adamc@39
|
244 | L.CRecord (k, xcs) =>
|
adamc@39
|
245 (L'.CRecord (corifyKind k, map (fn (c1, c2) => (corifyCon st c1, corifyCon st c2)) xcs), loc)
|
adamc@39
|
246 | L.CConcat (c1, c2) => (L'.CConcat (corifyCon st c1, corifyCon st c2), loc)
|
adamc@69
|
247 | L.CFold (k1, k2) => (L'.CFold (corifyKind k1, corifyKind k2), loc)
|
adamc@16
|
248
|
adamc@39
|
249 fun corifyExp st (e, loc) =
|
adamc@16
|
250 case e of
|
adamc@16
|
251 L.EPrim p => (L'.EPrim p, loc)
|
adamc@16
|
252 | L.ERel n => (L'.ERel n, loc)
|
adamc@39
|
253 | L.ENamed n =>
|
adamc@39
|
254 (case St.lookupCoreById st n of
|
adamc@39
|
255 NONE => (L'.ENamed n, loc)
|
adamc@39
|
256 | SOME n => (L'.ENamed n, loc))
|
adamc@39
|
257 | L.EModProj (m, ms, x) =>
|
adamc@39
|
258 let
|
adamc@39
|
259 val st = St.lookupStrById st m
|
adamc@39
|
260 val st = foldl St.lookupStrByName st ms
|
adamc@39
|
261 in
|
adamc@48
|
262 case St.lookupCoreByName st x of
|
adamc@48
|
263 St.Normal n => (L'.ENamed n, loc)
|
adamc@49
|
264 | St.Ffi (_, NONE) => raise Fail "corifyExp: Unknown type for FFI expression variable"
|
adamc@49
|
265 | St.Ffi (m, SOME t) =>
|
adamc@49
|
266 case t of
|
adamc@50
|
267 (L'.TFun (dom as (L'.TRecord (L'.CRecord (_, []), _), _), ran), _) =>
|
adamc@50
|
268 (L'.EAbs ("arg", dom, ran, (L'.EFfiApp (m, x, []), loc)), loc)
|
adamc@50
|
269 | t as (L'.TFun _, _) =>
|
adamc@49
|
270 let
|
adamc@49
|
271 fun getArgs (all as (t, _), args) =
|
adamc@49
|
272 case t of
|
adamc@49
|
273 L'.TFun (dom, ran) => getArgs (ran, dom :: args)
|
adamc@49
|
274 | _ => (all, rev args)
|
adamc@49
|
275
|
adamc@49
|
276 val (result, args) = getArgs (t, [])
|
adamc@49
|
277
|
adamc@50
|
278 val (actuals, _) = foldr (fn (_, (actuals, n)) =>
|
adamc@50
|
279 ((L'.ERel n, loc) :: actuals,
|
adamc@50
|
280 n + 1)) ([], 0) args
|
adamc@50
|
281 val app = (L'.EFfiApp (m, x, actuals), loc)
|
adamc@49
|
282 val (abs, _, _) = foldr (fn (t, (abs, ran, n)) =>
|
adamc@49
|
283 ((L'.EAbs ("arg" ^ Int.toString n,
|
adamc@49
|
284 t,
|
adamc@49
|
285 ran,
|
adamc@49
|
286 abs), loc),
|
adamc@49
|
287 (L'.TFun (t, ran), loc),
|
adamc@49
|
288 n - 1)) (app, result, length args - 1) args
|
adamc@49
|
289 in
|
adamc@49
|
290 abs
|
adamc@49
|
291 end
|
adamc@49
|
292 | _ => (L'.EFfi (m, x), loc)
|
adamc@39
|
293 end
|
adamc@39
|
294 | L.EApp (e1, e2) => (L'.EApp (corifyExp st e1, corifyExp st e2), loc)
|
adamc@39
|
295 | L.EAbs (x, dom, ran, e1) => (L'.EAbs (x, corifyCon st dom, corifyCon st ran, corifyExp st e1), loc)
|
adamc@39
|
296 | L.ECApp (e1, c) => (L'.ECApp (corifyExp st e1, corifyCon st c), loc)
|
adamc@39
|
297 | L.ECAbs (x, k, e1) => (L'.ECAbs (x, corifyKind k, corifyExp st e1), loc)
|
adamc@16
|
298
|
adamc@39
|
299 | L.ERecord xes => (L'.ERecord (map (fn (c, e, t) => (corifyCon st c, corifyExp st e, corifyCon st t)) xes), loc)
|
adamc@39
|
300 | L.EField (e1, c, {field, rest}) => (L'.EField (corifyExp st e1, corifyCon st c,
|
adamc@39
|
301 {field = corifyCon st field, rest = corifyCon st rest}), loc)
|
adamc@16
|
302
|
adamc@39
|
303 fun corifyDecl ((d, loc : EM.span), st) =
|
adamc@39
|
304 case d of
|
adamc@39
|
305 L.DCon (x, n, k, c) =>
|
adamc@39
|
306 let
|
adamc@39
|
307 val (st, n) = St.bindCore st x n
|
adamc@39
|
308 in
|
adamc@39
|
309 ([(L'.DCon (x, n, corifyKind k, corifyCon st c), loc)], st)
|
adamc@39
|
310 end
|
adamc@39
|
311 | L.DVal (x, n, t, e) =>
|
adamc@39
|
312 let
|
adamc@39
|
313 val (st, n) = St.bindCore st x n
|
adamc@39
|
314 in
|
adamc@39
|
315 ([(L'.DVal (x, n, corifyCon st t, corifyExp st e), loc)], st)
|
adamc@39
|
316 end
|
adamc@39
|
317
|
adamc@39
|
318 | L.DSgn _ => ([], st)
|
adamc@16
|
319
|
adamc@46
|
320 | L.DStr (x, n, _, (L.StrFun (_, na, _, _, str), _)) =>
|
adamc@46
|
321 ([], St.bindFunctor st x n na str)
|
adamc@46
|
322
|
adamc@39
|
323 | L.DStr (x, n, _, str) =>
|
adamc@39
|
324 let
|
adamc@39
|
325 val (ds, {inner, outer}) = corifyStr (str, st)
|
adamc@39
|
326 val st = St.bindStr outer x n inner
|
adamc@39
|
327 in
|
adamc@39
|
328 (ds, st)
|
adamc@39
|
329 end
|
adamc@16
|
330
|
adamc@49
|
331 | L.DFfiStr (m, n, (sgn, _)) =>
|
adamc@49
|
332 (case sgn of
|
adamc@49
|
333 L.SgnConst sgis =>
|
adamc@49
|
334 let
|
adamc@49
|
335 val (ds, cmap, st) =
|
adamc@49
|
336 foldl (fn ((sgi, _), (ds, cmap, st)) =>
|
adamc@49
|
337 case sgi of
|
adamc@49
|
338 L.SgiConAbs (x, n, k) =>
|
adamc@49
|
339 let
|
adamc@49
|
340 val (st, n') = St.bindCore st x n
|
adamc@49
|
341 in
|
adamc@49
|
342 ((L'.DCon (x, n', corifyKind k, (L'.CFfi (m, x), loc)), loc) :: ds,
|
adamc@49
|
343 cmap,
|
adamc@49
|
344 st)
|
adamc@49
|
345 end
|
adamc@49
|
346 | L.SgiCon (x, n, k, _) =>
|
adamc@49
|
347 let
|
adamc@49
|
348 val (st, n') = St.bindCore st x n
|
adamc@49
|
349 in
|
adamc@49
|
350 ((L'.DCon (x, n', corifyKind k, (L'.CFfi (m, x), loc)), loc) :: ds,
|
adamc@49
|
351 cmap,
|
adamc@49
|
352 st)
|
adamc@49
|
353 end
|
adamc@49
|
354
|
adamc@49
|
355 | L.SgiVal (x, _, c) =>
|
adamc@49
|
356 (ds,
|
adamc@49
|
357 SM.insert (cmap, x, corifyCon st c),
|
adamc@49
|
358 st)
|
adamc@49
|
359 | _ => (ds, cmap, st)) ([], SM.empty, st) sgis
|
adamc@49
|
360
|
adamc@49
|
361 val st = St.bindStr st m n (St.ffi m cmap)
|
adamc@49
|
362 in
|
adamc@49
|
363 (rev ds, st)
|
adamc@49
|
364 end
|
adamc@49
|
365 | _ => raise Fail "Non-const signature for FFI structure")
|
adamc@48
|
366
|
adamc@48
|
367
|
adamc@39
|
368 and corifyStr ((str, _), st) =
|
adamc@39
|
369 case str of
|
adamc@39
|
370 L.StrConst ds =>
|
adamc@39
|
371 let
|
adamc@39
|
372 val st = St.enter st
|
adamc@39
|
373 val (ds, st) = ListUtil.foldlMapConcat corifyDecl st ds
|
adamc@39
|
374 in
|
adamc@39
|
375 (ds, St.leave st)
|
adamc@39
|
376 end
|
adamc@39
|
377 | L.StrVar n => ([], {inner = St.lookupStrById st n, outer = st})
|
adamc@39
|
378 | L.StrProj (str, x) =>
|
adamc@39
|
379 let
|
adamc@39
|
380 val (ds, {inner, outer}) = corifyStr (str, st)
|
adamc@39
|
381 in
|
adamc@39
|
382 (ds, {inner = St.lookupStrByName (x, inner), outer = outer})
|
adamc@39
|
383 end
|
adamc@46
|
384 | L.StrFun _ => raise Fail "Corify of nested functor definition"
|
adamc@46
|
385 | L.StrApp (str1, str2) =>
|
adamc@46
|
386 let
|
adamc@46
|
387 fun unwind' (str, _) =
|
adamc@46
|
388 case str of
|
adamc@46
|
389 L.StrVar n => St.lookupStrById st n
|
adamc@46
|
390 | L.StrProj (str, x) => St.lookupStrByName (x, unwind' str)
|
adamc@46
|
391 | _ => raise Fail "Corify of fancy functor application [1]"
|
adamc@46
|
392
|
adamc@46
|
393 fun unwind (str, _) =
|
adamc@46
|
394 case str of
|
adamc@46
|
395 L.StrVar n => St.lookupFunctorById st n
|
adamc@46
|
396 | L.StrProj (str, x) => St.lookupFunctorByName (x, unwind' str)
|
adamc@46
|
397 | _ => raise Fail "Corify of fancy functor application [2]"
|
adamc@46
|
398
|
adamc@46
|
399 val (na, body) = unwind str1
|
adamc@46
|
400
|
adamc@46
|
401 val (ds1, {inner, outer}) = corifyStr (str2, st)
|
adamc@46
|
402 val (ds2, sts) = corifyStr (body, St.bindStr outer "ARG" na inner)
|
adamc@46
|
403 in
|
adamc@46
|
404 (ds1 @ ds2, sts)
|
adamc@46
|
405 end
|
adamc@31
|
406
|
adamc@39
|
407 fun maxName ds = foldl (fn ((d, _), n) =>
|
adamc@39
|
408 case d of
|
adamc@39
|
409 L.DCon (_, n', _, _) => Int.max (n, n')
|
adamc@39
|
410 | L.DVal (_, n', _ , _) => Int.max (n, n')
|
adamc@39
|
411 | L.DSgn (_, n', _) => Int.max (n, n')
|
adamc@48
|
412 | L.DStr (_, n', _, str) => Int.max (n, Int.max (n', maxNameStr str))
|
adamc@48
|
413 | L.DFfiStr (_, n', _) => Int.max (n, n'))
|
adamc@39
|
414 0 ds
|
adamc@39
|
415
|
adamc@39
|
416 and maxNameStr (str, _) =
|
adamc@39
|
417 case str of
|
adamc@39
|
418 L.StrConst ds => maxName ds
|
adamc@39
|
419 | L.StrVar n => n
|
adamc@39
|
420 | L.StrProj (str, _) => maxNameStr str
|
adamc@45
|
421 | L.StrFun (_, _, _, _, str) => maxNameStr str
|
adamc@45
|
422 | L.StrApp (str1, str2) => Int.max (maxNameStr str1, maxNameStr str2)
|
adamc@39
|
423
|
adamc@39
|
424 fun corify ds =
|
adamc@39
|
425 let
|
adamc@39
|
426 val () = reset (maxName ds + 1)
|
adamc@39
|
427 val (ds, _) = ListUtil.foldlMapConcat corifyDecl St.empty ds
|
adamc@39
|
428 in
|
adamc@39
|
429 ds
|
adamc@39
|
430 end
|
adamc@16
|
431
|
adamc@16
|
432 end
|