My solution the original post is to always set 'con <- NULL' after closing a
connection, and then test for NULL.  This is how I do to make sure to make
sure that opened connections are closed and as soon as possible.

foo <- function(...) {
  con <- file("foo.R", open="r"):
  on.exit({
    if (!is.null(con)) {
      close(con);
      con <- NULL;
    }
  })

  # Do some thing that might cause foo() to exit.
  bar();

  # Do some thing else
  cat(con, "foo");
  # Close connection as soon as possible
  close(con);
  con <- NULL;

  # Do more things before returning
}



However, is there a reason for not having isOpen() return FALSE after
close() with the logic that a destroy connection is also a non-open one?
So, basically:

isOpen <- function (con, rw = "") {
  rw <- pmatch(rw, c("read", "write"), 0)
  res <- FALSE
  tryCatch({
    res <- .Internal(isOpen(con, rw))
  }, error = function(ex) {
  })
  res
}

EXAMPLE:
> con <- file("foo.R")
> print(isOpen(con))
[1] FALSE
> open(con, "w")
> print(isOpen(con))
[1] TRUE
> close(con)
> print(isOpen(con))
[1] FALSE
> open(con, "w")
Error in open.connection(con, "w") : invalid connection

If there is a use case that needs to test if a connection has been
destroyed, it would be more natural to add isDestroyed(), although I cannot
really see where it should be needed.

/Henrik

On Nov 14, 2007 11:18 PM, Prof Brian Ripley <[EMAIL PROTECTED]> wrote:
I think the confusion here is over close(): that closes *and destroys* a
connection, so it no longer exists.

isOpen applies to existing connections: you cannot close but not destroy
them at R level, but C code can (and does).  You will see it in use in the
utils package.



On Nov 14, 2007 11:18 PM, Prof Brian Ripley <[EMAIL PROTECTED]> wrote:

> I think the confusion here is over close(): that closes *and destroys* a
> connection, so it no longer exists.
>
> isOpen applies to existing connections: you cannot close but not destroy
> them at R level, but C code can (and does).  You will see it in use in the
> utils package.
>
>
> On Wed, 14 Nov 2007, Seth Falcon wrote:
>
> > "Roger D. Peng" <[EMAIL PROTECTED]> writes:
> >
> >> As far as I can tell, 'isOpen' cannot return FALSE in the case when 'rw
> = ""'.
> >> If the connection has already been closed by 'close' or some other
> function,
> >> then isOpen will produce an error.  The problem is that when isOpen
> calls
> >> 'getConnection', the connection cannot be found and 'getConnection'
> produces an
> >> error.  The check to see if it is open is never actually done.
> >
> > I see this too with R-devel (r43376) {from Nov 6th}.
> >
> >    con = file("example1", "w")
> >    isOpen(con)
> >
> >    [1] TRUE
> >
> >    showConnections()
> >
> >      description class  mode text   isopen   can read can write
> >    3 "example1"  "file" "w"  "text" "opened" "no"     "yes"
> >
> >    close(con)
> >    isOpen(con)
> >
> >    Error in isOpen(con) : invalid connection
> >
> >    ## printing also fails
> >    con
> >    Error in summary.connection(x) : invalid connection
> >
> >> This came up in some code where I'm trying to clean up connections
> after
> >> successfully opening them.  The problem is that if I try to close a
> connection
> >> that has already been closed, I get an error (because 'getConnection'
> cannot
> >> find it).  But then there's no way for me to find out if a connection
> has
> >> already been closed.  Perhaps there's another approach I should be
> taking?  The
> >> context is basically,
> >>
> >> con <- file("foo", "w")
> >>
> >> tryCatch({
> >>      ## Do stuff that might fail
> >>      writeLines(stuff, con)
> >>      close(con)
> >>
> >>      file.copy("foo", "bar")
> >> }, finally = {
> >>      close(con)
> >> })
> >
> > This doesn't address isOpen, but why do you have the call to close
> > inside the tryCatch block?  Isn't the idea that finally will always be
> > run and so you can be reasonably sure that close gets called once?
> >
> > If your real world code is more complicated, perhaps you can make use
> > of a work around like:
> >
> > myIsOpen = function(con) tryCatch(isOpen(con), error=function(e) FALSE)
> >
> > You could do similar with myClose and "close" a connection as many
> > times as you'd like :-)
> >
> > + seth
> >
> >
>
> --
> Brian D. Ripley,                  [EMAIL PROTECTED]
> Professor of Applied Statistics,  
> http://www.stats.ox.ac.uk/~ripley/<http://www.stats.ox.ac.uk/%7Eripley/>
> University of Oxford,             Tel:  +44 1865 272861 (self)
> 1 South Parks Road,                     +44 1865 272866 (PA)
> Oxford OX1 3TG, UK                Fax:  +44 1865 272595
>
> ______________________________________________
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>

        [[alternative HTML version deleted]]

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

Reply via email to