The problem is that that you have asserted your result is of class "htest", and it is not like the format given in e.g. ?t.test. Specifically, print.htest contains

    if (!is.null(x$p.value)) {
        fp <- format.pval(x$p.value, digits = digits)
        out <- c(out, paste("p-value", if (substr(fp, 1, 1) ==
            "<") fp else paste("=", fp)))
    }

and this assumes x$p.value is of length one, not two.

On Thu, 30 Mar 2006, Matthieu Dubois wrote:

Dear Rusers,

I  tried to implement a function comparing mean scores between one
subject (the patient) and a group a control subjects. The function
returns attended results, but  I also obtained the following warning :

Warning message:
the condition has length > 1 and only the first element will be used
in: if (substr(fp, 1, 1) == "<") fp else paste("=", fp)

Maybe the cause of the message is obvious, but I don't understand. I
am newbie in R  and certainly I missed something. Any help would be
greatly appreciated.

The aim of the function was to :
1. compute a modified t-test with either raw data (controls and
patient) in vectors or only summaries for the control group (mean,
standard deviation, size of the group :  mean.c, sd.c, n) as inputs ;
2. estimate the rarity of the  difference observed between patient
and controls and computing confidence intervals

The function was the following:

crawford.t.test <- function(patient, controls, mean.c=0, sd.c=0, n=0,
na.rm=F) {
        #from Crawford et al. (1998, Clinical Neuropsychologist ; 2002,
Neuropsychologia)

        na<-na.rm

        #if no summaries are entered, they are computed
        if(missing(n)) {
                n <- length(controls)
                mean.c <- mean(controls, na.rm=na)
                sd.c <- sd(controls, na.rm=na)
                }
        dl <- n-1    #degrees of freedom of the  test

        #t.test computation
        t.obs <- (patient-mean.c) / (sd.c*(((n+1)/n)^0.5))
        proba.onetailed <- 1-pt(abs(t.obs), df=dl)
        rar <- pt(t.obs, df=dl) #point estimate of the rarity

        #confidence intervals computation on the rarity (Crawford &
Garthwaite, 2002, Neuropsychologia)
        c <- (patient-mean.c)/sd.c
        #finding the non central parameter of t distributions
        f <- function(delta, pr, x, df) pt(x, df = df, ncp = delta) - pr
        deltaL <- uniroot(f, lower=-37.62, upper=37.62, pr = 0.025, x = c*
(n^0.5), df = dl)
        deltaU <- uniroot(f, lower=-37.62, upper=37.62, pr = 0.975, x = c*
(n^0.5), df = dl)
        CI.U <- pnorm(deltaL$root/(n^0.5)) * 100 #upper bound of the
confidence interval
        CI.L <- pnorm(deltaU$root/(n^0.5)) * 100 #lower bound of the
confidence interval

        #output
        output <- list(statistic=t.obs, p.value=c
(one.tailed=proba.onetailed, twotailed=2*proba.onetailed), rarity=c
(rarity=rar, lower.boud=CI.L, upper.bound=CI.U), df=dl, method=paste
("Crawford modified t test with", dl, "degrees of freedom", sep=" "))
        class(output)<-"htest"
        return(output)
        }



Matthieu Dubois, PH.D. Student
Cognitive Neuroscience Unit
Université catholique de Louvain
10, Place cardinal Mercier - 1348 Louvain-la-Neuve - BELGIUM

[EMAIL PROTECTED]




        [[alternative HTML version deleted]]



--
Brian D. Ripley,                  [EMAIL PROTECTED]
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
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-help@stat.math.ethz.ch mailing list
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html

Reply via email to