ziv@2250
|
1 structure Sqlcache :> SQLCACHE = struct
|
ziv@2209
|
2
|
ziv@2209
|
3 open Mono
|
ziv@2209
|
4
|
ziv@2209
|
5 structure IS = IntBinarySet
|
ziv@2209
|
6 structure IM = IntBinaryMap
|
ziv@2213
|
7 structure SK = struct type ord_key = string val compare = String.compare end
|
ziv@2213
|
8 structure SS = BinarySetFn(SK)
|
ziv@2213
|
9 structure SM = BinaryMapFn(SK)
|
ziv@2213
|
10 structure SIMM = MultimapFn(structure KeyMap = SM structure ValSet = IS)
|
ziv@2209
|
11
|
ziv@2250
|
12 fun iterate f n x = if n < 0
|
ziv@2250
|
13 then raise Fail "Can't iterate function negative number of times."
|
ziv@2250
|
14 else if n = 0
|
ziv@2250
|
15 then x
|
ziv@2250
|
16 else iterate f (n-1) (f x)
|
ziv@2250
|
17
|
ziv@2268
|
18 (* Filled in by [addFlushing]. *)
|
ziv@2268
|
19 val ffiInfoRef : {index : int, params : int} list ref = ref []
|
ziv@2209
|
20
|
ziv@2268
|
21 fun resetFfiInfo () = ffiInfoRef := []
|
ziv@2227
|
22
|
ziv@2268
|
23 fun getFfiInfo () = !ffiInfoRef
|
ziv@2213
|
24
|
ziv@2215
|
25 (* Some FFIs have writing as their only effect, which the caching records. *)
|
ziv@2215
|
26 val ffiEffectful =
|
ziv@2223
|
27 (* ASK: how can this be less hard-coded? *)
|
ziv@2215
|
28 let
|
ziv@2258
|
29 val okayWrites = SS.fromList ["htmlifyInt_w",
|
ziv@2258
|
30 "htmlifyFloat_w",
|
ziv@2258
|
31 "htmlifyString_w",
|
ziv@2258
|
32 "htmlifyBool_w",
|
ziv@2258
|
33 "htmlifyTime_w",
|
ziv@2258
|
34 "attrifyInt_w",
|
ziv@2258
|
35 "attrifyFloat_w",
|
ziv@2258
|
36 "attrifyString_w",
|
ziv@2258
|
37 "attrifyChar_w",
|
ziv@2258
|
38 "urlifyInt_w",
|
ziv@2258
|
39 "urlifyFloat_w",
|
ziv@2258
|
40 "urlifyString_w",
|
ziv@2258
|
41 "urlifyBool_w",
|
ziv@2258
|
42 "urlifyChannel_w"]
|
ziv@2215
|
43 in
|
ziv@2265
|
44 (* ASK: is it okay to hardcode Sqlcache functions as effectful? *)
|
ziv@2215
|
45 fn (m, f) => Settings.isEffectful (m, f)
|
ziv@2258
|
46 andalso not (m = "Basis" andalso SS.member (okayWrites, f))
|
ziv@2215
|
47 end
|
ziv@2215
|
48
|
ziv@2234
|
49 val cache = ref LruCache.cache
|
ziv@2233
|
50 fun setCache c = cache := c
|
ziv@2233
|
51 fun getCache () = !cache
|
ziv@2233
|
52
|
ziv@2248
|
53 (* Used to have type context for local variables in MonoUtil functions. *)
|
ziv@2248
|
54 val doBind =
|
ziv@2262
|
55 fn (env, MonoUtil.Exp.RelE (x, t)) => MonoEnv.pushERel env x t NONE
|
ziv@2262
|
56 | (env, MonoUtil.Exp.NamedE (x, n, t, eo, s)) => MonoEnv.pushENamed env x n t eo s
|
ziv@2262
|
57 | (env, MonoUtil.Exp.Datatype (x, n, cs)) => MonoEnv.pushDatatype env x n cs
|
ziv@2215
|
58
|
ziv@2271
|
59 val dummyLoc = ErrorMsg.dummySpan
|
ziv@2271
|
60
|
ziv@2271
|
61
|
ziv@2271
|
62 (*********************)
|
ziv@2271
|
63 (* General Utilities *)
|
ziv@2271
|
64 (*********************)
|
ziv@2266
|
65
|
ziv@2266
|
66 (* From the MLton wiki. *)
|
ziv@2266
|
67 infixr 3 /> fun f /> y = fn x => f (x, y) (* Right section *)
|
ziv@2266
|
68 infixr 3 </ fun x </ f = f x (* Right application *)
|
ziv@2266
|
69
|
ziv@2271
|
70 fun mapFst f (x, y) = (f x, y)
|
ziv@2271
|
71
|
ziv@2266
|
72 (* Option monad. *)
|
ziv@2266
|
73 fun obind (x, f) = Option.mapPartial f x
|
ziv@2266
|
74 fun oguard (b, x) = if b then x else NONE
|
ziv@2271
|
75 fun omap f = fn SOME x => SOME (f x) | _ => NONE
|
ziv@2271
|
76 fun omap2 f = fn (SOME x, SOME y) => SOME (f (x,y)) | _ => NONE
|
ziv@2271
|
77 fun osequence ys = List.foldr (omap2 op::) (SOME []) ys
|
ziv@2248
|
78
|
ziv@2271
|
79 fun indexOf test =
|
ziv@2271
|
80 let
|
ziv@2271
|
81 fun f n =
|
ziv@2271
|
82 fn [] => NONE
|
ziv@2271
|
83 | (x::xs) => if test x then SOME n else f (n+1) xs
|
ziv@2271
|
84 in
|
ziv@2271
|
85 f 0
|
ziv@2271
|
86 end
|
ziv@2268
|
87
|
ziv@2248
|
88 (*******************)
|
ziv@2248
|
89 (* Effect Analysis *)
|
ziv@2248
|
90 (*******************)
|
ziv@2215
|
91
|
ziv@2216
|
92 (* Makes an exception for [EWrite] (which is recorded when caching). *)
|
ziv@2248
|
93 fun effectful (effs : IS.set) =
|
ziv@2215
|
94 let
|
ziv@2248
|
95 val isFunction =
|
ziv@2248
|
96 fn (TFun _, _) => true
|
ziv@2248
|
97 | _ => false
|
ziv@2250
|
98 fun doExp (env, e) =
|
ziv@2248
|
99 case e of
|
ziv@2248
|
100 EPrim _ => false
|
ziv@2248
|
101 (* For now: variables of function type might be effectful, but
|
ziv@2248
|
102 others are fully evaluated and are therefore not effectful. *)
|
ziv@2250
|
103 | ERel n => isFunction (#2 (MonoEnv.lookupERel env n))
|
ziv@2248
|
104 | ENamed n => IS.member (effs, n)
|
ziv@2248
|
105 | EFfi (m, f) => ffiEffectful (m, f)
|
ziv@2248
|
106 | EFfiApp (m, f, _) => ffiEffectful (m, f)
|
ziv@2248
|
107 (* These aren't effectful unless a subexpression is. *)
|
ziv@2248
|
108 | ECon _ => false
|
ziv@2248
|
109 | ENone _ => false
|
ziv@2248
|
110 | ESome _ => false
|
ziv@2248
|
111 | EApp _ => false
|
ziv@2248
|
112 | EAbs _ => false
|
ziv@2248
|
113 | EUnop _ => false
|
ziv@2248
|
114 | EBinop _ => false
|
ziv@2248
|
115 | ERecord _ => false
|
ziv@2248
|
116 | EField _ => false
|
ziv@2248
|
117 | ECase _ => false
|
ziv@2248
|
118 | EStrcat _ => false
|
ziv@2248
|
119 (* EWrite is a special exception because we record writes when caching. *)
|
ziv@2248
|
120 | EWrite _ => false
|
ziv@2248
|
121 | ESeq _ => false
|
ziv@2248
|
122 | ELet _ => false
|
ziv@2250
|
123 | EUnurlify _ => false
|
ziv@2248
|
124 (* ASK: what should we do about closures? *)
|
ziv@2248
|
125 (* Everything else is some sort of effect. We could flip this and
|
ziv@2248
|
126 explicitly list bits of Mono that are effectful, but this is
|
ziv@2248
|
127 conservatively robust to future changes (however unlikely). *)
|
ziv@2248
|
128 | _ => true
|
ziv@2215
|
129 in
|
ziv@2248
|
130 MonoUtil.Exp.existsB {typ = fn _ => false, exp = doExp, bind = doBind}
|
ziv@2215
|
131 end
|
ziv@2215
|
132
|
ziv@2215
|
133 (* TODO: test this. *)
|
ziv@2252
|
134 fun effectfulDecls (decls, _) =
|
ziv@2215
|
135 let
|
ziv@2248
|
136 fun doVal ((_, name, _, e, _), effs) =
|
ziv@2250
|
137 if effectful effs MonoEnv.empty e
|
ziv@2248
|
138 then IS.add (effs, name)
|
ziv@2248
|
139 else effs
|
ziv@2215
|
140 val doDecl =
|
ziv@2248
|
141 fn ((DVal v, _), effs) => doVal (v, effs)
|
ziv@2248
|
142 (* Repeat the list of declarations a number of times equal to its size,
|
ziv@2248
|
143 making sure effectfulness propagates everywhere it should. This is
|
ziv@2248
|
144 analagous to the Bellman-Ford algorithm. *)
|
ziv@2248
|
145 | ((DValRec vs, _), effs) =>
|
ziv@2248
|
146 List.foldl doVal effs (List.concat (List.map (fn _ => vs) vs))
|
ziv@2215
|
147 (* ASK: any other cases? *)
|
ziv@2248
|
148 | (_, effs) => effs
|
ziv@2215
|
149 in
|
ziv@2248
|
150 List.foldl doDecl IS.empty decls
|
ziv@2215
|
151 end
|
ziv@2215
|
152
|
ziv@2215
|
153
|
ziv@2248
|
154 (*********************************)
|
ziv@2248
|
155 (* Boolean Formula Normalization *)
|
ziv@2248
|
156 (*********************************)
|
ziv@2216
|
157
|
ziv@2234
|
158 datatype junctionType = Conj | Disj
|
ziv@2216
|
159
|
ziv@2216
|
160 datatype 'atom formula =
|
ziv@2216
|
161 Atom of 'atom
|
ziv@2216
|
162 | Negate of 'atom formula
|
ziv@2234
|
163 | Combo of junctionType * 'atom formula list
|
ziv@2216
|
164
|
ziv@2243
|
165 (* Guaranteed to have all negation pushed to the atoms. *)
|
ziv@2243
|
166 datatype 'atom formula' =
|
ziv@2243
|
167 Atom' of 'atom
|
ziv@2243
|
168 | Combo' of junctionType * 'atom formula' list
|
ziv@2243
|
169
|
ziv@2234
|
170 val flipJt = fn Conj => Disj | Disj => Conj
|
ziv@2216
|
171
|
ziv@2236
|
172 fun concatMap f xs = List.concat (map f xs)
|
ziv@2216
|
173
|
ziv@2216
|
174 val rec cartesianProduct : 'a list list -> 'a list list =
|
ziv@2216
|
175 fn [] => [[]]
|
ziv@2236
|
176 | (xs :: xss) => concatMap (fn ys => concatMap (fn x => [x :: ys]) xs)
|
ziv@2236
|
177 (cartesianProduct xss)
|
ziv@2216
|
178
|
ziv@2218
|
179 (* Pushes all negation to the atoms.*)
|
ziv@2244
|
180 fun pushNegate (normalizeAtom : bool * 'atom -> 'atom) (negating : bool) =
|
ziv@2244
|
181 fn Atom x => Atom' (normalizeAtom (negating, x))
|
ziv@2244
|
182 | Negate f => pushNegate normalizeAtom (not negating) f
|
ziv@2244
|
183 | Combo (j, fs) => Combo' (if negating then flipJt j else j,
|
ziv@2244
|
184 map (pushNegate normalizeAtom negating) fs)
|
ziv@2218
|
185
|
ziv@2218
|
186 val rec flatten =
|
ziv@2243
|
187 fn Combo' (_, [f]) => flatten f
|
ziv@2243
|
188 | Combo' (j, fs) =>
|
ziv@2243
|
189 Combo' (j, List.foldr (fn (f, acc) =>
|
ziv@2243
|
190 case f of
|
ziv@2243
|
191 Combo' (j', fs') =>
|
ziv@2243
|
192 if j = j' orelse length fs' = 1
|
ziv@2243
|
193 then fs' @ acc
|
ziv@2243
|
194 else f :: acc
|
ziv@2243
|
195 | _ => f :: acc)
|
ziv@2243
|
196 []
|
ziv@2243
|
197 (map flatten fs))
|
ziv@2218
|
198 | f => f
|
ziv@2218
|
199
|
ziv@2243
|
200 (* [simplify] operates on the desired normal form. E.g., if [junc] is [Disj],
|
ziv@2243
|
201 consider the list of lists to be a disjunction of conjunctions. *)
|
ziv@2237
|
202 fun normalize' (simplify : 'a list list -> 'a list list)
|
ziv@2235
|
203 (junc : junctionType) =
|
ziv@2216
|
204 let
|
ziv@2235
|
205 fun norm junc =
|
ziv@2237
|
206 simplify
|
ziv@2243
|
207 o (fn Atom' x => [[x]]
|
ziv@2243
|
208 | Combo' (j, fs) =>
|
ziv@2235
|
209 let
|
ziv@2236
|
210 val fss = map (norm junc) fs
|
ziv@2235
|
211 in
|
ziv@2236
|
212 if j = junc
|
ziv@2236
|
213 then List.concat fss
|
ziv@2236
|
214 else map List.concat (cartesianProduct fss)
|
ziv@2235
|
215 end)
|
ziv@2216
|
216 in
|
ziv@2235
|
217 norm junc
|
ziv@2216
|
218 end
|
ziv@2216
|
219
|
ziv@2244
|
220 fun normalize simplify normalizeAtom junc =
|
ziv@2243
|
221 normalize' simplify junc
|
ziv@2235
|
222 o flatten
|
ziv@2244
|
223 o pushNegate normalizeAtom false
|
ziv@2216
|
224
|
ziv@2221
|
225 fun mapFormula mf =
|
ziv@2221
|
226 fn Atom x => Atom (mf x)
|
ziv@2221
|
227 | Negate f => Negate (mapFormula mf f)
|
ziv@2235
|
228 | Combo (j, fs) => Combo (j, map (mapFormula mf) fs)
|
ziv@2216
|
229
|
ziv@2230
|
230
|
ziv@2248
|
231 (****************)
|
ziv@2248
|
232 (* SQL Analysis *)
|
ziv@2248
|
233 (****************)
|
ziv@2213
|
234
|
ziv@2240
|
235 structure CmpKey = struct
|
ziv@2235
|
236
|
ziv@2235
|
237 type ord_key = Sql.cmp
|
ziv@2235
|
238
|
ziv@2235
|
239 val compare =
|
ziv@2235
|
240 fn (Sql.Eq, Sql.Eq) => EQUAL
|
ziv@2235
|
241 | (Sql.Eq, _) => LESS
|
ziv@2235
|
242 | (_, Sql.Eq) => GREATER
|
ziv@2235
|
243 | (Sql.Ne, Sql.Ne) => EQUAL
|
ziv@2235
|
244 | (Sql.Ne, _) => LESS
|
ziv@2235
|
245 | (_, Sql.Ne) => GREATER
|
ziv@2235
|
246 | (Sql.Lt, Sql.Lt) => EQUAL
|
ziv@2235
|
247 | (Sql.Lt, _) => LESS
|
ziv@2235
|
248 | (_, Sql.Lt) => GREATER
|
ziv@2235
|
249 | (Sql.Le, Sql.Le) => EQUAL
|
ziv@2235
|
250 | (Sql.Le, _) => LESS
|
ziv@2235
|
251 | (_, Sql.Le) => GREATER
|
ziv@2235
|
252 | (Sql.Gt, Sql.Gt) => EQUAL
|
ziv@2235
|
253 | (Sql.Gt, _) => LESS
|
ziv@2235
|
254 | (_, Sql.Gt) => GREATER
|
ziv@2235
|
255 | (Sql.Ge, Sql.Ge) => EQUAL
|
ziv@2235
|
256
|
ziv@2235
|
257 end
|
ziv@2235
|
258
|
ziv@2216
|
259 val rec chooseTwos : 'a list -> ('a * 'a) list =
|
ziv@2216
|
260 fn [] => []
|
ziv@2216
|
261 | x :: ys => map (fn y => (x, y)) ys @ chooseTwos ys
|
ziv@2213
|
262
|
ziv@2237
|
263 fun removeRedundant madeRedundantBy zs =
|
ziv@2237
|
264 let
|
ziv@2237
|
265 fun removeRedundant' (xs, ys) =
|
ziv@2237
|
266 case xs of
|
ziv@2237
|
267 [] => ys
|
ziv@2237
|
268 | x :: xs' =>
|
ziv@2237
|
269 removeRedundant' (xs',
|
ziv@2237
|
270 if List.exists (fn y => madeRedundantBy (x, y)) (xs' @ ys)
|
ziv@2237
|
271 then ys
|
ziv@2237
|
272 else x :: ys)
|
ziv@2237
|
273 in
|
ziv@2237
|
274 removeRedundant' (zs, [])
|
ziv@2237
|
275 end
|
ziv@2237
|
276
|
ziv@2216
|
277 datatype atomExp =
|
ziv@2216
|
278 QueryArg of int
|
ziv@2216
|
279 | DmlRel of int
|
ziv@2216
|
280 | Prim of Prim.t
|
ziv@2216
|
281 | Field of string * string
|
ziv@2216
|
282
|
ziv@2216
|
283 structure AtomExpKey : ORD_KEY = struct
|
ziv@2216
|
284
|
ziv@2234
|
285 type ord_key = atomExp
|
ziv@2216
|
286
|
ziv@2234
|
287 val compare =
|
ziv@2234
|
288 fn (QueryArg n1, QueryArg n2) => Int.compare (n1, n2)
|
ziv@2234
|
289 | (QueryArg _, _) => LESS
|
ziv@2234
|
290 | (_, QueryArg _) => GREATER
|
ziv@2234
|
291 | (DmlRel n1, DmlRel n2) => Int.compare (n1, n2)
|
ziv@2234
|
292 | (DmlRel _, _) => LESS
|
ziv@2234
|
293 | (_, DmlRel _) => GREATER
|
ziv@2234
|
294 | (Prim p1, Prim p2) => Prim.compare (p1, p2)
|
ziv@2234
|
295 | (Prim _, _) => LESS
|
ziv@2234
|
296 | (_, Prim _) => GREATER
|
ziv@2234
|
297 | (Field (t1, f1), Field (t2, f2)) =>
|
ziv@2234
|
298 case String.compare (t1, t2) of
|
ziv@2234
|
299 EQUAL => String.compare (f1, f2)
|
ziv@2234
|
300 | ord => ord
|
ziv@2216
|
301
|
ziv@2216
|
302 end
|
ziv@2216
|
303
|
ziv@2244
|
304 structure AtomOptionKey = OptionKeyFn(AtomExpKey)
|
ziv@2244
|
305
|
ziv@2271
|
306 val rec tablesOfQuery =
|
ziv@2271
|
307 fn Sql.Query1 {From = tablePairs, ...} => SS.fromList (map #1 tablePairs)
|
ziv@2271
|
308 | Sql.Union (q1, q2) => SS.union (tablesOfQuery q1, tablesOfQuery q2)
|
ziv@2271
|
309
|
ziv@2271
|
310 val tableOfDml =
|
ziv@2271
|
311 fn Sql.Insert (tab, _) => tab
|
ziv@2271
|
312 | Sql.Delete (tab, _) => tab
|
ziv@2271
|
313 | Sql.Update (tab, _, _) => tab
|
ziv@2271
|
314
|
ziv@2271
|
315 val freeVars =
|
ziv@2271
|
316 MonoUtil.Exp.foldB
|
ziv@2271
|
317 {typ = #2,
|
ziv@2271
|
318 exp = fn (bound, ERel n, vars) => if n < bound
|
ziv@2271
|
319 then vars
|
ziv@2271
|
320 else IS.add (vars, n - bound)
|
ziv@2271
|
321 | (_, _, vars) => vars,
|
ziv@2271
|
322 bind = fn (bound, MonoUtil.Exp.RelE _) => bound + 1 | (bound, _) => bound}
|
ziv@2271
|
323 0
|
ziv@2271
|
324 IS.empty
|
ziv@2271
|
325
|
ziv@2271
|
326 datatype unbind = Known of exp | Unknowns of int
|
ziv@2271
|
327
|
ziv@2271
|
328 structure InvalInfo :> sig
|
ziv@2271
|
329 type t
|
ziv@2271
|
330 type state = {tableToIndices : SIMM.multimap,
|
ziv@2271
|
331 indexToInvalInfo : (t * int) IntBinaryMap.map,
|
ziv@2271
|
332 ffiInfo : {index : int, params : int} list,
|
ziv@2271
|
333 index : int}
|
ziv@2271
|
334 val empty : t
|
ziv@2271
|
335 val singleton : Sql.query -> t
|
ziv@2271
|
336 val query : t -> Sql.query
|
ziv@2271
|
337 val orderArgs : t * IS.set -> int list
|
ziv@2271
|
338 val unbind : t * unbind -> t option
|
ziv@2271
|
339 val union : t * t -> t
|
ziv@2271
|
340 val updateState : t * int * state -> state
|
ziv@2271
|
341 end = struct
|
ziv@2271
|
342
|
ziv@2271
|
343 type t = Sql.query list
|
ziv@2271
|
344
|
ziv@2271
|
345 type state = {tableToIndices : SIMM.multimap,
|
ziv@2271
|
346 indexToInvalInfo : (t * int) IntBinaryMap.map,
|
ziv@2271
|
347 ffiInfo : {index : int, params : int} list,
|
ziv@2271
|
348 index : int}
|
ziv@2271
|
349
|
ziv@2271
|
350 val empty = []
|
ziv@2271
|
351
|
ziv@2271
|
352 fun singleton q = [q]
|
ziv@2271
|
353
|
ziv@2271
|
354 val union = op@
|
ziv@2271
|
355
|
ziv@2271
|
356 (* Need lift', etc. because we don't have rank-2 polymorphism. This should
|
ziv@2271
|
357 probably use a functor, but this works for now. *)
|
ziv@2271
|
358 fun traverseSqexp (pure, _, lift, _, lift'', lift2, _) f =
|
ziv@2271
|
359 let
|
ziv@2271
|
360 val rec tr =
|
ziv@2271
|
361 fn Sql.SqNot se => lift Sql.SqNot (tr se)
|
ziv@2271
|
362 | Sql.Binop (r, se1, se2) =>
|
ziv@2271
|
363 lift2 (fn (trse1, trse2) => Sql.Binop (r, trse1, trse2)) (tr se1, tr se2)
|
ziv@2271
|
364 | Sql.SqKnown se => lift Sql.SqKnown (tr se)
|
ziv@2271
|
365 | Sql.Inj (e', loc) => lift'' (fn fe' => Sql.Inj (fe', loc)) (f e')
|
ziv@2271
|
366 | Sql.SqFunc (s, se) => lift (fn trse => Sql.SqFunc (s, trse)) (tr se)
|
ziv@2271
|
367 | se => pure se
|
ziv@2271
|
368 in
|
ziv@2271
|
369 tr
|
ziv@2271
|
370 end
|
ziv@2271
|
371
|
ziv@2271
|
372 fun traverseQuery (ops as (_, pure', _, lift', _, _, lift2')) f =
|
ziv@2271
|
373 let
|
ziv@2271
|
374 val rec mp =
|
ziv@2271
|
375 fn Sql.Query1 q =>
|
ziv@2271
|
376 (case #Where q of
|
ziv@2271
|
377 NONE => pure' (Sql.Query1 q)
|
ziv@2271
|
378 | SOME se =>
|
ziv@2271
|
379 lift' (fn mpse => Sql.Query1 {Select = #Select q,
|
ziv@2271
|
380 From = #From q,
|
ziv@2271
|
381 Where = SOME mpse})
|
ziv@2271
|
382 (traverseSqexp ops f se))
|
ziv@2271
|
383 | Sql.Union (q1, q2) => lift2' Sql.Union (mp q1, mp q2)
|
ziv@2271
|
384 in
|
ziv@2271
|
385 mp
|
ziv@2271
|
386 end
|
ziv@2271
|
387
|
ziv@2271
|
388 fun foldMapQuery plus zero = traverseQuery (fn _ => zero,
|
ziv@2271
|
389 fn _ => zero,
|
ziv@2271
|
390 fn _ => fn x => x,
|
ziv@2271
|
391 fn _ => fn x => x,
|
ziv@2271
|
392 fn _ => fn x => x,
|
ziv@2271
|
393 fn _ => plus,
|
ziv@2271
|
394 fn _ => plus)
|
ziv@2271
|
395
|
ziv@2271
|
396 val omapQuery = traverseQuery (SOME, SOME, omap, omap, omap, omap2, omap2)
|
ziv@2271
|
397
|
ziv@2271
|
398 val varsOfQuery = foldMapQuery IS.union
|
ziv@2271
|
399 IS.empty
|
ziv@2271
|
400 (fn e' => freeVars (e', dummyLoc))
|
ziv@2271
|
401
|
ziv@2271
|
402 val varsOfList =
|
ziv@2271
|
403 fn [] => IS.empty
|
ziv@2271
|
404 | (q::qs) => varsOfQuery (List.foldl Sql.Union q qs)
|
ziv@2271
|
405
|
ziv@2271
|
406 fun orderArgs (qs, vars) =
|
ziv@2271
|
407 let
|
ziv@2271
|
408 val invalVars = varsOfList qs
|
ziv@2271
|
409 in
|
ziv@2271
|
410 (* Put arguments we might invalidate by first. *)
|
ziv@2271
|
411 IS.listItems invalVars @ IS.listItems (IS.difference (vars, invalVars))
|
ziv@2271
|
412 end
|
ziv@2271
|
413
|
ziv@2271
|
414 (* As a kludge, we rename the variables in the query to correspond to the
|
ziv@2271
|
415 argument of the cache they're part of. *)
|
ziv@2271
|
416 val query =
|
ziv@2271
|
417 fn (q::qs) =>
|
ziv@2271
|
418 let
|
ziv@2271
|
419 val q = List.foldl Sql.Union q qs
|
ziv@2271
|
420 val ns = IS.listItems (varsOfQuery q)
|
ziv@2271
|
421 val rename =
|
ziv@2271
|
422 fn ERel n => omap ERel (indexOf (fn n' => n' = n) ns)
|
ziv@2271
|
423 | _ => raise Match
|
ziv@2271
|
424 in
|
ziv@2271
|
425 case omapQuery rename q of
|
ziv@2271
|
426 SOME q => q
|
ziv@2271
|
427 (* We should never get NONE because indexOf should never fail. *)
|
ziv@2271
|
428 | NONE => raise Match
|
ziv@2271
|
429 end
|
ziv@2271
|
430 (* We should never reach this case because [updateState] won't put
|
ziv@2271
|
431 anything in the state if there are no queries. *)
|
ziv@2271
|
432 | [] => raise Match
|
ziv@2271
|
433
|
ziv@2271
|
434 fun unbind1 ub =
|
ziv@2271
|
435 case ub of
|
ziv@2271
|
436 Known (e', loc) =>
|
ziv@2271
|
437 let
|
ziv@2271
|
438 val replaceRel0 = case e' of
|
ziv@2271
|
439 ERel m => SOME (ERel m)
|
ziv@2271
|
440 | _ => NONE
|
ziv@2271
|
441 in
|
ziv@2271
|
442 omapQuery (fn ERel 0 => replaceRel0
|
ziv@2271
|
443 | ERel n => SOME (ERel (n-1))
|
ziv@2271
|
444 | _ => raise Match)
|
ziv@2271
|
445 end
|
ziv@2271
|
446 | Unknowns k =>
|
ziv@2271
|
447 omapQuery (fn ERel n => if n >= k then NONE else SOME (ERel (n-k))
|
ziv@2271
|
448 | _ => raise Match)
|
ziv@2271
|
449
|
ziv@2271
|
450 fun unbind (qs, ub) =
|
ziv@2271
|
451 case ub of
|
ziv@2271
|
452 (* Shortcut if nothing's changing. *)
|
ziv@2271
|
453 Unknowns 0 => SOME qs
|
ziv@2271
|
454 | _ => osequence (map (unbind1 ub) qs)
|
ziv@2271
|
455
|
ziv@2271
|
456 fun updateState ((qs, numArgs, state as {index, ...}) : t * int * state) =
|
ziv@2271
|
457 {tableToIndices = List.foldr (fn (q, acc) =>
|
ziv@2271
|
458 SS.foldl (fn (tab, acc) =>
|
ziv@2271
|
459 SIMM.insert (acc, tab, index))
|
ziv@2271
|
460 acc
|
ziv@2271
|
461 (tablesOfQuery q))
|
ziv@2271
|
462 (#tableToIndices state)
|
ziv@2271
|
463 qs,
|
ziv@2271
|
464 indexToInvalInfo = IM.insert (#indexToInvalInfo state, index, (qs, numArgs)),
|
ziv@2271
|
465 ffiInfo = {index = index, params = numArgs} :: #ffiInfo state,
|
ziv@2271
|
466 index = index + 1}
|
ziv@2271
|
467
|
ziv@2271
|
468 end
|
ziv@2271
|
469
|
ziv@2216
|
470 structure UF = UnionFindFn(AtomExpKey)
|
ziv@2234
|
471
|
ziv@2235
|
472 structure ConflictMaps = struct
|
ziv@2235
|
473
|
ziv@2235
|
474 structure TK = TripleKeyFn(structure I = CmpKey
|
ziv@2244
|
475 structure J = AtomOptionKey
|
ziv@2244
|
476 structure K = AtomOptionKey)
|
ziv@2244
|
477 structure TS : ORD_SET = BinarySetFn(TK)
|
ziv@2235
|
478
|
ziv@2235
|
479 val toKnownEquality =
|
ziv@2235
|
480 (* [NONE] here means unkown. Anything that isn't a comparison between two
|
ziv@2235
|
481 knowns shouldn't be used, and simply dropping unused terms is okay in
|
ziv@2235
|
482 disjunctive normal form. *)
|
ziv@2235
|
483 fn (Sql.Eq, SOME e1, SOME e2) => SOME (e1, e2)
|
ziv@2235
|
484 | _ => NONE
|
ziv@2235
|
485
|
ziv@2235
|
486 val equivClasses : (Sql.cmp * atomExp option * atomExp option) list -> atomExp list list =
|
ziv@2235
|
487 UF.classes
|
ziv@2235
|
488 o List.foldl UF.union' UF.empty
|
ziv@2235
|
489 o List.mapPartial toKnownEquality
|
ziv@2235
|
490
|
ziv@2235
|
491 fun addToEqs (eqs, n, e) =
|
ziv@2235
|
492 case IM.find (eqs, n) of
|
ziv@2235
|
493 (* Comparing to a constant is probably better than comparing to a
|
ziv@2235
|
494 variable? Checking that existing constants match a new ones is
|
ziv@2235
|
495 handled by [accumulateEqs]. *)
|
ziv@2235
|
496 SOME (Prim _) => eqs
|
ziv@2235
|
497 | _ => IM.insert (eqs, n, e)
|
ziv@2235
|
498
|
ziv@2235
|
499 val accumulateEqs =
|
ziv@2235
|
500 (* [NONE] means we have a contradiction. *)
|
ziv@2235
|
501 fn (_, NONE) => NONE
|
ziv@2235
|
502 | ((Prim p1, Prim p2), eqso) =>
|
ziv@2235
|
503 (case Prim.compare (p1, p2) of
|
ziv@2235
|
504 EQUAL => eqso
|
ziv@2235
|
505 | _ => NONE)
|
ziv@2235
|
506 | ((QueryArg n, Prim p), SOME eqs) => SOME (addToEqs (eqs, n, Prim p))
|
ziv@2235
|
507 | ((QueryArg n, DmlRel r), SOME eqs) => SOME (addToEqs (eqs, n, DmlRel r))
|
ziv@2235
|
508 | ((Prim p, QueryArg n), SOME eqs) => SOME (addToEqs (eqs, n, Prim p))
|
ziv@2235
|
509 | ((DmlRel r, QueryArg n), SOME eqs) => SOME (addToEqs (eqs, n, DmlRel r))
|
ziv@2235
|
510 (* TODO: deal with equalities between [DmlRel]s and [Prim]s.
|
ziv@2235
|
511 This would involve guarding the invalidation with a check for the
|
ziv@2235
|
512 relevant comparisons. *)
|
ziv@2235
|
513 | (_, eqso) => eqso
|
ziv@2235
|
514
|
ziv@2235
|
515 val eqsOfClass : atomExp list -> atomExp IM.map option =
|
ziv@2235
|
516 List.foldl accumulateEqs (SOME IM.empty)
|
ziv@2235
|
517 o chooseTwos
|
ziv@2235
|
518
|
ziv@2235
|
519 fun toAtomExps rel (cmp, e1, e2) =
|
ziv@2235
|
520 let
|
ziv@2235
|
521 val qa =
|
ziv@2235
|
522 (* Here [NONE] means unkown. *)
|
ziv@2235
|
523 fn Sql.SqConst p => SOME (Prim p)
|
ziv@2235
|
524 | Sql.Field tf => SOME (Field tf)
|
ziv@2235
|
525 | Sql.Inj (EPrim p, _) => SOME (Prim p)
|
ziv@2235
|
526 | Sql.Inj (ERel n, _) => SOME (rel n)
|
ziv@2235
|
527 (* We can't deal with anything else, e.g., CURRENT_TIMESTAMP
|
ziv@2235
|
528 becomes Sql.Unmodeled, which becomes NONE here. *)
|
ziv@2235
|
529 | _ => NONE
|
ziv@2235
|
530 in
|
ziv@2235
|
531 (cmp, qa e1, qa e2)
|
ziv@2235
|
532 end
|
ziv@2235
|
533
|
ziv@2244
|
534 val negateCmp =
|
ziv@2244
|
535 fn Sql.Eq => Sql.Ne
|
ziv@2244
|
536 | Sql.Ne => Sql.Eq
|
ziv@2244
|
537 | Sql.Lt => Sql.Ge
|
ziv@2244
|
538 | Sql.Le => Sql.Gt
|
ziv@2244
|
539 | Sql.Gt => Sql.Le
|
ziv@2244
|
540 | Sql.Ge => Sql.Lt
|
ziv@2244
|
541
|
ziv@2244
|
542 fun normalizeAtom (negating, (cmp, e1, e2)) =
|
ziv@2244
|
543 (* Restricting to Le/Lt and sorting the expressions in Eq/Ne helps with
|
ziv@2244
|
544 simplification, where we put the triples in sets. *)
|
ziv@2244
|
545 case (if negating then negateCmp cmp else cmp) of
|
ziv@2244
|
546 Sql.Eq => (case AtomOptionKey.compare (e1, e2) of
|
ziv@2244
|
547 LESS => (Sql.Eq, e2, e1)
|
ziv@2244
|
548 | _ => (Sql.Eq, e1, e2))
|
ziv@2244
|
549 | Sql.Ne => (case AtomOptionKey.compare (e1, e2) of
|
ziv@2244
|
550 LESS => (Sql.Ne, e2, e1)
|
ziv@2244
|
551 | _ => (Sql.Ne, e1, e2))
|
ziv@2244
|
552 | Sql.Lt => (Sql.Lt, e1, e2)
|
ziv@2244
|
553 | Sql.Le => (Sql.Le, e1, e2)
|
ziv@2244
|
554 | Sql.Gt => (Sql.Lt, e2, e1)
|
ziv@2244
|
555 | Sql.Ge => (Sql.Le, e2, e1)
|
ziv@2235
|
556
|
ziv@2235
|
557 val markQuery : (Sql.cmp * Sql.sqexp * Sql.sqexp) formula ->
|
ziv@2235
|
558 (Sql.cmp * atomExp option * atomExp option) formula =
|
ziv@2235
|
559 mapFormula (toAtomExps QueryArg)
|
ziv@2235
|
560
|
ziv@2235
|
561 val markDml : (Sql.cmp * Sql.sqexp * Sql.sqexp) formula ->
|
ziv@2235
|
562 (Sql.cmp * atomExp option * atomExp option) formula =
|
ziv@2235
|
563 mapFormula (toAtomExps DmlRel)
|
ziv@2250
|
564
|
ziv@2235
|
565 (* No eqs should have key conflicts because no variable is in two
|
ziv@2235
|
566 equivalence classes, so the [#1] could be [#2]. *)
|
ziv@2235
|
567 val mergeEqs : (atomExp IntBinaryMap.map option list
|
ziv@2235
|
568 -> atomExp IntBinaryMap.map option) =
|
ziv@2271
|
569 List.foldr (omap2 (IM.unionWith #1)) (SOME IM.empty)
|
ziv@2235
|
570
|
ziv@2239
|
571 val simplify =
|
ziv@2239
|
572 map TS.listItems
|
ziv@2239
|
573 o removeRedundant (fn (x, y) => TS.isSubset (y, x))
|
ziv@2239
|
574 o map (fn xs => TS.addList (TS.empty, xs))
|
ziv@2239
|
575
|
ziv@2235
|
576 fun dnf (fQuery, fDml) =
|
ziv@2244
|
577 normalize simplify normalizeAtom Disj (Combo (Conj, [markQuery fQuery, markDml fDml]))
|
ziv@2235
|
578
|
ziv@2235
|
579 val conflictMaps = List.mapPartial (mergeEqs o map eqsOfClass o equivClasses) o dnf
|
ziv@2235
|
580
|
ziv@2235
|
581 end
|
ziv@2235
|
582
|
ziv@2235
|
583 val conflictMaps = ConflictMaps.conflictMaps
|
ziv@2213
|
584
|
ziv@2216
|
585 val rec sqexpToFormula =
|
ziv@2234
|
586 fn Sql.SqTrue => Combo (Conj, [])
|
ziv@2234
|
587 | Sql.SqFalse => Combo (Disj, [])
|
ziv@2216
|
588 | Sql.SqNot e => Negate (sqexpToFormula e)
|
ziv@2216
|
589 | Sql.Binop (Sql.RCmp c, e1, e2) => Atom (c, e1, e2)
|
ziv@2234
|
590 | Sql.Binop (Sql.RLop l, p1, p2) => Combo (case l of Sql.And => Conj | Sql.Or => Disj,
|
ziv@2216
|
591 [sqexpToFormula p1, sqexpToFormula p2])
|
ziv@2216
|
592 (* ASK: any other sqexps that can be props? *)
|
ziv@2216
|
593 | _ => raise Match
|
ziv@2213
|
594
|
ziv@2218
|
595 fun renameTables tablePairs =
|
ziv@2216
|
596 let
|
ziv@2216
|
597 fun renameString table =
|
ziv@2216
|
598 case List.find (fn (_, t) => table = t) tablePairs of
|
ziv@2216
|
599 NONE => table
|
ziv@2216
|
600 | SOME (realTable, _) => realTable
|
ziv@2216
|
601 val renameSqexp =
|
ziv@2216
|
602 fn Sql.Field (table, field) => Sql.Field (renameString table, field)
|
ziv@2216
|
603 | e => e
|
ziv@2218
|
604 fun renameAtom (cmp, e1, e2) = (cmp, renameSqexp e1, renameSqexp e2)
|
ziv@2216
|
605 in
|
ziv@2218
|
606 mapFormula renameAtom
|
ziv@2216
|
607 end
|
ziv@2218
|
608
|
ziv@2218
|
609 val rec queryToFormula =
|
ziv@2234
|
610 fn Sql.Query1 {Where = NONE, ...} => Combo (Conj, [])
|
ziv@2218
|
611 | Sql.Query1 {From = tablePairs, Where = SOME e, ...} =>
|
ziv@2218
|
612 renameTables tablePairs (sqexpToFormula e)
|
ziv@2234
|
613 | Sql.Union (q1, q2) => Combo (Disj, [queryToFormula q1, queryToFormula q2])
|
ziv@2216
|
614
|
ziv@2218
|
615 fun valsToFormula (table, vals) =
|
ziv@2234
|
616 Combo (Conj, map (fn (field, v) => Atom (Sql.Eq, Sql.Field (table, field), v)) vals)
|
ziv@2218
|
617
|
ziv@2216
|
618 val rec dmlToFormula =
|
ziv@2221
|
619 fn Sql.Insert (table, vals) => valsToFormula (table, vals)
|
ziv@2218
|
620 | Sql.Delete (table, wher) => renameTables [(table, "T")] (sqexpToFormula wher)
|
ziv@2218
|
621 | Sql.Update (table, vals, wher) =>
|
ziv@2218
|
622 let
|
ziv@2221
|
623 val fWhere = sqexpToFormula wher
|
ziv@2221
|
624 val fVals = valsToFormula (table, vals)
|
ziv@2237
|
625 val modifiedFields = SS.addList (SS.empty, map #1 vals)
|
ziv@2221
|
626 (* TODO: don't use field name hack. *)
|
ziv@2221
|
627 val markField =
|
ziv@2237
|
628 fn e as Sql.Field (t, v) => if SS.member (modifiedFields, v)
|
ziv@2237
|
629 then Sql.Field (t, v ^ "'")
|
ziv@2237
|
630 else e
|
ziv@2221
|
631 | e => e
|
ziv@2221
|
632 val mark = mapFormula (fn (cmp, e1, e2) => (cmp, markField e1, markField e2))
|
ziv@2218
|
633 in
|
ziv@2218
|
634 renameTables [(table, "T")]
|
ziv@2234
|
635 (Combo (Disj, [Combo (Conj, [fVals, mark fWhere]),
|
ziv@2244
|
636 Combo (Conj, [mark fVals, fWhere])]))
|
ziv@2218
|
637 end
|
ziv@2213
|
638
|
ziv@2213
|
639
|
ziv@2265
|
640 (*************************************)
|
ziv@2265
|
641 (* Program Instrumentation Utilities *)
|
ziv@2265
|
642 (*************************************)
|
ziv@2213
|
643
|
ziv@2234
|
644 val varName =
|
ziv@2234
|
645 let
|
ziv@2234
|
646 val varNumber = ref 0
|
ziv@2234
|
647 in
|
ziv@2234
|
648 fn s => (varNumber := !varNumber + 1; s ^ Int.toString (!varNumber))
|
ziv@2234
|
649 end
|
ziv@2234
|
650
|
ziv@2233
|
651 val {check, store, flush, ...} = getCache ()
|
ziv@2233
|
652
|
ziv@2248
|
653 val dummyTyp = (TRecord [], dummyLoc)
|
ziv@2248
|
654
|
ziv@2230
|
655 fun stringExp s = (EPrim (Prim.String (Prim.Normal, s)), dummyLoc)
|
ziv@2230
|
656
|
ziv@2230
|
657 val stringTyp = (TFfi ("Basis", "string"), dummyLoc)
|
ziv@2213
|
658
|
ziv@2213
|
659 val sequence =
|
ziv@2213
|
660 fn (exp :: exps) =>
|
ziv@2213
|
661 let
|
ziv@2230
|
662 val loc = dummyLoc
|
ziv@2213
|
663 in
|
ziv@2213
|
664 List.foldl (fn (e', seq) => ESeq ((seq, loc), (e', loc))) exp exps
|
ziv@2213
|
665 end
|
ziv@2213
|
666 | _ => raise Match
|
ziv@2213
|
667
|
ziv@2248
|
668 (* Always increments negative indices as a hack we use later. *)
|
ziv@2248
|
669 fun incRels inc =
|
ziv@2215
|
670 MonoUtil.Exp.mapB
|
ziv@2248
|
671 {typ = fn t' => t',
|
ziv@2248
|
672 exp = fn bound =>
|
ziv@2248
|
673 (fn ERel n => ERel (if n >= bound orelse n < 0 then n + inc else n)
|
ziv@2248
|
674 | e' => e'),
|
ziv@2248
|
675 bind = fn (bound, MonoUtil.Exp.RelE _) => bound + 1 | (bound, _) => bound}
|
ziv@2248
|
676 0
|
ziv@2213
|
677
|
ziv@2262
|
678 fun fileTopLevelMapfoldB doTopLevelExp (decls, sideInfo) state =
|
ziv@2262
|
679 let
|
ziv@2262
|
680 fun doVal env ((x, n, t, exp, s), state) =
|
ziv@2262
|
681 let
|
ziv@2262
|
682 val (exp, state) = doTopLevelExp env exp state
|
ziv@2262
|
683 in
|
ziv@2262
|
684 ((x, n, t, exp, s), state)
|
ziv@2262
|
685 end
|
ziv@2262
|
686 fun doDecl' env (decl', state) =
|
ziv@2262
|
687 case decl' of
|
ziv@2262
|
688 DVal v =>
|
ziv@2262
|
689 let
|
ziv@2262
|
690 val (v, state) = doVal env (v, state)
|
ziv@2262
|
691 in
|
ziv@2262
|
692 (DVal v, state)
|
ziv@2262
|
693 end
|
ziv@2262
|
694 | DValRec vs =>
|
ziv@2262
|
695 let
|
ziv@2262
|
696 val (vs, state) = ListUtil.foldlMap (doVal env) state vs
|
ziv@2262
|
697 in
|
ziv@2262
|
698 (DValRec vs, state)
|
ziv@2262
|
699 end
|
ziv@2262
|
700 | _ => (decl', state)
|
ziv@2262
|
701 fun doDecl (decl as (decl', loc), (env, state)) =
|
ziv@2262
|
702 let
|
ziv@2262
|
703 val env = MonoEnv.declBinds env decl
|
ziv@2262
|
704 val (decl', state) = doDecl' env (decl', state)
|
ziv@2262
|
705 in
|
ziv@2262
|
706 ((decl', loc), (env, state))
|
ziv@2262
|
707 end
|
ziv@2262
|
708 val (decls, (_, state)) = (ListUtil.foldlMap doDecl (MonoEnv.empty, state) decls)
|
ziv@2262
|
709 in
|
ziv@2262
|
710 ((decls, sideInfo), state)
|
ziv@2262
|
711 end
|
ziv@2262
|
712
|
ziv@2262
|
713 fun fileAllMapfoldB doExp file start =
|
ziv@2248
|
714 case MonoUtil.File.mapfoldB
|
ziv@2248
|
715 {typ = Search.return2,
|
ziv@2250
|
716 exp = fn env => fn e' => fn s => Search.Continue (doExp env e' s),
|
ziv@2248
|
717 decl = fn _ => Search.return2,
|
ziv@2248
|
718 bind = doBind}
|
ziv@2250
|
719 MonoEnv.empty file start of
|
ziv@2213
|
720 Search.Continue x => x
|
ziv@2213
|
721 | Search.Return _ => raise Match
|
ziv@2213
|
722
|
ziv@2262
|
723 fun fileMap doExp file = #1 (fileAllMapfoldB (fn _ => fn e => fn _ => (doExp e, ())) file ())
|
ziv@2213
|
724
|
ziv@2267
|
725 (* TODO: make this a bit prettier.... *)
|
ziv@2267
|
726 val simplifySql =
|
ziv@2266
|
727 let
|
ziv@2267
|
728 fun factorOutNontrivial text =
|
ziv@2267
|
729 let
|
ziv@2267
|
730 val loc = dummyLoc
|
ziv@2267
|
731 fun strcat (e1, e2) = (EStrcat (e1, e2), loc)
|
ziv@2267
|
732 val chunks = Sql.chunkify text
|
ziv@2267
|
733 val (newText, newVariables) =
|
ziv@2267
|
734 (* Important that this is foldr (to oppose foldl below). *)
|
ziv@2267
|
735 List.foldr
|
ziv@2267
|
736 (fn (chunk, (qText, newVars)) =>
|
ziv@2267
|
737 (* Variable bound to the head of newVars will have the lowest index. *)
|
ziv@2267
|
738 case chunk of
|
ziv@2267
|
739 (* EPrim should always be a string in this case. *)
|
ziv@2267
|
740 Sql.Exp (e as (EPrim _, _)) => (strcat (e, qText), newVars)
|
ziv@2267
|
741 | Sql.Exp e =>
|
ziv@2267
|
742 let
|
ziv@2267
|
743 val n = length newVars
|
ziv@2267
|
744 in
|
ziv@2267
|
745 (* This is the (n+1)th new variable, so there are
|
ziv@2267
|
746 already n new variables bound, so we increment
|
ziv@2267
|
747 indices by n. *)
|
ziv@2267
|
748 (strcat ((ERel (~(n+1)), loc), qText), incRels n e :: newVars)
|
ziv@2267
|
749 end
|
ziv@2267
|
750 | Sql.String s => (strcat (stringExp s, qText), newVars))
|
ziv@2267
|
751 (stringExp "", [])
|
ziv@2267
|
752 chunks
|
ziv@2267
|
753 fun wrapLets e' =
|
ziv@2267
|
754 (* Important that this is foldl (to oppose foldr above). *)
|
ziv@2267
|
755 List.foldl (fn (v, e') => ELet (varName "sqlArg", stringTyp, v, (e', loc)))
|
ziv@2267
|
756 e'
|
ziv@2267
|
757 newVariables
|
ziv@2267
|
758 val numArgs = length newVariables
|
ziv@2267
|
759 in
|
ziv@2267
|
760 (newText, wrapLets, numArgs)
|
ziv@2267
|
761 end
|
ziv@2267
|
762 fun doExp exp' =
|
ziv@2267
|
763 let
|
ziv@2267
|
764 val text = case exp' of
|
ziv@2267
|
765 EQuery {query = text, ...} => text
|
ziv@2267
|
766 | EDml (text, _) => text
|
ziv@2267
|
767 | _ => raise Match
|
ziv@2267
|
768 val (newText, wrapLets, numArgs) = factorOutNontrivial text
|
ziv@2267
|
769 val newExp' = case exp' of
|
ziv@2267
|
770 EQuery q => EQuery {query = newText,
|
ziv@2267
|
771 exps = #exps q,
|
ziv@2267
|
772 tables = #tables q,
|
ziv@2267
|
773 state = #state q,
|
ziv@2267
|
774 body = #body q,
|
ziv@2267
|
775 initial = #initial q}
|
ziv@2267
|
776 | EDml (_, failureMode) => EDml (newText, failureMode)
|
ziv@2267
|
777 | _ => raise Match
|
ziv@2267
|
778 in
|
ziv@2267
|
779 (* Increment once for each new variable just made. This is
|
ziv@2267
|
780 where we use the negative De Bruijn indices hack. *)
|
ziv@2267
|
781 (* TODO: please don't use that hack. As anyone could have
|
ziv@2267
|
782 predicted, it was incomprehensible a year later.... *)
|
ziv@2267
|
783 wrapLets (#1 (incRels numArgs (newExp', dummyLoc)))
|
ziv@2267
|
784 end
|
ziv@2266
|
785 in
|
ziv@2267
|
786 fileMap (fn exp' => case exp' of
|
ziv@2267
|
787 EQuery _ => doExp exp'
|
ziv@2267
|
788 | EDml _ => doExp exp'
|
ziv@2267
|
789 | _ => exp')
|
ziv@2266
|
790 end
|
ziv@2266
|
791
|
ziv@2250
|
792
|
ziv@2250
|
793 (**********************)
|
ziv@2250
|
794 (* Mono Type Checking *)
|
ziv@2250
|
795 (**********************)
|
ziv@2250
|
796
|
ziv@2250
|
797 fun typOfExp' (env : MonoEnv.env) : exp' -> typ option =
|
ziv@2250
|
798 fn EPrim p => SOME (TFfi ("Basis", case p of
|
ziv@2250
|
799 Prim.Int _ => "int"
|
ziv@2250
|
800 | Prim.Float _ => "double"
|
ziv@2250
|
801 | Prim.String _ => "string"
|
ziv@2250
|
802 | Prim.Char _ => "char"),
|
ziv@2250
|
803 dummyLoc)
|
ziv@2250
|
804 | ERel n => SOME (#2 (MonoEnv.lookupERel env n))
|
ziv@2250
|
805 | ENamed n => SOME (#2 (MonoEnv.lookupENamed env n))
|
ziv@2250
|
806 (* ASK: okay to make a new [ref] each time? *)
|
ziv@2250
|
807 | ECon (dk, PConVar nCon, _) =>
|
ziv@2250
|
808 let
|
ziv@2250
|
809 val (_, _, nData) = MonoEnv.lookupConstructor env nCon
|
ziv@2250
|
810 val (_, cs) = MonoEnv.lookupDatatype env nData
|
ziv@2250
|
811 in
|
ziv@2250
|
812 SOME (TDatatype (nData, ref (dk, cs)), dummyLoc)
|
ziv@2250
|
813 end
|
ziv@2250
|
814 | ECon (_, PConFfi {mod = s, datatyp, ...}, _) => SOME (TFfi (s, datatyp), dummyLoc)
|
ziv@2250
|
815 | ENone t => SOME (TOption t, dummyLoc)
|
ziv@2250
|
816 | ESome (t, _) => SOME (TOption t, dummyLoc)
|
ziv@2250
|
817 | EFfi _ => NONE
|
ziv@2250
|
818 | EFfiApp _ => NONE
|
ziv@2250
|
819 | EApp (e1, e2) => (case typOfExp env e1 of
|
ziv@2250
|
820 SOME (TFun (_, t), _) => SOME t
|
ziv@2250
|
821 | _ => NONE)
|
ziv@2250
|
822 | EAbs (_, t1, t2, _) => SOME (TFun (t1, t2), dummyLoc)
|
ziv@2250
|
823 (* ASK: is this right? *)
|
ziv@2250
|
824 | EUnop (unop, e) => (case unop of
|
ziv@2250
|
825 "!" => SOME (TFfi ("Basis", "bool"), dummyLoc)
|
ziv@2250
|
826 | "-" => typOfExp env e
|
ziv@2250
|
827 | _ => NONE)
|
ziv@2250
|
828 (* ASK: how should this (and other "=> NONE" cases) work? *)
|
ziv@2250
|
829 | EBinop _ => NONE
|
ziv@2250
|
830 | ERecord fields => SOME (TRecord (map (fn (s, _, t) => (s, t)) fields), dummyLoc)
|
ziv@2250
|
831 | EField (e, s) => (case typOfExp env e of
|
ziv@2250
|
832 SOME (TRecord fields, _) =>
|
ziv@2250
|
833 (case List.find (fn (s', _) => s = s') fields of
|
ziv@2250
|
834 SOME (_, t) => SOME t
|
ziv@2250
|
835 | _ => NONE)
|
ziv@2250
|
836 | _ => NONE)
|
ziv@2250
|
837 | ECase (_, _, {result, ...}) => SOME result
|
ziv@2250
|
838 | EStrcat _ => SOME (TFfi ("Basis", "string"), dummyLoc)
|
ziv@2250
|
839 | EWrite _ => SOME (TRecord [], dummyLoc)
|
ziv@2250
|
840 | ESeq (_, e) => typOfExp env e
|
ziv@2250
|
841 | ELet (s, t, e1, e2) => typOfExp (MonoEnv.pushERel env s t (SOME e1)) e2
|
ziv@2250
|
842 | EClosure _ => NONE
|
ziv@2250
|
843 | EUnurlify (_, t, _) => SOME t
|
ziv@2269
|
844 | EQuery {state, ...} => SOME state
|
ziv@2256
|
845 | _ => NONE
|
ziv@2250
|
846
|
ziv@2250
|
847 and typOfExp env (e', loc) = typOfExp' env e'
|
ziv@2250
|
848
|
ziv@2250
|
849
|
ziv@2266
|
850 (***********)
|
ziv@2266
|
851 (* Caching *)
|
ziv@2266
|
852 (***********)
|
ziv@2250
|
853
|
ziv@2267
|
854 (*
|
ziv@2267
|
855
|
ziv@2267
|
856 To get the invalidations for a dml, we need (each <- is list-monad-y):
|
ziv@2267
|
857 * table <- dml
|
ziv@2267
|
858 * cache <- table
|
ziv@2267
|
859 * query <- cache
|
ziv@2267
|
860 * inval <- (query, dml),
|
ziv@2267
|
861 where inval is a list of query argument indices, so
|
ziv@2267
|
862 * way to change query args in inval to cache args.
|
ziv@2267
|
863 For now, the last one is just
|
ziv@2267
|
864 * a map from query arg number to the corresponding free variable (per query)
|
ziv@2267
|
865 * a map from free variable to cache arg number (per cache).
|
ziv@2267
|
866 Both queries and caches should have IDs.
|
ziv@2267
|
867
|
ziv@2267
|
868 *)
|
ziv@2267
|
869
|
ziv@2271
|
870 type state = InvalInfo.state
|
ziv@2271
|
871
|
ziv@2271
|
872 datatype subexp = Cachable of InvalInfo.t * (state -> exp * state) | Impure of exp
|
ziv@2271
|
873
|
ziv@2271
|
874 val isImpure =
|
ziv@2271
|
875 fn Cachable _ => false
|
ziv@2271
|
876 | Impure _ => true
|
ziv@2271
|
877
|
ziv@2271
|
878 val runSubexp : subexp * state -> exp * state =
|
ziv@2271
|
879 fn (Cachable (_, f), state) => f state
|
ziv@2271
|
880 | (Impure e, state) => (e, state)
|
ziv@2271
|
881
|
ziv@2271
|
882 val invalInfoOfSubexp =
|
ziv@2271
|
883 fn Cachable (invalInfo, _) => invalInfo
|
ziv@2271
|
884 | Impure _ => raise Match
|
ziv@2271
|
885
|
ziv@2271
|
886 fun cacheWrap (env, exp, typ, args, index) =
|
ziv@2265
|
887 let
|
ziv@2265
|
888 val loc = dummyLoc
|
ziv@2265
|
889 val rel0 = (ERel 0, loc)
|
ziv@2265
|
890 in
|
ziv@2271
|
891 case MonoFooify.urlify env (rel0, typ) of
|
ziv@2265
|
892 NONE => NONE
|
ziv@2265
|
893 | SOME urlified =>
|
ziv@2265
|
894 let
|
ziv@2265
|
895 (* We ensure before this step that all arguments aren't effectful.
|
ziv@2265
|
896 by turning them into local variables as needed. *)
|
ziv@2265
|
897 val argsInc = map (incRels 1) args
|
ziv@2268
|
898 val check = (check (index, args), loc)
|
ziv@2268
|
899 val store = (store (index, argsInc, urlified), loc)
|
ziv@2265
|
900 in
|
ziv@2271
|
901 SOME (ECase (check,
|
ziv@2271
|
902 [((PNone stringTyp, loc),
|
ziv@2271
|
903 (ELet (varName "q", typ, exp, (ESeq (store, rel0), loc)), loc)),
|
ziv@2271
|
904 ((PSome (stringTyp, (PVar (varName "hit", stringTyp), loc)), loc),
|
ziv@2271
|
905 (* Boolean is false because we're not unurlifying from a cookie. *)
|
ziv@2271
|
906 (EUnurlify (rel0, typ, false), loc))],
|
ziv@2271
|
907 {disc = (TOption stringTyp, loc), result = typ}))
|
ziv@2265
|
908 end
|
ziv@2265
|
909 end
|
ziv@2265
|
910
|
ziv@2258
|
911 val expSize = MonoUtil.Exp.fold {typ = #2, exp = fn (_, n) => n+1} 0
|
ziv@2258
|
912
|
ziv@2259
|
913 (* TODO: pick a number. *)
|
ziv@2259
|
914 val sizeWorthCaching = 5
|
ziv@2259
|
915
|
ziv@2269
|
916 val worthCaching =
|
ziv@2269
|
917 fn EQuery _ => true
|
ziv@2269
|
918 | exp' => expSize (exp', dummyLoc) > sizeWorthCaching
|
ziv@2269
|
919
|
ziv@2271
|
920 fun cacheExp ((env, exp', invalInfo, state) : MonoEnv.env * exp' * InvalInfo.t * state) =
|
ziv@2269
|
921 case (worthCaching exp')
|
ziv@2269
|
922 </oguard/>
|
ziv@2269
|
923 typOfExp' env exp' of
|
ziv@2269
|
924 NONE => NONE
|
ziv@2269
|
925 | SOME (TFun _, _) => NONE
|
ziv@2269
|
926 | SOME typ =>
|
ziv@2271
|
927 let
|
ziv@2271
|
928 val ns = InvalInfo.orderArgs (invalInfo, freeVars (exp', dummyLoc))
|
ziv@2271
|
929 val numArgs = length ns
|
ziv@2271
|
930 in (List.foldr (fn (_, NONE) => NONE
|
ziv@2271
|
931 | ((n, typ), SOME args) =>
|
ziv@2271
|
932 (MonoFooify.urlify env ((ERel n, dummyLoc), typ))
|
ziv@2271
|
933 </obind/>
|
ziv@2271
|
934 (fn arg => SOME (arg :: args)))
|
ziv@2271
|
935 (SOME [])
|
ziv@2271
|
936 (map (fn n => (n, #2 (MonoEnv.lookupERel env n))) ns))
|
ziv@2271
|
937 </obind/>
|
ziv@2271
|
938 (fn args =>
|
ziv@2271
|
939 (cacheWrap (env, (exp', dummyLoc), typ, args, #index state))
|
ziv@2271
|
940 </obind/>
|
ziv@2271
|
941 (fn cachedExp =>
|
ziv@2271
|
942 SOME (cachedExp, InvalInfo.updateState (invalInfo, numArgs, state))))
|
ziv@2271
|
943 end
|
ziv@2269
|
944
|
ziv@2271
|
945 fun cacheQuery (effs, env, q) : subexp =
|
ziv@2266
|
946 let
|
ziv@2266
|
947 (* We use dummyTyp here. I think this is okay because databases don't
|
ziv@2266
|
948 store (effectful) functions, but perhaps there's some pathalogical
|
ziv@2266
|
949 corner case missing.... *)
|
ziv@2266
|
950 fun safe bound =
|
ziv@2266
|
951 not
|
ziv@2266
|
952 o effectful effs
|
ziv@2266
|
953 (iterate (fn env => MonoEnv.pushERel env "_" dummyTyp NONE)
|
ziv@2266
|
954 bound
|
ziv@2266
|
955 env)
|
ziv@2271
|
956 val {query = queryText, initial, body, ...} = q
|
ziv@2271
|
957 (* DEBUG *)
|
ziv@2271
|
958 (* val () = Print.preface ("sqlcache> ", MonoPrint.p_exp MonoEnv.empty queryText) *)
|
ziv@2266
|
959 val attempt =
|
ziv@2266
|
960 (* Ziv misses Haskell's do notation.... *)
|
ziv@2267
|
961 (safe 0 queryText andalso safe 0 initial andalso safe 2 body)
|
ziv@2268
|
962 </oguard/>
|
ziv@2268
|
963 Sql.parse Sql.query queryText
|
ziv@2268
|
964 </obind/>
|
ziv@2268
|
965 (fn queryParsed =>
|
ziv@2271
|
966 let
|
ziv@2271
|
967 val invalInfo = InvalInfo.singleton queryParsed
|
ziv@2271
|
968 fun mkExp state =
|
ziv@2271
|
969 case cacheExp (env, EQuery q, invalInfo, state) of
|
ziv@2271
|
970 NONE => ((EQuery q, dummyLoc), state)
|
ziv@2271
|
971 | SOME (cachedExp, state) => ((cachedExp, dummyLoc), state)
|
ziv@2271
|
972 in
|
ziv@2271
|
973 SOME (Cachable (invalInfo, mkExp))
|
ziv@2271
|
974 end)
|
ziv@2266
|
975 in
|
ziv@2266
|
976 case attempt of
|
ziv@2271
|
977 NONE => Impure (EQuery q, dummyLoc)
|
ziv@2271
|
978 | SOME subexp => subexp
|
ziv@2266
|
979 end
|
ziv@2266
|
980
|
ziv@2271
|
981 fun cacheTree (effs : IS.set) ((env, exp as (exp', loc)), state) =
|
ziv@2250
|
982 let
|
ziv@2271
|
983 fun wrapBindN (f : exp list -> exp')
|
ziv@2271
|
984 (args : ((MonoEnv.env * exp) * unbind) list) =
|
ziv@2250
|
985 let
|
ziv@2271
|
986 val (subexps, state) =
|
ziv@2271
|
987 ListUtil.foldlMap (cacheTree effs)
|
ziv@2271
|
988 state
|
ziv@2271
|
989 (map #1 args)
|
ziv@2268
|
990 fun mkExp state = mapFst (fn exps => (f exps, loc))
|
ziv@2268
|
991 (ListUtil.foldlMap runSubexp state subexps)
|
ziv@2271
|
992 val attempt =
|
ziv@2271
|
993 if List.exists isImpure subexps
|
ziv@2271
|
994 then NONE
|
ziv@2271
|
995 else (List.foldl (omap2 InvalInfo.union)
|
ziv@2271
|
996 (SOME InvalInfo.empty)
|
ziv@2271
|
997 (ListPair.map
|
ziv@2271
|
998 (fn (subexp, (_, unbinds)) =>
|
ziv@2271
|
999 InvalInfo.unbind (invalInfoOfSubexp subexp, unbinds))
|
ziv@2271
|
1000 (subexps, args)))
|
ziv@2271
|
1001 </obind/>
|
ziv@2271
|
1002 (fn invalInfo =>
|
ziv@2271
|
1003 SOME (Cachable (invalInfo,
|
ziv@2271
|
1004 fn state =>
|
ziv@2271
|
1005 case cacheExp (env,
|
ziv@2271
|
1006 f (map (#2 o #1) args),
|
ziv@2271
|
1007 invalInfo,
|
ziv@2271
|
1008 state) of
|
ziv@2271
|
1009 NONE => mkExp state
|
ziv@2271
|
1010 | SOME (e', state) => ((e', loc), state)),
|
ziv@2271
|
1011 state))
|
ziv@2250
|
1012 in
|
ziv@2271
|
1013 case attempt of
|
ziv@2271
|
1014 SOME (subexp, state) => (subexp, state)
|
ziv@2271
|
1015 | NONE => mapFst Impure (mkExp state)
|
ziv@2250
|
1016 end
|
ziv@2250
|
1017 fun wrapBind1 f arg =
|
ziv@2250
|
1018 wrapBindN (fn [arg] => f arg | _ => raise Match) [arg]
|
ziv@2250
|
1019 fun wrapBind2 f (arg1, arg2) =
|
ziv@2250
|
1020 wrapBindN (fn [arg1, arg2] => f (arg1, arg2) | _ => raise Match) [arg1, arg2]
|
ziv@2271
|
1021 fun wrapN f es = wrapBindN f (map (fn e => ((env, e), Unknowns 0)) es)
|
ziv@2271
|
1022 fun wrap1 f e = wrapBind1 f ((env, e), Unknowns 0)
|
ziv@2271
|
1023 fun wrap2 f (e1, e2) = wrapBind2 f (((env, e1), Unknowns 0), ((env, e2), Unknowns 0))
|
ziv@2250
|
1024 in
|
ziv@2250
|
1025 case exp' of
|
ziv@2250
|
1026 ECon (dk, pc, SOME e) => wrap1 (fn e => ECon (dk, pc, SOME e)) e
|
ziv@2250
|
1027 | ESome (t, e) => wrap1 (fn e => ESome (t, e)) e
|
ziv@2250
|
1028 | EFfiApp (s1, s2, args) =>
|
ziv@2258
|
1029 if ffiEffectful (s1, s2)
|
ziv@2266
|
1030 then (Impure exp, state)
|
ziv@2258
|
1031 else wrapN (fn es =>
|
ziv@2258
|
1032 EFfiApp (s1, s2, ListPair.map (fn (e, (_, t)) => (e, t)) (es, args)))
|
ziv@2258
|
1033 (map #1 args)
|
ziv@2250
|
1034 | EApp (e1, e2) => wrap2 EApp (e1, e2)
|
ziv@2250
|
1035 | EAbs (s, t1, t2, e) =>
|
ziv@2250
|
1036 wrapBind1 (fn e => EAbs (s, t1, t2, e))
|
ziv@2271
|
1037 ((MonoEnv.pushERel env s t1 NONE, e), Unknowns 1)
|
ziv@2250
|
1038 | EUnop (s, e) => wrap1 (fn e => EUnop (s, e)) e
|
ziv@2250
|
1039 | EBinop (bi, s, e1, e2) => wrap2 (fn (e1, e2) => EBinop (bi, s, e1, e2)) (e1, e2)
|
ziv@2250
|
1040 | ERecord fields =>
|
ziv@2250
|
1041 wrapN (fn es => ERecord (ListPair.map (fn (e, (s, _, t)) => (s, e, t)) (es, fields)))
|
ziv@2250
|
1042 (map #2 fields)
|
ziv@2250
|
1043 | EField (e, s) => wrap1 (fn e => EField (e, s)) e
|
ziv@2250
|
1044 | ECase (e, cases, {disc, result}) =>
|
ziv@2250
|
1045 wrapBindN (fn (e::es) =>
|
ziv@2250
|
1046 ECase (e,
|
ziv@2250
|
1047 (ListPair.map (fn (e, (p, _)) => (p, e)) (es, cases)),
|
ziv@2256
|
1048 {disc = disc, result = result})
|
ziv@2256
|
1049 | _ => raise Match)
|
ziv@2271
|
1050 (((env, e), Unknowns 0)
|
ziv@2271
|
1051 :: map (fn (p, e) =>
|
ziv@2271
|
1052 ((MonoEnv.patBinds env p, e), Unknowns (MonoEnv.patBindsN p)))
|
ziv@2271
|
1053 cases)
|
ziv@2250
|
1054 | EStrcat (e1, e2) => wrap2 EStrcat (e1, e2)
|
ziv@2250
|
1055 (* We record page writes, so they're cachable. *)
|
ziv@2250
|
1056 | EWrite e => wrap1 EWrite e
|
ziv@2250
|
1057 | ESeq (e1, e2) => wrap2 ESeq (e1, e2)
|
ziv@2250
|
1058 | ELet (s, t, e1, e2) =>
|
ziv@2250
|
1059 wrapBind2 (fn (e1, e2) => ELet (s, t, e1, e2))
|
ziv@2271
|
1060 (((env, e1), Unknowns 0),
|
ziv@2271
|
1061 ((MonoEnv.pushERel env s t (SOME e1), e2), Known e1))
|
ziv@2250
|
1062 (* ASK: | EClosure (n, es) => ? *)
|
ziv@2250
|
1063 | EUnurlify (e, t, b) => wrap1 (fn e => EUnurlify (e, t, b)) e
|
ziv@2271
|
1064 | EQuery q => (cacheQuery (effs, env, q), state)
|
ziv@2269
|
1065 | _ => (if effectful effs env exp
|
ziv@2269
|
1066 then Impure exp
|
ziv@2271
|
1067 else Cachable (InvalInfo.empty,
|
ziv@2271
|
1068 fn state =>
|
ziv@2271
|
1069 case cacheExp (env, exp', InvalInfo.empty, state) of
|
ziv@2269
|
1070 NONE => ((exp', loc), state)
|
ziv@2269
|
1071 | SOME (exp', state) => ((exp', loc), state)),
|
ziv@2269
|
1072 state)
|
ziv@2256
|
1073 end
|
ziv@2256
|
1074
|
ziv@2266
|
1075 fun addCaching file =
|
ziv@2256
|
1076 let
|
ziv@2266
|
1077 val effs = effectfulDecls file
|
ziv@2271
|
1078 fun doTopLevelExp env exp state = runSubexp (cacheTree effs ((env, exp), state))
|
ziv@2256
|
1079 in
|
ziv@2271
|
1080 (fileTopLevelMapfoldB doTopLevelExp
|
ziv@2271
|
1081 file
|
ziv@2271
|
1082 {tableToIndices = SIMM.empty,
|
ziv@2271
|
1083 indexToInvalInfo = IM.empty,
|
ziv@2271
|
1084 ffiInfo = [],
|
ziv@2271
|
1085 index = 0},
|
ziv@2271
|
1086 effs)
|
ziv@2265
|
1087 end
|
ziv@2265
|
1088
|
ziv@2265
|
1089
|
ziv@2265
|
1090 (************)
|
ziv@2265
|
1091 (* Flushing *)
|
ziv@2265
|
1092 (************)
|
ziv@2265
|
1093
|
ziv@2265
|
1094 structure Invalidations = struct
|
ziv@2265
|
1095
|
ziv@2265
|
1096 val loc = dummyLoc
|
ziv@2265
|
1097
|
ziv@2265
|
1098 val optionAtomExpToExp =
|
ziv@2265
|
1099 fn NONE => (ENone stringTyp, loc)
|
ziv@2265
|
1100 | SOME e => (ESome (stringTyp,
|
ziv@2265
|
1101 (case e of
|
ziv@2265
|
1102 DmlRel n => ERel n
|
ziv@2265
|
1103 | Prim p => EPrim p
|
ziv@2265
|
1104 (* TODO: make new type containing only these two. *)
|
ziv@2265
|
1105 | _ => raise Match,
|
ziv@2265
|
1106 loc)),
|
ziv@2265
|
1107 loc)
|
ziv@2265
|
1108
|
ziv@2265
|
1109 fun eqsToInvalidation numArgs eqs =
|
ziv@2269
|
1110 List.tabulate (numArgs, (fn n => IM.find (eqs, n)))
|
ziv@2265
|
1111
|
ziv@2265
|
1112 (* Tests if [ys] makes [xs] a redundant cache invalidation. [NONE] here
|
ziv@2265
|
1113 represents unknown, which means a wider invalidation. *)
|
ziv@2265
|
1114 val rec madeRedundantBy : atomExp option list * atomExp option list -> bool =
|
ziv@2265
|
1115 fn ([], []) => true
|
ziv@2265
|
1116 | (_ :: xs, NONE :: ys) => madeRedundantBy (xs, ys)
|
ziv@2265
|
1117 | (SOME x :: xs, SOME y :: ys) => (case AtomExpKey.compare (x, y) of
|
ziv@2265
|
1118 EQUAL => madeRedundantBy (xs, ys)
|
ziv@2265
|
1119 | _ => false)
|
ziv@2265
|
1120 | _ => false
|
ziv@2265
|
1121
|
ziv@2265
|
1122 fun eqss (query, dml) = conflictMaps (queryToFormula query, dmlToFormula dml)
|
ziv@2265
|
1123
|
ziv@2271
|
1124 fun invalidations ((invalInfo, numArgs), dml) =
|
ziv@2271
|
1125 let
|
ziv@2271
|
1126 val query = InvalInfo.query invalInfo
|
ziv@2271
|
1127 in
|
ziv@2271
|
1128 (map (map optionAtomExpToExp)
|
ziv@2271
|
1129 o removeRedundant madeRedundantBy
|
ziv@2271
|
1130 o map (eqsToInvalidation numArgs)
|
ziv@2271
|
1131 o eqss)
|
ziv@2271
|
1132 (query, dml)
|
ziv@2271
|
1133 end
|
ziv@2265
|
1134
|
ziv@2265
|
1135 end
|
ziv@2265
|
1136
|
ziv@2265
|
1137 val invalidations = Invalidations.invalidations
|
ziv@2265
|
1138
|
ziv@2265
|
1139 (* DEBUG *)
|
ziv@2265
|
1140 (* val gunk : ((Sql.query * int) * Sql.dml) list ref = ref [] *)
|
ziv@2265
|
1141 (* val gunk' : exp list ref = ref [] *)
|
ziv@2265
|
1142
|
ziv@2271
|
1143 fun addFlushing ((file, {tableToIndices, indexToInvalInfo, ffiInfo, index}), effs) =
|
ziv@2265
|
1144 let
|
ziv@2265
|
1145 val flushes = List.concat
|
ziv@2265
|
1146 o map (fn (i, argss) => map (fn args => flush (i, args)) argss)
|
ziv@2265
|
1147 val doExp =
|
ziv@2267
|
1148 fn dmlExp as EDml (dmlText, failureMode) =>
|
ziv@2265
|
1149 let
|
ziv@2265
|
1150 (* DEBUG *)
|
ziv@2265
|
1151 (* val () = gunk' := origDmlText :: !gunk' *)
|
ziv@2265
|
1152 (* val () = Print.preface ("SQLCACHE: ", (MonoPrint.p_exp MonoEnv.empty origDmlText)) *)
|
ziv@2265
|
1153 val inval =
|
ziv@2265
|
1154 case Sql.parse Sql.dml dmlText of
|
ziv@2265
|
1155 SOME dmlParsed =>
|
ziv@2271
|
1156 SOME (map (fn i => (case IM.find (indexToInvalInfo, i) of
|
ziv@2271
|
1157 SOME invalInfo =>
|
ziv@2271
|
1158 (i, invalidations (invalInfo, dmlParsed))
|
ziv@2265
|
1159 (* TODO: fail more gracefully. *)
|
ziv@2271
|
1160 (* This probably means invalidating everything.... *)
|
ziv@2265
|
1161 | NONE => raise Match))
|
ziv@2271
|
1162 (SIMM.findList (tableToIndices, tableOfDml dmlParsed)))
|
ziv@2265
|
1163 | NONE => NONE
|
ziv@2265
|
1164 in
|
ziv@2265
|
1165 case inval of
|
ziv@2265
|
1166 (* TODO: fail more gracefully. *)
|
ziv@2265
|
1167 NONE => raise Match
|
ziv@2267
|
1168 | SOME invs => sequence (flushes invs @ [dmlExp])
|
ziv@2265
|
1169 end
|
ziv@2265
|
1170 | e' => e'
|
ziv@2265
|
1171 in
|
ziv@2265
|
1172 (* DEBUG *)
|
ziv@2265
|
1173 (* gunk := []; *)
|
ziv@2268
|
1174 ffiInfoRef := ffiInfo;
|
ziv@2266
|
1175 fileMap doExp file
|
ziv@2265
|
1176 end
|
ziv@2265
|
1177
|
ziv@2265
|
1178
|
ziv@2268
|
1179 (************************)
|
ziv@2268
|
1180 (* Compiler Entry Point *)
|
ziv@2268
|
1181 (************************)
|
ziv@2265
|
1182
|
ziv@2265
|
1183 val inlineSql =
|
ziv@2265
|
1184 let
|
ziv@2265
|
1185 val doExp =
|
ziv@2265
|
1186 (* TODO: EQuery, too? *)
|
ziv@2265
|
1187 (* ASK: should this live in [MonoOpt]? *)
|
ziv@2265
|
1188 fn EDml ((ECase (disc, cases, {disc = dTyp, ...}), loc), failureMode) =>
|
ziv@2265
|
1189 let
|
ziv@2265
|
1190 val newCases = map (fn (p, e) => (p, (EDml (e, failureMode), loc))) cases
|
ziv@2265
|
1191 in
|
ziv@2265
|
1192 ECase (disc, newCases, {disc = dTyp, result = (TRecord [], loc)})
|
ziv@2265
|
1193 end
|
ziv@2265
|
1194 | e => e
|
ziv@2265
|
1195 in
|
ziv@2265
|
1196 fileMap doExp
|
ziv@2265
|
1197 end
|
ziv@2265
|
1198
|
ziv@2262
|
1199 fun insertAfterDatatypes ((decls, sideInfo), newDecls) =
|
ziv@2262
|
1200 let
|
ziv@2262
|
1201 val (datatypes, others) = List.partition (fn (DDatatype _, _) => true | _ => false) decls
|
ziv@2262
|
1202 in
|
ziv@2262
|
1203 (datatypes @ newDecls @ others, sideInfo)
|
ziv@2262
|
1204 end
|
ziv@2262
|
1205
|
ziv@2267
|
1206 val go' = addFlushing o addCaching o simplifySql o inlineSql
|
ziv@2256
|
1207
|
ziv@2256
|
1208 fun go file =
|
ziv@2256
|
1209 let
|
ziv@2256
|
1210 (* TODO: do something nicer than [Sql] being in one of two modes. *)
|
ziv@2256
|
1211 val () = (resetFfiInfo (); Sql.sqlcacheMode := true)
|
ziv@2262
|
1212 val file = go' file
|
ziv@2262
|
1213 (* Important that this happens after [MonoFooify.urlify] calls! *)
|
ziv@2262
|
1214 val fmDecls = MonoFooify.getNewFmDecls ()
|
ziv@2256
|
1215 val () = Sql.sqlcacheMode := false
|
ziv@2256
|
1216 in
|
ziv@2262
|
1217 insertAfterDatatypes (file, rev fmDecls)
|
ziv@2250
|
1218 end
|
ziv@2250
|
1219
|
ziv@2209
|
1220 end
|