[R] plot formula 'x' is missing?
Gabor Grothendieck
ggrothendieck at gmail.com
Sat May 15 13:14:53 CEST 2010
There are several problems:
- as mentioned by Duncan, the code calls plot but specifies
plot.formula argument names -- it must specify the x argument of plot.
(You also have an x defined in your data frame but that is a
different x -- replacing your x with X everywhere still gives a
message about x being missing since its referring to the x argument of
plot.)
- the left and right sides of the formula are supposed to be y and x,
not y on both sides
- y is undefined
- the call to plot is somewhat non-standard so
plot(x = 1 / (1 + exp(5.0993 - 0.1084 * x)) ~ x, y = data.frame(x =
seq(0, 100, length.out=1000)))
does not work even though
plot(1 / (1 + exp(5.0993 - 0.1084 * x)) ~ x, data.frame(x = seq(0,
100, length.out=1000)))
does work by passing the two arguments as x and y to plot:
> debug(plot)
> plot(1 / (1 + exp(5.0993 - 0.1084 * x)) ~ x, data.frame(x =
seq(0, 100, length.out=1000)))
debugging in: plot(1/(1 + exp(5.0993 - 0.1084 * x)) ~ x,
data.frame(x = seq(0,
100, length.out = 1000)))
debug: {
if (is.function(x) && is.null(attr(x, "class"))) {
if (missing(y))
y <- NULL
hasylab <- function(...) !all(is.na(pmatch(names(list(...)),
"ylab")))
if (hasylab(...))
plot.function(x, y, ...)
else plot.function(x, y, ylab = paste(deparse(substitute(x)),
"(x)"), ...)
}
else UseMethod("plot")
}
Browse[2]> x
1/(1 + exp(5.0993 - 0.1084 * x)) ~ x
Browse[2]> head(y)
x
1 0.0000000
2 0.1001001
3 0.2002002
4 0.3003003
5 0.4004004
6 0.5005005
Instead, try these (which all give the same result):
op <-par(mfrow = c(3,2))
plot(1 / (1 + exp(5.0993 - 0.1084 * x)) ~ x, data = data.frame(x =
seq(0, 100, length.out=1000)))
graphics:::plot.formula(formula = 1 / (1 + exp(5.0993 - 0.1084 * x)) ~
x, data = data.frame(x = seq(0, 100, length.out=1000)))
x <- seq(0, 100, length.out = 1000)
plot(1 / (1 + exp(5.0993 - 0.1084 * x)) ~ x)
x <- seq(0, 100, length.out = 1000)
y <- 1 / (1 + exp(5.0993 - 0.1084 * x))
plot(y ~ x)
x <- seq(0, 100, length.out = 1000)
y <- 1 / (1 + exp(5.0993 - 0.1084 * x))
plot(x, y)
par(op)
On Sat, May 15, 2010 at 1:22 AM, Giovanni Azua <bravegag at gmail.com> wrote:
> Hi Jorge and Dennis,
>
> Thank you for the hint!
>
> However, I'm still very intrigued as to why it does not work using plot ... what is special about this specific formula that plot doesn't like it?
>
> Best regards,
> Giovanni
>
> On May 15, 2010, at 7:12 AM, Jorge Ivan Velez wrote:
>> Hi Giovanni,
>>
>> curve(1/(1+exp(5.0993-0.1084*x)), 0, 100)
>>
>> HTH,
>> Jorge
>>
>>
>> On Sat, May 15, 2010 at 12:43 AM, Giovanni Azua <> wrote:
>> Hello,
>>
>> I'd like to plot the logistic function for a specific model like this:
>>
>> > plot(formula=y~1/(1+exp(5.0993-0.1084*x)),data=data.frame(x=seq(0,100,length.out=1000)))
>> Error in is.function(x) : 'x' is missing
>>
>> However, I get the 'x' is missing error above and don't know how to fix it ...
>>
>> Can anyone advice?
>> Thanks in advance,
>> Best regards,
>> Giovanni
>>
>> ______________________________________________
>> R-help at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-help
>> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
>> and provide commented, minimal, self-contained, reproducible code.
>>
>
>
> [[alternative HTML version deleted]]
>
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
>
More information about the R-help
mailing list