Hello,
`textConnection`  prepares arguments for an internal function, and one of
these arguments is "description" that must be a character vector of
length 1
(or so it seems).
Now the one and only argument you usually give to `textConnection` is
called "object"; from the code you can see how this becomes a
"description":
    .Internal(textConnection(deparse(substitute(object)), object,
        open, env, type))
deparse(substitute(object)) -- which is intended to get the name of the
object you supplied. Try
> obj <- "a 1\nb 2\nc 3"
> deparse(substitute(obj))
[1] "obj"> deparse(substitute("a 1\nb 2\nc 3"))
[1] "\"a 1\\nb 2\\nc 3\""
This is called "non-standard evaluation" - in almost every other case
it
makes no difference whether you do some_fun(obj) or some_fun("a 1\nb 2\nc
3") but in this case it does.
Now for some reason (I'm not exactly sure why this happens) the result
deparse+substitute of your gsub thing is a character vector of length 2.
ugly.string <-  deparse
(substitute(gsub("&","\n",(strsplit('{"abc",{"def","X,1&Y,2&Z,3"}}','\\"')[[1]][6]))))
length( ugly.string)
Anyway, if the textConnection object has a "description" component
then it
is probably useful for something but something like
"gsub(\"&\", \"\\n\",
(strsplit(\"{\\\"abc\\\",{\\\"def\\\",\\\"X,1&Y,2&Z,3\\\"}}\"
doesn't seem
too useful. If you really hate the intermediate step (assignment) then a
solution might be to use the internal textConnection function directly, or
modify the code of `textConnection` e.g. like this:
tc <- function (object, open = "r", local = FALSE, encoding =
c("",
    "bytes", "UTF-8")) {
    env <- if (local) parent.frame() else .GlobalEnv
    type <- match(match.arg(encoding), c("", "bytes",
"UTF-8"))
    description <- deparse(substitute(object))
    is.ugly <- function(x) length(x)>1
    if(is.ugly(description)) description <- "a nice description"
    .Internal(textConnection(description, object, open, env, type))
}
# this will work with your examples
Bu the answer to your bug report was not particularly helpful (a simple
"RTFC"  would have helped more) and from an ordinary mortal's 
perspective
it is also wrong.
>   your usage is incorrect.
>      object: character.  A description of the connection.  For an input
> this is an R character vector object ...
>  and you used an expression.  Some expressions work, but only
> simple ones (and none are guaranteed to).
But what you actually used is "character" and not an expression:
is.character(gsub("&","\n",(strsplit('{"abc",{"def","X,1&Y,2&Z,3"}}','\\"')[[1]][6])))
# TRUE
 is.expression(gsub("&","\n",(strsplit('{"abc",{"def","X,1&Y,2&Z,3"}}','\\"')[[1]][6])))
# FALSE :-P
(Provided that standard evaluation is used which one would ordinarily
expect.) So in my opinion, the documentation is not complete here: it should
say explicitly that the object would better be a simple name and that
otherwise the result is not guaranteed.
Best regards,
Kenn
On Thu, Mar 10, 2011 at 12:20 PM, WANGSONG <mr.wangsong@hotmail.com>
wrote:
>
> I need read a table in a string with special format. I used read.csv and
> textConnection function.
> But i am confuse about textConnection by follow code.
>
> case A: It is OK£¡
>  str0 <-
'{"abc",{"def","X,1&Y,2&Z,3"}}'
>  str1 <- strsplit(str0,'"')[[1]][6]
>  str2 <- gsub("&","\n", str1)
>  con  <- textConnection( str2 )
>  read.csv(con,header=F)
>  close(con)
>
> case B: It is NOK!
>  con  <- textConnection(
>
gsub("&","\n",(strsplit('{"abc",{"def","X,1&Y,2&Z,3"}}','"')[[1]][6]))
)
>  # Error in here
>  read.csv(con,header=F)
>  close(con)
>
> case C: It is OK!
>  str0 <-
'{"abc",{"def","X,1&Y,2&Z,3"}}'
>  con  <- textConnection( gsub("&","\n",
(strsplit(str0,'"')[[1]][6])) )
>  read.csv(con,header=F)
>  close(con)
>
> case D: It is OK!
>  str2 <- gsub("&","\n",
>
strsplit('{"abc",{"def","X,1&Y,2&Z,3"}}','"')[[1]][6])
>  con  <- textConnection( str2 )
>  read.csv(con,header=F)
>  close(con)
>
> Except case B, textConnection report "invalid 'description'
argument", in
> other case, textConnection is OK.
>
> I don't known, what is different£¿ I report it as [Bug 14527], But the
> Answer is :
> >   your usage is incorrect.
> >      object: character.  A description of the connection.  For an
input
> this is an R character vector object ...
> >  and you used an expression.  Some expressions work, but only simple
ones
> (and none are guaranteed to).
>
> I read the help carefully, but i don't known which usage is incorrect.
>
> Would you help me?
>
>
> WangSong
>
>
>        [[alternative HTML version deleted]]
>
>
> ______________________________________________
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
	[[alternative HTML version deleted]]