aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--caching-tests/test.dbbin0 -> 3072 bytes
-rw-r--r--caching-tests/test.sql11
-rw-r--r--caching-tests/test.ur52
-rw-r--r--caching-tests/test.urp7
-rw-r--r--caching-tests/test.urs6
-rw-r--r--include/urweb/urweb_cpp.h4
-rw-r--r--src/c/urweb.c13
-rw-r--r--src/cjr_print.sml66
-rw-r--r--src/compiler.sig9
-rw-r--r--src/compiler.sml20
-rw-r--r--src/main.mlton.sml12
-rw-r--r--src/multimap_fn.sml14
-rw-r--r--src/sources6
-rw-r--r--src/sql.sig91
-rw-r--r--src/sql.sml28
-rw-r--r--src/sqlcache.sig6
-rw-r--r--src/sqlcache.sml182
17 files changed, 489 insertions, 38 deletions
diff --git a/caching-tests/test.db b/caching-tests/test.db
new file mode 100644
index 00000000..190d2868
--- /dev/null
+++ b/caching-tests/test.db
Binary files differ
diff --git a/caching-tests/test.sql b/caching-tests/test.sql
new file mode 100644
index 00000000..862245b7
--- /dev/null
+++ b/caching-tests/test.sql
@@ -0,0 +1,11 @@
+CREATE TABLE uw_Test_foo01(uw_id integer NOT NULL, uw_bar text NOT NULL,
+ PRIMARY KEY (uw_id)
+
+ );
+
+ CREATE TABLE uw_Test_foo10(uw_id integer NOT NULL, uw_bar text NOT NULL,
+ PRIMARY KEY (uw_id)
+
+ );
+
+ \ No newline at end of file
diff --git a/caching-tests/test.ur b/caching-tests/test.ur
new file mode 100644
index 00000000..a99a387b
--- /dev/null
+++ b/caching-tests/test.ur
@@ -0,0 +1,52 @@
+table foo01 : {Id : int, Bar : string} PRIMARY KEY Id
+table foo10 : {Id : int, Bar : string} PRIMARY KEY Id
+
+fun flush01 () : transaction page =
+ dml (UPDATE foo01 SET Bar = "baz01" WHERE Id = 42);
+ return <xml><body>
+ Flushed 1!
+ </body></xml>
+
+fun flush10 () : transaction page =
+ dml (UPDATE foo10 SET Bar = "baz10" WHERE Id = 42);
+ return <xml><body>
+ Flushed 2!
+ </body></xml>
+
+fun flush11 () : transaction page =
+ dml (UPDATE foo01 SET Bar = "baz11" WHERE Id = 42);
+ dml (UPDATE foo10 SET Bar = "baz11" WHERE Id = 42);
+ return <xml><body>
+ Flushed 1 and 2!
+ </body></xml>
+
+fun cache01 () : transaction page =
+ res <- oneOrNoRows (SELECT foo01.Bar FROM foo01 WHERE foo01.Id = 42);
+ return <xml><body>
+ Reading 1.
+ {case res of
+ None => <xml></xml>
+ | Some row => <xml>{[row.Foo01.Bar]}</xml>}
+ </body></xml>
+
+fun cache10 () : transaction page =
+ res <- oneOrNoRows (SELECT foo10.Bar FROM foo10 WHERE foo10.Id = 42);
+ return <xml><body>
+ Reading 2.
+ {case res of
+ None => <xml></xml>
+ | Some row => <xml>{[row.Foo10.Bar]}</xml>}
+ </body></xml>
+
+fun cache11 () : transaction page =
+ res <- oneOrNoRows (SELECT foo01.Bar FROM foo01 WHERE foo01.Id = 42);
+ bla <- oneOrNoRows (SELECT foo10.Bar FROM foo10 WHERE foo10.Id = 42);
+ return <xml><body>
+ Reading 1 and 2.
+ {case res of
+ None => <xml></xml>
+ | Some row => <xml>{[row.Foo01.Bar]}</xml>}
+ {case bla of
+ None => <xml></xml>
+ | Some row => <xml>{[row.Foo10.Bar]}</xml>}
+ </body></xml>
diff --git a/caching-tests/test.urp b/caching-tests/test.urp
new file mode 100644
index 00000000..123f58e5
--- /dev/null
+++ b/caching-tests/test.urp
@@ -0,0 +1,7 @@
+database test.db
+sql test.sql
+safeGet Test/flush01
+safeGet Test/flush10
+safeGet Test/flush11
+
+test
diff --git a/caching-tests/test.urs b/caching-tests/test.urs
new file mode 100644
index 00000000..ce7d0350
--- /dev/null
+++ b/caching-tests/test.urs
@@ -0,0 +1,6 @@
+val cache01 : unit -> transaction page
+val cache10 : unit -> transaction page
+val cache11 : unit -> transaction page
+val flush01 : unit -> transaction page
+val flush10 : unit -> transaction page
+val flush11 : unit -> transaction page
diff --git a/include/urweb/urweb_cpp.h b/include/urweb/urweb_cpp.h
index d83b2cbb..39dc0bc0 100644
--- a/include/urweb/urweb_cpp.h
+++ b/include/urweb/urweb_cpp.h
@@ -77,6 +77,10 @@ int uw_next_entry(struct uw_context *);
void uw_write(struct uw_context *, const char*);
+// For caching.
+void uw_recordingStart(struct uw_context *);
+char *uw_recordingRead(struct uw_context *);
+
uw_Basis_source uw_Basis_new_client_source(struct uw_context *, uw_Basis_string);
uw_unit uw_Basis_set_client_source(struct uw_context *, uw_Basis_source, uw_Basis_string);
diff --git a/src/c/urweb.c b/src/c/urweb.c
index d7bc05e3..51ce2735 100644
--- a/src/c/urweb.c
+++ b/src/c/urweb.c
@@ -476,6 +476,9 @@ struct uw_context {
char *output_buffer;
size_t output_buffer_size;
+
+ // For caching.
+ char *recording;
};
size_t uw_headers_max = SIZE_MAX;
@@ -559,6 +562,8 @@ uw_context uw_init(int id, uw_loggers *lg) {
ctx->output_buffer = malloc(1);
ctx->output_buffer_size = 1;
+ ctx->recording = 0;
+
return ctx;
}
@@ -1666,6 +1671,14 @@ void uw_write(uw_context ctx, const char* s) {
*ctx->page.front = 0;
}
+void uw_recordingStart(uw_context ctx) {
+ ctx->recording = ctx->page.front;
+}
+
+char *uw_recordingRead(uw_context ctx) {
+ return strdup(ctx->recording);
+}
+
char *uw_Basis_attrifyInt(uw_context ctx, uw_Basis_int n) {
char *result;
int len;
diff --git a/src/cjr_print.sml b/src/cjr_print.sml
index 0867f001..b2e8d2a7 100644
--- a/src/cjr_print.sml
+++ b/src/cjr_print.sml
@@ -16,7 +16,7 @@
* AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+ * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
* CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
* SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
* INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
@@ -734,7 +734,7 @@ fun unurlify fromClient env (t, loc) =
string (Int.toString (size has_arg)),
string ", ((*request)[0] == '/' ? ++*request : NULL), ",
newline,
-
+
if unboxable then
unurlify' "(*request)" (#1 t)
else
@@ -914,7 +914,7 @@ fun unurlify fromClient env (t, loc) =
space,
string "4, ((*request)[0] == '/' ? ++*request : NULL), ",
newline,
-
+
string "({",
newline,
p_typ env (t, loc),
@@ -1188,7 +1188,7 @@ fun urlify env t =
string "(ctx,",
space,
string "it",
- string (Int.toString level),
+ string (Int.toString level),
string ");",
newline]
else
@@ -1388,7 +1388,7 @@ fun urlify env t =
string (Int.toString level),
string ");",
newline])
-
+
| _ => (ErrorMsg.errorAt loc "Unable to choose a URL encoding function";
space)
in
@@ -1578,7 +1578,7 @@ and p_exp' par tail env (e, loc) =
newline],
string "tmp;",
newline,
- string "})"]
+ string "})"]
end
| ENone _ => string "NULL"
| ESome (t, e) =>
@@ -2078,7 +2078,7 @@ and p_exp' par tail env (e, loc) =
space,
p_exp' false false (E.pushERel
(E.pushERel env "r" (TRecord rnum, loc))
- "acc" state)
+ "acc" state)
body,
string ";",
newline]
@@ -2102,7 +2102,7 @@ and p_exp' par tail env (e, loc) =
newline,
string "uw_ensure_transaction(ctx);",
newline,
-
+
case prepared of
NONE =>
box [string "char *query = ",
@@ -2187,7 +2187,7 @@ and p_exp' par tail env (e, loc) =
string "uw_ensure_transaction(ctx);",
newline,
newline,
-
+
#dmlPrepared (Settings.currentDbms ()) {loc = loc,
id = id,
dml = dml',
@@ -3393,6 +3393,50 @@ fun p_file env (ds, ps) =
newline,
newline,
+ (* For caching. *)
+ box (List.map
+ (fn index =>
+ let val i = Int.toString index
+ in box [string "static char *cache",
+ string i,
+ string " = NULL;",
+ newline,
+ string "static uw_Basis_bool uw_Cache_check",
+ string i,
+ string "(uw_context ctx) { puts(\"Checked cache ",
+ string i,
+ string ".\"); if (cache",
+ string i,
+ string " == NULL) { uw_recordingStart(ctx); return uw_Basis_False; } else { uw_write(ctx, cache",
+ string i,
+ string "); return uw_Basis_True; } };",
+ newline,
+ string "static uw_unit uw_Cache_store",
+ string i,
+ string "(uw_context ctx) { cache",
+ string i,
+ string " = uw_recordingRead(ctx); puts(\"Stored cache ",
+ string i,
+ string ".\"); return uw_unit_v; };",
+ newline,
+ string "static uw_unit uw_Cache_flush",
+ string i,
+ string "(uw_context ctx) { free(cache",
+ string i,
+ string "); cache",
+ string i,
+ string " = NULL; puts(\"Flushed cache ",
+ string i,
+ string ".\"); return uw_unit_v; };",
+ newline,
+ string "static uw_unit uw_Cache_ready",
+ string i,
+ string "(uw_context ctx) { return uw_unit_v; };",
+ newline,
+ newline]
+ end)
+ (!Sqlcache.ffiIndices)),
+ newline,
p_list_sep newline (fn x => x) pds,
newline,
@@ -3448,7 +3492,7 @@ fun p_file env (ds, ps) =
makeChecker ("uw_check_envVar", Settings.getEnvVarRules ()),
newline,
-
+
string "extern void uw_sign(const char *in, char *out);",
newline,
string "extern int uw_hash_blocksize;",
@@ -3495,7 +3539,7 @@ fun p_file env (ds, ps) =
newline,
string ("uw_write_header(ctx, \"Last-Modified: " ^ Date.fmt rfcFmt nowD ^ "\\r\\n\");"),
newline,
- string ("uw_write_header(ctx, \"Cache-Control: max-age=31536000, public\\r\\n\");"),
+ string ("uw_write_header(ctx, \"Cache-Control: max-age=31536000, public\\r\\n\");"),
newline,
string "uw_write(ctx, jslib);",
newline,
diff --git a/src/compiler.sig b/src/compiler.sig
index d74ec533..fb0245ea 100644
--- a/src/compiler.sig
+++ b/src/compiler.sig
@@ -16,7 +16,7 @@
* AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+ * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
* CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
* SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
* INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
@@ -122,6 +122,7 @@ signature COMPILER = sig
val pathcheck : (Mono.file, Mono.file) phase
val sidecheck : (Mono.file, Mono.file) phase
val sigcheck : (Mono.file, Mono.file) phase
+ val sqlcache : (Mono.file, Mono.file) phase
val cjrize : (Mono.file, Cjr.file) phase
val prepare : (Cjr.file, Cjr.file) phase
val checknest : (Cjr.file, Cjr.file) phase
@@ -137,12 +138,12 @@ signature COMPILER = sig
val toCorify : (string, Core.file) transform
val toCore_untangle : (string, Core.file) transform
val toShake1 : (string, Core.file) transform
- val toEspecialize1' : (string, Core.file) transform
+ val toEspecialize1' : (string, Core.file) transform
val toShake1' : (string, Core.file) transform
val toRpcify : (string, Core.file) transform
val toCore_untangle2 : (string, Core.file) transform
val toShake2 : (string, Core.file) transform
- val toEspecialize1 : (string, Core.file) transform
+ val toEspecialize1 : (string, Core.file) transform
val toCore_untangle3 : (string, Core.file) transform
val toShake3 : (string, Core.file) transform
val toTag : (string, Core.file) transform
@@ -187,6 +188,7 @@ signature COMPILER = sig
val toPathcheck : (string, Mono.file) transform
val toSidecheck : (string, Mono.file) transform
val toSigcheck : (string, Mono.file) transform
+ val toSqlcache : (string, Mono.file) transform
val toCjrize : (string, Cjr.file) transform
val toPrepare : (string, Cjr.file) transform
val toChecknest : (string, Cjr.file) transform
@@ -197,6 +199,7 @@ signature COMPILER = sig
val enableBoot : unit -> unit
val doIflow : bool ref
+ val doSqlcache : bool ref
val addPath : string * string -> unit
val addModuleRoot : string * string -> unit
diff --git a/src/compiler.sml b/src/compiler.sml
index b46643ff..d7ee8700 100644
--- a/src/compiler.sml
+++ b/src/compiler.sml
@@ -16,7 +16,7 @@
* AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+ * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
* CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
* SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
* INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
@@ -25,7 +25,7 @@
* POSSIBILITY OF SUCH DAMAGE.
*)
-structure Compiler :> COMPILER = struct
+structure Compiler :> COMPILER = struct
structure UrwebLrVals = UrwebLrValsFn(structure Token = LrParser.Token)
structure Lex = UrwebLexFn(structure Tokens = UrwebLrVals.Tokens)
@@ -83,6 +83,7 @@ type ('src, 'dst) transform = {
val debug = ref false
val dumpSource = ref false
val doIflow = ref false
+val doSqlcache = ref false
val doDumpSource = ref (fn () => ())
@@ -268,7 +269,7 @@ val parseUr = {
| _ => absyn
end
handle LrParser.ParseError => [],
- print = SourcePrint.p_file}
+ print = SourcePrint.p_file}
fun p_job ({prefix, database, exe, sql, sources, debug, profile,
timeout, ffi, link, headers, scripts,
@@ -1100,7 +1101,7 @@ val parse = {
ErrorMsg.error ("Rooted module " ^ full ^ " has multiple versions.")
else
();
-
+
makeD true "" pieces
before ignore (foldl (fn (new, path) =>
let
@@ -1455,12 +1456,19 @@ val sigcheck = {
val toSigcheck = transform sigcheck "sigcheck" o toSidecheck
+val sqlcache = {
+ func = (fn file => (if !doSqlcache then Sqlcache.go file else file)),
+ print = MonoPrint.p_file MonoEnv.empty
+}
+
+val toSqlcache = transform sqlcache "sqlcache" o toSigcheck
+
val cjrize = {
func = Cjrize.cjrize,
print = CjrPrint.p_file CjrEnv.empty
}
-val toCjrize = transform cjrize "cjrize" o toSigcheck
+val toCjrize = transform cjrize "cjrize" o toSqlcache
val prepare = {
func = Prepare.prepare,
@@ -1616,7 +1624,7 @@ fun compile job =
compileC {cname = cname, oname = oname, ename = ename, libs = libs,
profile = #profile job, debug = #debug job, linker = #linker job, link = #link job}
-
+
before cleanup ())
end
handle ex => (((cleanup ()) handle _ => ()); raise ex)
diff --git a/src/main.mlton.sml b/src/main.mlton.sml
index bfc18e59..5ecd7290 100644
--- a/src/main.mlton.sml
+++ b/src/main.mlton.sml
@@ -16,7 +16,7 @@
* AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
+ * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
* CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
* SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
* INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
@@ -47,6 +47,7 @@ fun oneRun args =
Elaborate.unifyMore := false;
Compiler.dumpSource := false;
Compiler.doIflow := false;
+ Compiler.doSqlcache := false;
Demo.noEmacs := false;
Settings.setDebug false)
@@ -64,7 +65,7 @@ fun oneRun args =
fun doArgs args =
case args of
[] => ()
- | "-version" :: rest =>
+ | "-version" :: rest =>
printVersion ()
| "-numeric-version" :: rest =>
printNumericVersion ()
@@ -159,6 +160,9 @@ fun oneRun args =
| "-iflow" :: rest =>
(Compiler.doIflow := true;
doArgs rest)
+ | "-sqlcache" :: rest =>
+ (Compiler.doSqlcache := true;
+ doArgs rest)
| "-moduleOf" :: fname :: _ =>
(print (Compiler.moduleOf fname ^ "\n");
raise Code OS.Process.success)
@@ -306,7 +310,7 @@ val () = case CommandLine.arguments () of
(* Redirect the daemon's output to the socket. *)
redirect Posix.FileSys.stdout;
redirect Posix.FileSys.stderr;
-
+
loop' ("", []);
Socket.close sock;
@@ -325,7 +329,7 @@ val () = case CommandLine.arguments () of
loop ()
end)
| ["daemon", "stop"] =>
- (OS.FileSys.remove socket handle OS.SysErr _ => OS.Process.exit OS.Process.success)
+ (OS.FileSys.remove socket handle OS.SysErr _ => OS.Process.exit OS.Process.success)
| args =>
let
val sock = UnixSock.Strm.socket ()
diff --git a/src/multimap_fn.sml b/src/multimap_fn.sml
new file mode 100644
index 00000000..585b741f
--- /dev/null
+++ b/src/multimap_fn.sml
@@ -0,0 +1,14 @@
+functor MultimapFn (structure KeyMap : ORD_MAP structure ValSet : ORD_SET) = struct
+ type key = KeyMap.Key.ord_key
+ type item = ValSet.item
+ type items = ValSet.set
+ type multimap = ValSet.set KeyMap.map
+ fun inserts (kToVs : multimap, k : key, vs : items) : multimap =
+ KeyMap.unionWith ValSet.union (kToVs, KeyMap.singleton (k, vs))
+ fun insert (kToVs : multimap, k : key, v : item) : multimap =
+ inserts (kToVs, k, ValSet.singleton v)
+ fun find (kToVs : multimap, k : key) =
+ case KeyMap.find (kToVs, k) of
+ SOME vs => vs
+ | NONE => ValSet.empty
+end
diff --git a/src/sources b/src/sources
index a5235357..8860b310 100644
--- a/src/sources
+++ b/src/sources
@@ -186,6 +186,7 @@ $(SRC)/mono_shake.sml
$(SRC)/fuse.sig
$(SRC)/fuse.sml
+$(SRC)/sql.sig
$(SRC)/sql.sml
$(SRC)/iflow.sig
@@ -206,6 +207,11 @@ $(SRC)/sidecheck.sml
$(SRC)/sigcheck.sig
$(SRC)/sigcheck.sml
+$(SRC)/multimap_fn.sml
+
+$(SRC)/sqlcache.sig
+$(SRC)/sqlcache.sml
+
$(SRC)/cjr.sml
$(SRC)/postgres.sig
diff --git a/src/sql.sig b/src/sql.sig
new file mode 100644
index 00000000..573a8baf
--- /dev/null
+++ b/src/sql.sig
@@ -0,0 +1,91 @@
+signature SQL = sig
+
+val debug : bool ref
+
+type lvar = int
+
+datatype func =
+ DtCon0 of string
+ | DtCon1 of string
+ | UnCon of string
+ | Other of string
+
+datatype exp =
+ Const of Prim.t
+ | Var of int
+ | Lvar of lvar
+ | Func of func * exp list
+ | Recd of (string * exp) list
+ | Proj of exp * string
+
+datatype reln =
+ Known
+ | Sql of string
+ | PCon0 of string
+ | PCon1 of string
+ | Eq
+ | Ne
+ | Lt
+ | Le
+ | Gt
+ | Ge
+
+datatype prop =
+ True
+ | False
+ | Unknown
+ | And of prop * prop
+ | Or of prop * prop
+ | Reln of reln * exp list
+ | Cond of exp * prop
+
+datatype chunk =
+ String of string
+ | Exp of Mono.exp
+
+type 'a parser = chunk list -> ('a * chunk list) option
+
+val parse : 'a parser -> Mono.exp -> 'a option
+
+datatype Rel =
+ Exps of exp * exp -> prop
+ | Props of prop * prop -> prop
+
+datatype sqexp =
+ SqConst of Prim.t
+ | SqTrue
+ | SqFalse
+ | SqNot of sqexp
+ | Field of string * string
+ | Computed of string
+ | Binop of Rel * sqexp * sqexp
+ | SqKnown of sqexp
+ | Inj of Mono.exp
+ | SqFunc of string * sqexp
+ | Unmodeled
+ | Null
+
+datatype ('a,'b) sum = inl of 'a | inr of 'b
+
+datatype sitem =
+ SqField of string * string
+ | SqExp of sqexp * string
+
+type query1 = {Select : sitem list,
+ From : (string * string) list,
+ Where : sqexp option}
+
+datatype query =
+ Query1 of query1
+ | Union of query * query
+
+val query : query parser
+
+datatype dml =
+ Insert of string * (string * sqexp) list
+ | Delete of string * sqexp
+ | Update of string * (string * sqexp) list * sqexp
+
+val dml : dml parser
+
+end
diff --git a/src/sql.sml b/src/sql.sml
index 91e303c3..8d245660 100644
--- a/src/sql.sml
+++ b/src/sql.sml
@@ -1,4 +1,4 @@
-structure Sql = struct
+structure Sql :> SQL = struct
open Mono
@@ -177,10 +177,10 @@ val uw_ident = wrapP ident (fn s => if String.isPrefix "uw_" s andalso size s >=
else
NONE)
-val field = wrap (follow t_ident
- (follow (const ".")
- uw_ident))
- (fn (t, ((), f)) => (t, f))
+val field = wrap (follow (opt (follow t_ident (const ".")))
+ uw_ident)
+ (fn (SOME (t, ()), f) => (t, f)
+ | (NONE, f) => ("T", f)) (* Should probably deal with this MySQL/SQLite case better some day. *)
datatype Rel =
Exps of exp * exp -> prop
@@ -238,7 +238,7 @@ fun string chs =
end
else
NONE
- | _ => NONE
+ | _ => NONE
val prim =
altL [wrap (follow (wrapP (follow (keep Char.isDigit) (follow (const ".") (keep Char.isDigit)))
@@ -267,7 +267,7 @@ fun sqlify chs =
((PCon (_, PConFfi {mod = "Basis", con = "False", ...}, NONE), _),
(EPrim (Prim.String (Prim.Normal, "FALSE")), _))], _), _) :: chs =>
SOME (e, chs)
-
+
| _ => NONE
fun constK s = wrap (const s) (fn () => s)
@@ -317,7 +317,7 @@ fun sqexp chs =
and known chs = wrap (follow known' (follow (const "(") (follow sqexp (const ")"))))
(fn ((), ((), (e, ()))) => e) chs
-
+
and func chs = wrap (follow funcName (follow (const "(") (follow sqexp (const ")"))))
(fn (f, ((), (e, ()))) => (f, e)) chs
@@ -396,22 +396,22 @@ val insert = log "insert"
val delete = log "delete"
(wrap (follow (const "DELETE FROM ")
(follow uw_ident
- (follow (const " AS T_T WHERE ")
+ (follow (follow (opt (const " AS T_T")) (const " WHERE "))
sqexp)))
- (fn ((), (tab, ((), es))) => (tab, es)))
+ (fn ((), (tab, (_, es))) => (tab, es)))
val setting = log "setting"
- (wrap (follow uw_ident (follow (const " = ") sqexp))
- (fn (f, ((), e)) => (f, e)))
+ (wrap (follow uw_ident (follow (const " = ") sqexp))
+ (fn (f, ((), e)) => (f, e)))
val update = log "update"
(wrap (follow (const "UPDATE ")
(follow uw_ident
- (follow (const " AS T_T SET ")
+ (follow (follow (opt (const " AS T_T")) (const " SET "))
(follow (list setting)
(follow (ws (const "WHERE "))
sqexp)))))
- (fn ((), (tab, ((), (fs, ((), e))))) =>
+ (fn ((), (tab, (_, (fs, ((), e))))) =>
(tab, fs, e)))
val dml = log "dml"
diff --git a/src/sqlcache.sig b/src/sqlcache.sig
new file mode 100644
index 00000000..ccc1741a
--- /dev/null
+++ b/src/sqlcache.sig
@@ -0,0 +1,6 @@
+signature SQLCACHE = sig
+
+val ffiIndices : int list ref
+val go : Mono.file -> Mono.file
+
+end
diff --git a/src/sqlcache.sml b/src/sqlcache.sml
new file mode 100644
index 00000000..2e7f6e42
--- /dev/null
+++ b/src/sqlcache.sml
@@ -0,0 +1,182 @@
+structure Sqlcache :> SQLCACHE = struct
+
+open Sql
+open Mono
+
+structure IS = IntBinarySet
+structure IM = IntBinaryMap
+structure StringKey = struct type ord_key = string val compare = String.compare end
+structure SS = BinarySetFn (StringKey)
+structure SM = BinaryMapFn (StringKey)
+structure SIMM = MultimapFn (structure KeyMap = SM structure ValSet = IS)
+
+val ffiIndices : int list ref = ref []
+
+val rec tablesRead =
+ fn Query1 {From=tablePairs, ...} => SS.fromList (map #1 tablePairs)
+ | Union (q1,q2) => SS.union (tablesRead q1, tablesRead q2)
+
+val tableWritten =
+ fn Insert (tab, _) => tab
+ | Delete (tab, _) => tab
+ | Update (tab, _, _) => tab
+
+fun tablesInExp' exp' =
+ let
+ val nothing = {read = SS.empty, written = SS.empty}
+ in
+ case exp' of
+ EQuery {query=e, ...} =>
+ (case parse query e of
+ SOME q => {read = tablesRead q, written = SS.empty}
+ | NONE => nothing)
+ | EDml (e, _) =>
+ (case parse dml e of
+ SOME q => {read = SS.empty, written = SS.singleton (tableWritten q)}
+ | NONE => nothing)
+ | _ => nothing
+ end
+
+val tablesInExp =
+ let
+ fun addTables (exp', {read, written}) =
+ let val {read = r, written = w} = tablesInExp' exp'
+ in {read = SS.union (r, read), written = SS.union (w, written)} end
+ in
+ MonoUtil.Exp.fold {typ = #2, exp = addTables}
+ {read = SS.empty, written = SS.empty}
+ end
+
+fun intExp (n, loc) = (EPrim (Prim.Int (Int64.fromInt n)), loc)
+fun intTyp loc = (TFfi ("Basis", "int"), loc)
+fun boolPat (b, loc) = (PCon (Enum,
+ PConFfi {mod = "Basis", datatyp = "bool", arg = NONE,
+ con = if b then "True" else "False"},
+ NONE),
+ loc)
+fun boolTyp loc = (TFfi ("Basis", "int"), loc)
+
+fun ffiAppExp (module, func, index, loc) =
+ (EFfiApp (module, func ^ Int.toString index, []), loc)
+
+fun sequence (befores, center, afters, loc) =
+ List.foldr (fn (exp, seq) => (ESeq (exp, seq), loc))
+ (List.foldl (fn (exp, seq) => (ESeq (seq, exp), loc))
+ center
+ afters)
+ befores
+
+fun antiguardUnit (cond, exp, loc) =
+ (ECase (cond,
+ [(boolPat (false, loc), exp),
+ (boolPat (true, loc), (ERecord [], loc))],
+ {disc = boolTyp loc, result = (TRecord [], loc)}),
+ loc)
+
+fun underAbs f (exp as (exp', loc)) =
+ case exp' of
+ EAbs (x, y, z, body) => (EAbs (x, y, z, underAbs f body), loc)
+ | _ => f exp
+
+fun addCacheCheck (index, exp) =
+ let
+ fun f (body as (_, loc)) =
+ let
+ val check = ffiAppExp ("Cache", "check", index, loc)
+ val store = ffiAppExp ("Cache", "store", index, loc)
+ in
+ antiguardUnit (check, sequence ([], body, [store], loc), loc)
+ end
+ in
+ underAbs f exp
+ end
+
+fun addCacheFlush (exp, tablesToIndices) =
+ let
+ fun addIndices (table, indices) = IS.union (indices, SIMM.find (tablesToIndices, table))
+ fun f (body as (_, loc)) =
+ let
+ fun mapFfi func = List.map (fn i => ffiAppExp ("Cache", func, i, loc))
+ val flushes =
+ IS.listItems (SS.foldr addIndices IS.empty (#written (tablesInExp body)))
+
+ in
+ sequence (mapFfi "flush" flushes, body, mapFfi "ready" flushes, loc)
+ end
+ in
+ underAbs f exp
+ end
+
+val handlerIndices =
+ let
+ val isUnit =
+ fn (TRecord [], _) => true
+ | _ => false
+ fun maybeAdd (d, soFar as {readers, writers}) =
+ case d of
+ DExport (Link ReadOnly, _, name, typs, typ, _) =>
+ if List.all isUnit (typ::typs)
+ then {readers = IS.add (readers, name), writers = writers}
+ else soFar
+ | DExport (_, _, name, _, _, _) => (* Not read only. *)
+ {readers = readers, writers = IS.add (writers, name)}
+ | _ => soFar
+ in
+ MonoUtil.File.fold {typ = #2, exp = #2, decl = maybeAdd}
+ {readers = IS.empty, writers = IS.empty}
+ end
+
+fun fileFoldMapiSelected f init (file, indices) =
+ let
+ fun doExp (original as ((a, index, b, exp, c), state)) =
+ if IS.member (indices, index)
+ then let val (newExp, newState) = f (index, exp, state)
+ in ((a, index, b, newExp, c), newState) end
+ else original
+ fun doDecl decl state =
+ let
+ val result =
+ case decl of
+ DVal x =>
+ let val (y, newState) = doExp (x, state)
+ in (DVal y, newState) end
+ | DValRec xs =>
+ let val (ys, newState) = ListUtil.foldlMap doExp state xs
+ in (DValRec ys, newState) end
+ | _ => (decl, state)
+ in
+ Search.Continue result
+ end
+ fun nada x y = Search.Continue (x, y)
+ in
+ case MonoUtil.File.mapfold {typ = nada, exp = nada, decl = doDecl} file init of
+ Search.Continue x => x
+ | _ => (file, init) (* Should never happen. *)
+ end
+
+fun fileMapSelected f = #1 o fileFoldMapiSelected (fn (_, x, _) => (f x, ())) ()
+
+val addCacheChecking =
+ let
+ fun f (index, exp, tablesToIndices) =
+ (addCacheCheck (index, exp),
+ SS.foldr (fn (table, tsToIs) => SIMM.insert (tsToIs, table, index))
+ tablesToIndices
+ (#read (tablesInExp exp)))
+ in
+ fileFoldMapiSelected f (SM.empty)
+ end
+
+fun addCacheFlushing (file, tablesToIndices, writers) =
+ fileMapSelected (fn exp => addCacheFlush (exp, tablesToIndices)) (file, writers)
+
+fun go file =
+ let
+ val {readers, writers} = handlerIndices file
+ val (fileWithChecks, tablesToIndices) = addCacheChecking (file, readers)
+ in
+ ffiIndices := IS.listItems readers;
+ addCacheFlushing (fileWithChecks, tablesToIndices, writers)
+ end
+
+end