Hi Tomas,

I have implemented your suggestions as follows: (I'm not certain yet if the first check in done - total_length == 0 is realy needed)

Creating the socket:

CreateSocket = function(host, port = 1984L, username, password) {
  tryCatch(
    {conn <- private$conn <- socketConnection(
      host = "localhost", port,
      open = "w+b", server = FALSE, blocking = FALSE, encoding = "UTF-8")
    }, error = function(e) {
      stop("Cannot open the connection")
     }
  )

#### Authenticating

response <- readBin_(conn) %>% rawToChar()
===> # browser()
splitted <-strsplit(response, "\\:")
ifelse(length(splitted[[1]]) > 1,
  { realm <- splitted[[1]][1]
    code  <- paste(username, realm, password, sep=":")
    nonce <- splitted[[1]][2] },
  { code  <- password
    nonce <- splitted[[1]][1]}
  )
code <- md5(paste(md5(code), nonce, sep = "")) %>% charToRaw()
# send username + code
auth <- c(charToRaw(username), as.raw(0x00), code, as.raw(0x00))
writeBin(auth, private$conn)
Accepted <- readBin(conn, what = "raw", n = 1) == 0x00
if (!Accepted) {
close(private$conn)
stop("Access denied")
}


Reading from the socket:

done <- function(rd, total_length) {
  if (total_length == 0) {   to done
    finish <- FALSE
  } else {
    finish <- ifelse(length(rd == Bsize), FALSE, TRUE)
  }
  return(finish)
}

readBin_ <- function(conn) {
  total_read <- rd <- as.raw(c())
  while(!done(rd, length(total_read))) {
    rd <- readBin(conn, "raw", Bsize)
    total_read %<>% c(rd)
    }
  return(total_read)
}

The first time readBin is used is while authenticating a new session.
This code fails ;-(

But when I insert a call to browser() after the first authentication line, I can execute all the following code without problems. This results in a fully functional session. And all the other following calls to readBin_ return the correct data. This means that 'done' and 'readBin' do exactly what they are intended to do.

Question
Why does creating and authenticating fail when a call to browser() is missing? (Or why does authentication succeed after I have debugged

Best,
Ben

Op 27-11-2021 om 20:19 schreef Tomas Kalibera:
On 11/27/21 8:05 PM, Tomas Kalibera wrote:


This is an extended demo with socketSelect() used to wait on the client for some data to be available, to avoid consuming too much CPU by polling. To be pasted into two R sessions running on the same computer. You would have to replace the function done() with something figuring out from the data whether it is complete or not, based on the protocol.

Best
Tomas


# the client

con2 <- socketConnection("localhost", port = 6011, open = "rb")
cat("Connected...\n")
total <- 0

done <- function(n) {
   n >= 2e8
}

while(!done(total)) {
    cat("Waiting for data to become ready...\n")
    socketSelect(list(con2))
    cat("Reading data...\n")
    r <- readBin(con2, "raw", 1024)
    total <- total + length(r)
    cat("Read", length(r), "bytes (total ", total, ").\n")
}
close(con2)

# the server

n <- 1e8
w <- as.raw(runif(n, 0, 255))
con1 <- socketConnection(port = 6011, blocking = TRUE, server = TRUE, open="a+b")
cat("Connected...\n")
writeBin(w, con1)
cat("Sent data the first time, sleeping...\n")
Sys.sleep(10)
cat("Sending data the second time...\n")
writeBin(w, con1)
cat("Data sent to client...\n")
close(con1)


Best
Tomas

# the client

con2 <- socketConnection("localhost", port = 6011, open = "rb")
cat("Connected...\n")
total <- 0

done <- function(n) {
  n >= 1e8
}

while(!done(total)) {
   r <- readBin(con2, "raw", 1024)
   total <- total + length(r)
   cat("Read", length(r), "bytes (total ", total, ").\n")
}
close(con2)

# the server

n <- 1e8
w <- as.raw(runif(n, 0, 255))
con1 <- socketConnection(port = 6011, blocking = TRUE, server = TRUE, open="a+b")
cat("Connected...\n")
writeBin(w, con1)
cat("Data sent to client...\n")
close(con1)


Ben

______________________________________________
R-package-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-package-devel
______________________________________________
R-package-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-package-devel

Reply via email to