R/scor.R

scor <-
function(x,y=NULL,corfun=pcor,gval=NA,plotit=FALSE,op=TRUE,cop=3,xlab="VAR 1",
ylab="VAR 2",STAND=TRUE,pr=TRUE,SEED=TRUE,MC=FALSE){
#
# Compute a skipped correlation coefficient.
#
# Eliminate outliers using a projection method
# That is, compute Donoho-Gasko median, for each point
# consider the line between it and the median,
# project all points onto this line, and
# check for outliers using a boxplot rule.
# Repeat this for all points. A point is declared
# an outlier if for any projection it is an outlier
# using a modification of the usual boxplot rule.
#
# For information about the argument cop, see the function
# outpro.
#
# Eliminate any outliers and compute correlation using
# remaining data.
#
#  MC=TRUE, the multicore version of outpro is used
#
# corfun=pcor means Pearson's correlation is used.
# corfun=spear means Spearman's correlation is used.
if(SEED){
oldSeed <- .Random.seed
set.seed(12) # So when using MVE or MCD, get consistent results
}
if(is.null(y[1]))m<-x
if(!is.null(y[1]))m<-cbind(x,y)
m<-elimna(m)
if(!MC)temp<-outpro(m,gval=gval,plotit=plotit,op=op,cop=cop,
xlab=xlab,ylab=ylab,STAND=STAND,pr=pr)$keep
if(MC)temp<-outproMC(m,gval=gval,plotit=plotit,op=op,cop=cop,
xlab=xlab,ylab=ylab,STAND=STAND,pr=pr)$keep
tcor<-corfun(m[temp,])$cor
if(!is.null(dim((m))))tcor<-tcor[1,2]
test<-abs(tcor*sqrt((nrow(m)-2)/(1-tcor**2)))
if(ncol(m)!=2)diag(test)<-NA
crit<-6.947/nrow(m)+2.3197
if(SEED) {
    assign(x=".Random.seed", value=oldSeed, envir=.GlobalEnv)
}
list(cor.value=tcor,test.stat=test,crit.05=crit)
}
musto101/wilcox_R documentation built on May 23, 2019, 10:52 a.m.