Add some comments; call 'writeLines' first when updating queue
[filehash.git] / R / queue.R
blobad77409a3aef7af10d2323f5883a47e0ec7cefd1
1 createQ <- function(filename) {
2         dbCreate(filename, "DB1")
3         qdb <- dbInit(filename, "DB1")
5         metaname <- paste(filename, "head", sep = ".")
6         file.create(metaname)
8         list(qdb = qdb, meta = metaname, name = filename)
11 initQ <- function(filename) {
12         list(qdb = dbInit(filename, "DB1"),
13              meta = paste(filename, "head", sep = "."),
14              name = filename)
17 lockFileQ <- function(dbl) {
18         paste(dbl$name, "qlock", sep = ".")
21 putQ <- function(dbl, vals) {
22         if(!createLockFile(lockFileQ(dbl)))
23                 stop("cannot create lock file")
24         on.exit(deleteLockFile(lockFileQ(dbl)))
26         if(!is.list(vals))
27                 vals <- as.list(vals)
28         len <- length(vals)
29         nextkey <- readLines(dbl$meta)
31         for(i in seq_along(vals)) {
32                 obj <- list(value = vals[[i]], nextkey = nextkey)
33                 key <- sha1(obj)
35                 ## These two are critical and need to be protected
36                 writeLines(key, dbl$meta)
37                 dbInsert(dbl$qdb, key, obj)
39                 nextkey <- key
40         }
41         writeLines(nextkey, dbl$meta)
44 headQkey <- function(dbl) {
45         with(dbl, readLines(meta))
48 popQ <- function(dbl) {
49         if(!createLockFile(lockFileQ(dbl)))
50                 stop("cannot create lock file")
51         on.exit(deleteLockFile(lockFileQ(dbl)))
53         h <- headQkey(dbl)
55         if(!length(h))
56                 return(NULL)
57         obj <- dbFetch(dbl$qdb, h)
59         ## These two are critical and need to be protected
60         writeLines(obj$nextkey, meta)
61         dbDelete(dbl$qdb, h)
63         obj$value