ziv@2213
|
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@2216
|
12 (* Filled in by [cacheWrap] during [Sqlcache]. *)
|
ziv@2213
|
13 val ffiInfo : {index : int, params : int} list ref = ref []
|
ziv@2209
|
14
|
ziv@2213
|
15 fun getFfiInfo () = !ffiInfo
|
ziv@2213
|
16
|
ziv@2215
|
17 (* Some FFIs have writing as their only effect, which the caching records. *)
|
ziv@2215
|
18 val ffiEffectful =
|
ziv@2216
|
19 (* TODO: have this less hard-coded. *)
|
ziv@2215
|
20 let
|
ziv@2215
|
21 val fs = SS.fromList ["htmlifyInt_w",
|
ziv@2215
|
22 "htmlifyFloat_w",
|
ziv@2215
|
23 "htmlifyString_w",
|
ziv@2215
|
24 "htmlifyBool_w",
|
ziv@2215
|
25 "htmlifyTime_w",
|
ziv@2215
|
26 "attrifyInt_w",
|
ziv@2215
|
27 "attrifyFloat_w",
|
ziv@2215
|
28 "attrifyString_w",
|
ziv@2215
|
29 "attrifyChar_w",
|
ziv@2215
|
30 "urlifyInt_w",
|
ziv@2215
|
31 "urlifyFloat_w",
|
ziv@2215
|
32 "urlifyString_w",
|
ziv@2215
|
33 "urlifyBool_w",
|
ziv@2215
|
34 "urlifyChannel_w"]
|
ziv@2215
|
35 in
|
ziv@2215
|
36 fn (m, f) => Settings.isEffectful (m, f)
|
ziv@2215
|
37 andalso not (m = "Basis" andalso SS.member (fs, f))
|
ziv@2215
|
38 end
|
ziv@2215
|
39
|
ziv@2215
|
40
|
ziv@2215
|
41 (* Effect analysis. *)
|
ziv@2215
|
42
|
ziv@2216
|
43 (* Makes an exception for [EWrite] (which is recorded when caching). *)
|
ziv@2215
|
44 fun effectful doPrint (effs : IS.set) (inFunction : bool) (bound : int) : Mono.exp -> bool =
|
ziv@2215
|
45 (* If result is true, expression is definitely effectful. If result is
|
ziv@2215
|
46 false, then expression is definitely not effectful if effs is fully
|
ziv@2215
|
47 populated. The intended pattern is to use this a number of times equal
|
ziv@2215
|
48 to the number of declarations in a file, Bellman-Ford style. *)
|
ziv@2215
|
49 (* TODO: make incrementing of bound less janky, probably by using MonoUtil
|
ziv@2215
|
50 instead of all this. *)
|
ziv@2215
|
51 let
|
ziv@2215
|
52 (* DEBUG: remove printing when done. *)
|
ziv@2215
|
53 fun tru msg = if doPrint then (print (msg ^ "\n"); true) else true
|
ziv@2215
|
54 val rec eff' =
|
ziv@2215
|
55 (* ASK: is there a better way? *)
|
ziv@2215
|
56 fn EPrim _ => false
|
ziv@2215
|
57 (* We don't know if local functions have effects when applied. *)
|
ziv@2215
|
58 | ERel idx => if inFunction andalso idx >= bound
|
ziv@2215
|
59 then tru ("rel" ^ Int.toString idx) else false
|
ziv@2215
|
60 | ENamed name => if IS.member (effs, name) then tru "named" else false
|
ziv@2215
|
61 | ECon (_, _, NONE) => false
|
ziv@2215
|
62 | ECon (_, _, SOME e) => eff e
|
ziv@2215
|
63 | ENone _ => false
|
ziv@2215
|
64 | ESome (_, e) => eff e
|
ziv@2215
|
65 | EFfi (m, f) => if ffiEffectful (m, f) then tru "ffi" else false
|
ziv@2215
|
66 | EFfiApp (m, f, _) => if ffiEffectful (m, f) then tru "ffiapp" else false
|
ziv@2215
|
67 (* ASK: we're calling functions effectful if they have effects when
|
ziv@2215
|
68 applied or if the function expressions themselves have effects.
|
ziv@2215
|
69 Is that okay? *)
|
ziv@2215
|
70 (* This is okay because the values we ultimately care about aren't
|
ziv@2215
|
71 functions, and this is a conservative approximation, anyway. *)
|
ziv@2215
|
72 | EApp (eFun, eArg) => effectful doPrint effs true bound eFun orelse eff eArg
|
ziv@2215
|
73 | EAbs (_, _, _, e) => effectful doPrint effs inFunction (bound+1) e
|
ziv@2215
|
74 | EUnop (_, e) => eff e
|
ziv@2215
|
75 | EBinop (_, _, e1, e2) => eff e1 orelse eff e2
|
ziv@2215
|
76 | ERecord xs => List.exists (fn (_, e, _) => eff e) xs
|
ziv@2215
|
77 | EField (e, _) => eff e
|
ziv@2215
|
78 (* If any case could be effectful, consider it effectful. *)
|
ziv@2215
|
79 | ECase (e, xs, _) => eff e orelse List.exists (fn (_, e) => eff e) xs
|
ziv@2215
|
80 | EStrcat (e1, e2) => eff e1 orelse eff e2
|
ziv@2215
|
81 (* ASK: how should we treat these three? *)
|
ziv@2215
|
82 | EError _ => tru "error"
|
ziv@2215
|
83 | EReturnBlob _ => tru "blob"
|
ziv@2215
|
84 | ERedirect _ => tru "redirect"
|
ziv@2215
|
85 (* EWrite is a special exception because we record writes when caching. *)
|
ziv@2215
|
86 | EWrite _ => false
|
ziv@2215
|
87 | ESeq (e1, e2) => eff e1 orelse eff e2
|
ziv@2215
|
88 (* TODO: keep context of which local variables aren't effectful? Only
|
ziv@2215
|
89 makes a difference for function expressions, though. *)
|
ziv@2215
|
90 | ELet (_, _, eBind, eBody) => eff eBind orelse
|
ziv@2215
|
91 effectful doPrint effs inFunction (bound+1) eBody
|
ziv@2215
|
92 | EClosure (_, es) => List.exists eff es
|
ziv@2215
|
93 (* TODO: deal with EQuery. *)
|
ziv@2215
|
94 | EQuery _ => tru "query"
|
ziv@2215
|
95 | EDml _ => tru "dml"
|
ziv@2215
|
96 | ENextval _ => tru "nextval"
|
ziv@2215
|
97 | ESetval _ => tru "setval"
|
ziv@2215
|
98 | EUnurlify (e, _, _) => eff e
|
ziv@2215
|
99 (* ASK: how should we treat this? *)
|
ziv@2215
|
100 | EJavaScript _ => tru "javascript"
|
ziv@2215
|
101 (* ASK: these are all effectful, right? *)
|
ziv@2215
|
102 | ESignalReturn _ => tru "signalreturn"
|
ziv@2215
|
103 | ESignalBind _ => tru "signalbind"
|
ziv@2215
|
104 | ESignalSource _ => tru "signalsource"
|
ziv@2215
|
105 | EServerCall _ => tru "servercall"
|
ziv@2215
|
106 | ERecv _ => tru "recv"
|
ziv@2215
|
107 | ESleep _ => tru "sleep"
|
ziv@2215
|
108 | ESpawn _ => tru "spawn"
|
ziv@2215
|
109 and eff = fn (e', _) => eff' e'
|
ziv@2215
|
110 in
|
ziv@2215
|
111 eff
|
ziv@2215
|
112 end
|
ziv@2215
|
113
|
ziv@2215
|
114 (* TODO: test this. *)
|
ziv@2215
|
115 val effectfulMap =
|
ziv@2215
|
116 let
|
ziv@2215
|
117 fun doVal ((_, name, _, e, _), effMap) =
|
ziv@2215
|
118 if effectful false effMap false 0 e
|
ziv@2215
|
119 then IS.add (effMap, name)
|
ziv@2215
|
120 else effMap
|
ziv@2215
|
121 val doDecl =
|
ziv@2215
|
122 fn (DVal v, effMap) => doVal (v, effMap)
|
ziv@2215
|
123 (* Repeat the list of declarations a number of times equal to its size. *)
|
ziv@2215
|
124 | (DValRec vs, effMap) =>
|
ziv@2215
|
125 List.foldl doVal effMap (List.concat (List.map (fn _ => vs) vs))
|
ziv@2215
|
126 (* ASK: any other cases? *)
|
ziv@2215
|
127 | (_, effMap) => effMap
|
ziv@2215
|
128 in
|
ziv@2215
|
129 MonoUtil.File.fold {typ = #2, exp = #2, decl = doDecl} IS.empty
|
ziv@2215
|
130 end
|
ziv@2215
|
131
|
ziv@2215
|
132
|
ziv@2216
|
133 (* Boolean formula normalization. *)
|
ziv@2216
|
134
|
ziv@2216
|
135 datatype normalForm = Cnf | Dnf
|
ziv@2216
|
136
|
ziv@2216
|
137 datatype 'atom formula =
|
ziv@2216
|
138 Atom of 'atom
|
ziv@2216
|
139 | Negate of 'atom formula
|
ziv@2216
|
140 | Combo of normalForm * 'atom formula list
|
ziv@2216
|
141
|
ziv@2216
|
142 val flipNf = fn Cnf => Dnf | Dnf => Cnf
|
ziv@2216
|
143
|
ziv@2216
|
144 fun bind xs f = List.concat (map f xs)
|
ziv@2216
|
145
|
ziv@2216
|
146 val rec cartesianProduct : 'a list list -> 'a list list =
|
ziv@2216
|
147 fn [] => [[]]
|
ziv@2216
|
148 | (xs :: xss) => bind (cartesianProduct xss)
|
ziv@2216
|
149 (fn ys => bind xs (fn x => [x :: ys]))
|
ziv@2216
|
150
|
ziv@2216
|
151 fun normalize (negate : 'atom -> 'atom) (norm : normalForm) =
|
ziv@2216
|
152 fn Atom x => [[x]]
|
ziv@2216
|
153 | Negate f => map (map negate) (normalize negate (flipNf norm) f)
|
ziv@2216
|
154 | Combo (n, fs) =>
|
ziv@2216
|
155 let
|
ziv@2216
|
156 val fss = bind fs (normalize negate n)
|
ziv@2216
|
157 in
|
ziv@2216
|
158 if n = norm then fss else cartesianProduct fss
|
ziv@2216
|
159 end
|
ziv@2216
|
160
|
ziv@2216
|
161 fun mapFormula mf =
|
ziv@2216
|
162 fn Atom x => Atom (mf x)
|
ziv@2216
|
163 | Negate f => Negate (mapFormula mf f)
|
ziv@2216
|
164 | Combo (n, fs) => Combo (n, map (mapFormula mf) fs)
|
ziv@2216
|
165
|
ziv@2216
|
166
|
ziv@2215
|
167 (* SQL analysis. *)
|
ziv@2213
|
168
|
ziv@2216
|
169 val rec chooseTwos : 'a list -> ('a * 'a) list =
|
ziv@2216
|
170 fn [] => []
|
ziv@2216
|
171 | x :: ys => map (fn y => (x, y)) ys @ chooseTwos ys
|
ziv@2213
|
172
|
ziv@2216
|
173 datatype atomExp =
|
ziv@2216
|
174 QueryArg of int
|
ziv@2216
|
175 | DmlRel of int
|
ziv@2216
|
176 | Prim of Prim.t
|
ziv@2216
|
177 | Field of string * string
|
ziv@2216
|
178
|
ziv@2216
|
179 structure AtomExpKey : ORD_KEY = struct
|
ziv@2216
|
180
|
ziv@2216
|
181 type ord_key = atomExp
|
ziv@2216
|
182
|
ziv@2216
|
183 val compare =
|
ziv@2216
|
184 fn (QueryArg n1, QueryArg n2) => Int.compare (n1, n2)
|
ziv@2216
|
185 | (QueryArg _, _) => LESS
|
ziv@2216
|
186 | (_, QueryArg _) => GREATER
|
ziv@2216
|
187 | (DmlRel n1, DmlRel n2) => Int.compare (n1, n2)
|
ziv@2216
|
188 | (DmlRel _, _) => LESS
|
ziv@2216
|
189 | (_, DmlRel _) => GREATER
|
ziv@2216
|
190 | (Prim p1, Prim p2) => Prim.compare (p1, p2)
|
ziv@2216
|
191 | (Prim _, _) => LESS
|
ziv@2216
|
192 | (_, Prim _) => GREATER
|
ziv@2216
|
193 | (Field (t1, f1), Field (t2, f2)) => String.compare (t1 ^ "." ^ f1, t2 ^ "." ^ f2)
|
ziv@2216
|
194
|
ziv@2216
|
195 end
|
ziv@2216
|
196
|
ziv@2216
|
197 structure UF = UnionFindFn(AtomExpKey)
|
ziv@2216
|
198
|
ziv@2216
|
199 fun conflictMaps (fQuery : (Sql.cmp * Sql.sqexp * Sql.sqexp) formula,
|
ziv@2216
|
200 fDml : (Sql.cmp * Sql.sqexp * Sql.sqexp) formula) =
|
ziv@2213
|
201 let
|
ziv@2216
|
202 val toKnownEquality =
|
ziv@2216
|
203 (* [NONE] here means unkown. Anything that isn't a comparison between
|
ziv@2216
|
204 two knowns shouldn't be used, and simply dropping unused terms is
|
ziv@2216
|
205 okay in disjunctive normal form. *)
|
ziv@2216
|
206 fn (Sql.Eq, SOME e1, SOME e2) => SOME (e1, e2)
|
ziv@2216
|
207 | _ => NONE
|
ziv@2216
|
208 val equivClasses : (Sql.cmp * atomExp option * atomExp option) list -> atomExp list list =
|
ziv@2216
|
209 UF.classes
|
ziv@2216
|
210 o List.foldl UF.union' UF.empty
|
ziv@2216
|
211 o List.mapPartial toKnownEquality
|
ziv@2216
|
212 fun addToEqs (eqs, n, e) =
|
ziv@2216
|
213 case IM.find (eqs, n) of
|
ziv@2216
|
214 (* Comparing to a constant seems better? *)
|
ziv@2216
|
215 SOME (EPrim _) => eqs
|
ziv@2216
|
216 | _ => IM.insert (eqs, n, e)
|
ziv@2216
|
217 val accumulateEqs =
|
ziv@2216
|
218 (* [NONE] means we have a contradiction. *)
|
ziv@2216
|
219 fn (_, NONE) => NONE
|
ziv@2216
|
220 | ((Prim p1, Prim p2), eqso) =>
|
ziv@2216
|
221 (case Prim.compare (p1, p2) of
|
ziv@2216
|
222 EQUAL => eqso
|
ziv@2213
|
223 | _ => NONE)
|
ziv@2216
|
224 | ((QueryArg n, Prim p), SOME eqs) => SOME (addToEqs (eqs, n, EPrim p))
|
ziv@2216
|
225 | ((QueryArg n, DmlRel r), SOME eqs) => SOME (addToEqs (eqs, n, ERel r))
|
ziv@2216
|
226 | ((Prim p, QueryArg n), SOME eqs) => SOME (addToEqs (eqs, n, EPrim p))
|
ziv@2216
|
227 | ((DmlRel r, QueryArg n), SOME eqs) => SOME (addToEqs (eqs, n, ERel r))
|
ziv@2216
|
228 (* TODO: deal with equalities involving just [DmlRel]s and [Prim]s. *)
|
ziv@2216
|
229 | (_, eqso) => eqso
|
ziv@2216
|
230 val eqsOfClass : atomExp list -> Mono.exp' IM.map option =
|
ziv@2216
|
231 List.foldl accumulateEqs (SOME IM.empty)
|
ziv@2216
|
232 o chooseTwos
|
ziv@2216
|
233 fun toAtomExps rel (cmp, e1, e2) =
|
ziv@2216
|
234 let
|
ziv@2216
|
235 val qa =
|
ziv@2216
|
236 (* Here [NONE] means unkown. *)
|
ziv@2216
|
237 fn Sql.SqConst p => SOME (Prim p)
|
ziv@2216
|
238 | Sql.Field tf => SOME (Field tf)
|
ziv@2216
|
239 | Sql.Inj (EPrim p, _) => SOME (Prim p)
|
ziv@2216
|
240 | Sql.Inj (ERel n, _) => SOME (rel n)
|
ziv@2216
|
241 (* We can't deal with anything else. *)
|
ziv@2216
|
242 | _ => NONE
|
ziv@2216
|
243 in
|
ziv@2216
|
244 (cmp, qa e1, qa e2)
|
ziv@2216
|
245 end
|
ziv@2216
|
246 fun negateCmp (cmp, e1, e2) =
|
ziv@2216
|
247 (case cmp of
|
ziv@2216
|
248 Sql.Eq => Sql.Ne
|
ziv@2216
|
249 | Sql.Ne => Sql.Eq
|
ziv@2216
|
250 | Sql.Lt => Sql.Ge
|
ziv@2216
|
251 | Sql.Le => Sql.Gt
|
ziv@2216
|
252 | Sql.Gt => Sql.Le
|
ziv@2216
|
253 | Sql.Ge => Sql.Lt,
|
ziv@2216
|
254 e1, e2)
|
ziv@2216
|
255 val markQuery = mapFormula (toAtomExps QueryArg)
|
ziv@2216
|
256 val markDml = mapFormula (toAtomExps DmlRel)
|
ziv@2216
|
257 val dnf = normalize negateCmp Dnf (Combo (Cnf, [markQuery fQuery, markDml fDml]))
|
ziv@2216
|
258 (* If one of the terms in a conjunction leads to a contradiction, which
|
ziv@2216
|
259 is represented by [NONE], drop the entire conjunction. *)
|
ziv@2216
|
260 val sequenceOption = List.foldr (fn (SOME x, SOME xs) => SOME (x :: xs) | _ => NONE)
|
ziv@2216
|
261 (SOME [])
|
ziv@2213
|
262 in
|
ziv@2216
|
263 List.mapPartial (sequenceOption o map eqsOfClass o equivClasses) dnf
|
ziv@2213
|
264 end
|
ziv@2213
|
265
|
ziv@2216
|
266 val rec sqexpToFormula =
|
ziv@2216
|
267 fn Sql.SqTrue => Combo (Cnf, [])
|
ziv@2216
|
268 | Sql.SqFalse => Combo (Dnf, [])
|
ziv@2216
|
269 | Sql.SqNot e => Negate (sqexpToFormula e)
|
ziv@2216
|
270 | Sql.Binop (Sql.RCmp c, e1, e2) => Atom (c, e1, e2)
|
ziv@2216
|
271 | Sql.Binop (Sql.RLop l, p1, p2) => Combo (case l of Sql.And => Cnf | Sql.Or => Dnf,
|
ziv@2216
|
272 [sqexpToFormula p1, sqexpToFormula p2])
|
ziv@2216
|
273 (* ASK: any other sqexps that can be props? *)
|
ziv@2216
|
274 | _ => raise Match
|
ziv@2213
|
275
|
ziv@2216
|
276 val rec queryToFormula =
|
ziv@2216
|
277 fn Sql.Query1 {From = tablePairs, Where = NONE, ...} => Combo (Cnf, [])
|
ziv@2216
|
278 | Sql.Query1 {From = tablePairs, Where = SOME e, ...} =>
|
ziv@2216
|
279 let
|
ziv@2216
|
280 fun renameString table =
|
ziv@2216
|
281 case List.find (fn (_, t) => table = t) tablePairs of
|
ziv@2216
|
282 NONE => table
|
ziv@2216
|
283 | SOME (realTable, _) => realTable
|
ziv@2216
|
284 val renameSqexp =
|
ziv@2216
|
285 fn Sql.Field (table, field) => Sql.Field (renameString table, field)
|
ziv@2216
|
286 | e => e
|
ziv@2216
|
287 fun renameAtom (cmp, e1, e2) = (cmp, renameSqexp e1, renameSqexp e2)
|
ziv@2216
|
288 in
|
ziv@2216
|
289 mapFormula renameAtom (sqexpToFormula e)
|
ziv@2216
|
290 end
|
ziv@2216
|
291 | Sql.Union (q1, q2) => Combo (Dnf, [queryToFormula q1, queryToFormula q2])
|
ziv@2216
|
292
|
ziv@2216
|
293 val rec dmlToFormula =
|
ziv@2216
|
294 fn Sql.Insert (table, vals) =>
|
ziv@2216
|
295 Combo (Cnf, map (fn (field, v) => Atom (Sql.Eq, Sql.Field (table, field), v)) vals)
|
ziv@2216
|
296 | Sql.Delete (_, wher) => sqexpToFormula wher
|
ziv@2216
|
297 (* TODO: refine formula for the vals part, which could take into account the wher part. *)
|
ziv@2216
|
298 | Sql.Update (table, vals, wher) => Combo (Dnf, [dmlToFormula (Sql.Insert (table, vals)),
|
ziv@2216
|
299 dmlToFormula (Sql.Delete (table, wher))])
|
ziv@2213
|
300
|
ziv@2213
|
301 val rec tablesQuery =
|
ziv@2216
|
302 fn Sql.Query1 {From = tablePairs, ...} => SS.fromList (map #1 tablePairs)
|
ziv@2216
|
303 | Sql.Union (q1, q2) => SS.union (tablesQuery q1, tablesQuery q2)
|
ziv@2213
|
304
|
ziv@2213
|
305 val tableDml =
|
ziv@2216
|
306 fn Sql.Insert (tab, _) => tab
|
ziv@2216
|
307 | Sql.Delete (tab, _) => tab
|
ziv@2216
|
308 | Sql.Update (tab, _, _) => tab
|
ziv@2213
|
309
|
ziv@2213
|
310
|
ziv@2213
|
311 (* Program instrumentation. *)
|
ziv@2213
|
312
|
ziv@2215
|
313 fun stringExp s = (EPrim (Prim.String (Prim.Normal, s)), ErrorMsg.dummySpan)
|
ziv@2216
|
314
|
ziv@2213
|
315 val stringTyp = (TFfi ("Basis", "string"), ErrorMsg.dummySpan)
|
ziv@2213
|
316
|
ziv@2213
|
317 val sequence =
|
ziv@2213
|
318 fn (exp :: exps) =>
|
ziv@2213
|
319 let
|
ziv@2213
|
320 val loc = ErrorMsg.dummySpan
|
ziv@2213
|
321 in
|
ziv@2213
|
322 List.foldl (fn (e', seq) => ESeq ((seq, loc), (e', loc))) exp exps
|
ziv@2213
|
323 end
|
ziv@2213
|
324 | _ => raise Match
|
ziv@2213
|
325
|
ziv@2213
|
326 fun ffiAppCache' (func, index, args) : Mono.exp' =
|
ziv@2213
|
327 EFfiApp ("Sqlcache", func ^ Int.toString index, args)
|
ziv@2213
|
328
|
ziv@2215
|
329 fun ffiAppCache (func, index, args) : Mono.exp =
|
ziv@2213
|
330 (ffiAppCache' (func, index, args), ErrorMsg.dummySpan)
|
ziv@2213
|
331
|
ziv@2213
|
332 val varPrefix = "queryResult"
|
ziv@2213
|
333
|
ziv@2213
|
334 fun indexOfName varName =
|
ziv@2213
|
335 if String.isPrefix varPrefix varName
|
ziv@2213
|
336 then Int.fromString (String.extract (varName, String.size varPrefix, NONE))
|
ziv@2213
|
337 else NONE
|
ziv@2213
|
338
|
ziv@2215
|
339 (* Always increments negative indices because that's what we need later. *)
|
ziv@2215
|
340 fun incRelsBound bound inc =
|
ziv@2215
|
341 MonoUtil.Exp.mapB
|
ziv@2215
|
342 {typ = fn x => x,
|
ziv@2215
|
343 exp = fn level =>
|
ziv@2215
|
344 (fn ERel n => ERel (if n >= level orelse n < 0 then n + inc else n)
|
ziv@2215
|
345 | x => x),
|
ziv@2215
|
346 bind = fn (level, MonoUtil.Exp.RelE _) => level + 1 | (level, _) => level}
|
ziv@2215
|
347 bound
|
ziv@2215
|
348
|
ziv@2215
|
349 val incRels = incRelsBound 0
|
ziv@2213
|
350
|
ziv@2216
|
351 (* Filled in by instrumentQuery during [Monoize], used during [Sqlcache]. *)
|
ziv@2213
|
352 val urlifiedRel0s : Mono.exp IM.map ref = ref IM.empty
|
ziv@2213
|
353
|
ziv@2216
|
354 (* Used by [Monoize]. *)
|
ziv@2213
|
355 val instrumentQuery =
|
ziv@2213
|
356 let
|
ziv@2213
|
357 val nextQuery = ref 0
|
ziv@2213
|
358 fun iq (query, urlifiedRel0) =
|
ziv@2213
|
359 case query of
|
ziv@2213
|
360 (EQuery {state = typ, ...}, loc) =>
|
ziv@2213
|
361 let
|
ziv@2213
|
362 val i = !nextQuery before nextQuery := !nextQuery + 1
|
ziv@2213
|
363 in
|
ziv@2213
|
364 urlifiedRel0s := IM.insert (!urlifiedRel0s, i, urlifiedRel0);
|
ziv@2213
|
365 (ELet (varPrefix ^ Int.toString i, typ, query,
|
ziv@2213
|
366 (* Uses a dummy FFI call to keep the urlified expression around, which
|
ziv@2213
|
367 in turn keeps the declarations required for urlification safe from
|
ziv@2216
|
368 [MonoShake]. The dummy call is removed during [Sqlcache]. *)
|
ziv@2216
|
369 (* TODO: thread a [Monoize.Fm.t] through this module. *)
|
ziv@2216
|
370 (ESeq ((EFfiApp ("Sqlcache",
|
ziv@2216
|
371 "dummy",
|
ziv@2216
|
372 [(urlifiedRel0, stringTyp)]),
|
ziv@2216
|
373 loc),
|
ziv@2213
|
374 (ERel 0, loc)),
|
ziv@2213
|
375 loc)),
|
ziv@2213
|
376 loc)
|
ziv@2213
|
377 end
|
ziv@2213
|
378 | _ => raise Match
|
ziv@2213
|
379 in
|
ziv@2213
|
380 iq
|
ziv@2213
|
381 end
|
ziv@2213
|
382
|
ziv@2216
|
383 fun cacheWrap (query, i, urlifiedRel0, args) =
|
ziv@2213
|
384 case query of
|
ziv@2213
|
385 (EQuery {state = typ, ...}, _) =>
|
ziv@2213
|
386 let
|
ziv@2216
|
387 val () = ffiInfo := {index = i, params = length args} :: !ffiInfo
|
ziv@2213
|
388 val loc = ErrorMsg.dummySpan
|
ziv@2215
|
389 (* We ensure before this step that all arguments aren't effectful.
|
ziv@2215
|
390 by turning them into local variables as needed. *)
|
ziv@2216
|
391 val argTyps = map (fn e => (e, stringTyp)) args
|
ziv@2216
|
392 val argTypsInc = map (fn (e, typ) => (incRels 1 e, typ)) argTyps
|
ziv@2216
|
393 val check = ffiAppCache ("check", i, argTyps)
|
ziv@2216
|
394 val store = ffiAppCache ("store", i, (urlifiedRel0, stringTyp) :: argTypsInc)
|
ziv@2215
|
395 val rel0 = (ERel 0, loc)
|
ziv@2213
|
396 in
|
ziv@2215
|
397 (ECase (check,
|
ziv@2213
|
398 [((PNone stringTyp, loc),
|
ziv@2215
|
399 (ELet ("q", typ, query, (ESeq (store, rel0), loc)), loc)),
|
ziv@2213
|
400 ((PSome (stringTyp, (PVar ("hit", stringTyp), loc)), loc),
|
ziv@2215
|
401 (* Boolean is false because we're not unurlifying from a cookie. *)
|
ziv@2215
|
402 (EUnurlify (rel0, typ, false), loc))],
|
ziv@2213
|
403 {disc = stringTyp, result = typ}),
|
ziv@2213
|
404 loc)
|
ziv@2213
|
405 end
|
ziv@2213
|
406 | _ => raise Match
|
ziv@2213
|
407
|
ziv@2213
|
408 fun fileMapfold doExp file start =
|
ziv@2213
|
409 case MonoUtil.File.mapfold {typ = Search.return2,
|
ziv@2213
|
410 exp = fn x => (fn s => Search.Continue (doExp x s)),
|
ziv@2213
|
411 decl = Search.return2} file start of
|
ziv@2213
|
412 Search.Continue x => x
|
ziv@2213
|
413 | Search.Return _ => raise Match
|
ziv@2213
|
414
|
ziv@2213
|
415 fun fileMap doExp file = #1 (fileMapfold (fn x => fn _ => (doExp x, ())) file ())
|
ziv@2213
|
416
|
ziv@2215
|
417 fun addChecking file =
|
ziv@2213
|
418 let
|
ziv@2213
|
419 fun doExp queryInfo =
|
ziv@2215
|
420 fn e' as ELet (v, t,
|
ziv@2215
|
421 queryExp' as (EQuery {query = origQueryText,
|
ziv@2215
|
422 initial, body, state, tables, exps}, queryLoc),
|
ziv@2215
|
423 letBody) =>
|
ziv@2213
|
424 let
|
ziv@2215
|
425 val loc = ErrorMsg.dummySpan
|
ziv@2216
|
426 val chunks = Sql.chunkify origQueryText
|
ziv@2215
|
427 fun strcat (e1, e2) = (EStrcat (e1, e2), loc)
|
ziv@2215
|
428 val (newQueryText, newVariables) =
|
ziv@2215
|
429 (* Important that this is foldr (to oppose foldl below). *)
|
ziv@2215
|
430 List.foldr
|
ziv@2215
|
431 (fn (chunk, (qText, newVars)) =>
|
ziv@2216
|
432 (* Variable bound to the head of newBs will have the lowest index. *)
|
ziv@2215
|
433 case chunk of
|
ziv@2216
|
434 Sql.Exp (e as (EPrim _, _)) => (strcat (e, qText), newVars)
|
ziv@2216
|
435 | Sql.Exp e =>
|
ziv@2215
|
436 let
|
ziv@2215
|
437 val n = length newVars
|
ziv@2215
|
438 in
|
ziv@2215
|
439 (* This is the (n + 1)th new variable, so
|
ziv@2215
|
440 there are already n new variables bound,
|
ziv@2215
|
441 so we increment indices by n. *)
|
ziv@2215
|
442 (strcat ((ERel (~(n+1)), loc), qText), incRels n e :: newVars)
|
ziv@2215
|
443 end
|
ziv@2216
|
444 | Sql.String s => (strcat (stringExp s, qText), newVars))
|
ziv@2215
|
445 (stringExp "", [])
|
ziv@2215
|
446 chunks
|
ziv@2215
|
447 fun wrapLets e' =
|
ziv@2215
|
448 (* Important that this is foldl (to oppose foldr above). *)
|
ziv@2216
|
449 List.foldl (fn (v, e') => ELet ("sqlArgz", stringTyp, v, (e', loc)))
|
ziv@2216
|
450 e'
|
ziv@2216
|
451 newVariables
|
ziv@2216
|
452 val numArgs = length newVariables
|
ziv@2215
|
453 (* Increment once for each new variable just made. *)
|
ziv@2215
|
454 val queryExp = incRels (length newVariables)
|
ziv@2215
|
455 (EQuery {query = newQueryText,
|
ziv@2215
|
456 initial = initial,
|
ziv@2215
|
457 body = body,
|
ziv@2215
|
458 state = state,
|
ziv@2215
|
459 tables = tables,
|
ziv@2215
|
460 exps = exps},
|
ziv@2215
|
461 queryLoc)
|
ziv@2215
|
462 val (EQuery {query = queryText, ...}, _) = queryExp
|
ziv@2215
|
463 (* val () = Print.preface ("sqlcache> ", (MonoPrint.p_exp MonoEnv.empty queryText)); *)
|
ziv@2216
|
464 val args = List.tabulate (numArgs, fn n => (ERel n, loc))
|
ziv@2213
|
465 fun bind x f = Option.mapPartial f x
|
ziv@2215
|
466 fun guard b x = if b then x else NONE
|
ziv@2215
|
467 (* DEBUG: set first boolean argument to true to turn on printing. *)
|
ziv@2215
|
468 fun safe bound = not o effectful true (effectfulMap file) false bound
|
ziv@2213
|
469 val attempt =
|
ziv@2213
|
470 (* Ziv misses Haskell's do notation.... *)
|
ziv@2215
|
471 guard (safe 0 queryText andalso safe 0 initial andalso safe 2 body) (
|
ziv@2216
|
472 bind (Sql.parse Sql.query queryText) (fn queryParsed =>
|
ziv@2213
|
473 bind (indexOfName v) (fn i =>
|
ziv@2213
|
474 bind (IM.find (!urlifiedRel0s, i)) (fn urlifiedRel0 =>
|
ziv@2215
|
475 SOME (wrapLets (ELet (v, t,
|
ziv@2216
|
476 cacheWrap (queryExp, i, urlifiedRel0, args),
|
ziv@2215
|
477 incRelsBound 1 (length newVariables) letBody)),
|
ziv@2213
|
478 SS.foldr (fn (tab, qi) => SIMM.insert (qi, tab, i))
|
ziv@2213
|
479 queryInfo
|
ziv@2216
|
480 (tablesQuery queryParsed))))))
|
ziv@2213
|
481 in
|
ziv@2213
|
482 case attempt of
|
ziv@2213
|
483 SOME pair => pair
|
ziv@2213
|
484 | NONE => (e', queryInfo)
|
ziv@2213
|
485 end
|
ziv@2213
|
486 | ESeq ((EFfiApp ("Sqlcache", "dummy", _), _), (e', _)) => (e', queryInfo)
|
ziv@2213
|
487 | e' => (e', queryInfo)
|
ziv@2213
|
488 in
|
ziv@2215
|
489 fileMapfold (fn exp => fn state => doExp state exp) file SIMM.empty
|
ziv@2213
|
490 end
|
ziv@2213
|
491
|
ziv@2216
|
492 fun invalidations (nQueryArgs, query, dml) =
|
ziv@2216
|
493 let
|
ziv@2216
|
494 val loc = ErrorMsg.dummySpan
|
ziv@2216
|
495 val optionToExp =
|
ziv@2216
|
496 fn NONE => (ENone stringTyp, loc)
|
ziv@2216
|
497 | SOME e => (ESome (stringTyp, (e, loc)), loc)
|
ziv@2216
|
498 fun eqsToInvalidation eqs =
|
ziv@2216
|
499 let
|
ziv@2216
|
500 fun inv n = if n < 0 then [] else optionToExp (IM.find (eqs, n)) :: inv (n - 1)
|
ziv@2216
|
501 in
|
ziv@2216
|
502 inv (nQueryArgs - 1)
|
ziv@2216
|
503 end
|
ziv@2216
|
504 in
|
ziv@2216
|
505 map (map eqsToInvalidation) (conflictMaps (queryToFormula query, dmlToFormula dml))
|
ziv@2216
|
506 end
|
ziv@2216
|
507
|
ziv@2213
|
508 fun addFlushing (file, queryInfo) =
|
ziv@2213
|
509 let
|
ziv@2213
|
510 val allIndices : int list = SM.foldr (fn (x, acc) => IS.listItems x @ acc) [] queryInfo
|
ziv@2213
|
511 fun flushes indices = map (fn i => ffiAppCache' ("flush", i, [])) indices
|
ziv@2213
|
512 val doExp =
|
ziv@2213
|
513 fn dmlExp as EDml (dmlText, _) =>
|
ziv@2213
|
514 let
|
ziv@2213
|
515 val indices =
|
ziv@2216
|
516 case Sql.parse Sql.dml dmlText of
|
ziv@2213
|
517 SOME dmlParsed => SIMM.findList (queryInfo, tableDml dmlParsed)
|
ziv@2213
|
518 | NONE => allIndices
|
ziv@2213
|
519 in
|
ziv@2213
|
520 sequence (flushes indices @ [dmlExp])
|
ziv@2213
|
521 end
|
ziv@2213
|
522 | e' => e'
|
ziv@2213
|
523 in
|
ziv@2213
|
524 fileMap doExp file
|
ziv@2213
|
525 end
|
ziv@2213
|
526
|
ziv@2213
|
527 fun go file =
|
ziv@2213
|
528 let
|
ziv@2213
|
529 val () = Sql.sqlcacheMode := true
|
ziv@2215
|
530 val file' = addFlushing (addChecking file)
|
ziv@2215
|
531 val () = Sql.sqlcacheMode := false
|
ziv@2213
|
532 in
|
ziv@2215
|
533 file'
|
ziv@2213
|
534 end
|
ziv@2213
|
535
|
ziv@2209
|
536 end
|