Rallfun-v26.txt

download Rallfun-v26.txt

of 923

Transcript of Rallfun-v26.txt

  • 8/10/2019 Rallfun-v26.txt

    1/921

    # TOP# May 12, 2014

    DqdifMC=.5)stop('q should be less than .5')if(!is.null(y)){xy=elimna(cbind(x,y))dif=xy[,1]-xy[,2]}

    if(is.null(y))dif=elimna(x)x=as.matrix(x)n=length(dif)if(plotit)akerd(dif,xlab=xlab)bvec=NAdata

  • 8/10/2019 Rallfun-v26.txt

    2/921

    ## Test hypothesis that for two independent groups, all regression parameters are equal# By default the Theil--Sen estimator is used## Strategy: Use bootstrap estimate of standard errors followed by# Johansen type test statistic.## ISO=TRUE, ignore intercept, test only the slope parameters.#x1=as.matrix(x1)p=ncol(x1)p1=p+1xy=elimna(cbind(x1,y1))x1=xy[,1:p]y1=xy[,p1]x2=as.matrix(x2)p=ncol(x2)p1=p+1xy=elimna(cbind(x2,y2))x2=xy[,1:p]y2=xy[,p1]if(plotit){xx1=x1

    yy1=y1xx2=x2yy2=y2if(ncol(as.matrix(x1))==1){if(eout){flag=outfun(cbind(x1,y1),plotit=FALSE,...)$keepxx1=x1[flag]yy1=y1[flag]flag=outfun(cbind(x2,y2),plotit=FALSE,...)$keepxx2=x2[flag]yy2=y2[flag]}if(xout){

    flag=outfun(xx1,plotit=FALSE,...)$keepxx1=x1[flag]yy1=y1[flag]flag=outfun(xx2,plotit=FALSE,...)$keepxx2=x2[flag]yy2=y2[flag]}plot(c(xx1,xx2),c(yy1,yy2),type="n",xlab=xlab,ylab=ylab)points(xx1,yy1)points(xx2,yy2,pch="+")abline(regfun(xx1,yy1,...)$coef)abline(regfun(xx2,yy2,...)$coef,lty=2)}}

    x=list()y=list()x[[1]]=x1x[[2]]=x2y[[1]]=y1y[[2]]=y2if(!ISO)output=reg1wayMC(x,y,regfun=regfun,nboot=nboot,xout=xout,outfun=outfun,SEED=SEED,STAND=STAND,...)if(ISO)output=reg1wayISOMC(x,y,regfun=regfun,nboot=nboot,xout=xout,outfun=outfun,

  • 8/10/2019 Rallfun-v26.txt

    3/921

    SEED=SEED,STAND=STAND,...)output}

    qcomhdMC

  • 8/10/2019 Rallfun-v26.txt

    4/921

    yax=c(output[,6],output[,7],output[,8])

    plot(xax,yax,xlab=xlab,ylab=ylab,type="n")

    points(output[,4],output[,6],pch="*")

    lines(output[,4],output[,6])

    points(output[,4],output[,7],pch="+")

    points(output[,4],output[,8],pch="+")

    }

    output

    }

    qcom.sub

  • 8/10/2019 Rallfun-v26.txt

    5/921

    # cop=5 uses TBS# cop=6 uses rmba (Olive's median ball algorithm)## For each point# consider the line between it and the center,# project all points onto this line, and# check for outliers using## MM=F, a boxplot rule.# MM=T, rule based on MAD and median## 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.## op=2 use mgv (function outmgv) method to eliminate outliers# an outlier if for any projection it is an outlier# using a modification of the usual boxplot rule.## op=3 use outlier method indicated by outfun## Eliminate any outliers and compute means# using remaining data.#

    m

  • 8/10/2019 Rallfun-v26.txt

    6/921

    up

  • 8/10/2019 Rallfun-v26.txt

    7/921

    print("pop=2 might be better")}}MM=as.vector(m)if(pop==0)akerd(MM,xlab=xlab,ylab=ylab)if(pop==1)rdplot(MM,fr=fr,xlab=xlab,ylab=ylab)if(pop==2)kdplot(MM,rval=rval,xlab=xlab,ylab=ylab)if(pop==3)boxplot(MM)if(pop==4)stem(MM)if(pop==5)hist(MM,xlab=xlab)if(pop==6)skerd(MM)}list(q=q,Est1=est1,Est2=est2,sum=est1+est2,ci=ci,p.value=p)}

    cbmhd_subMC

  • 8/10/2019 Rallfun-v26.txt

    8/921

    rvalb=matl(rvalb)rvalb

  • 8/10/2019 Rallfun-v26.txt

    9/921

    y1=xy1[,3]y2=xy2[,3]library(scatterplot3d)temp

  • 8/10/2019 Rallfun-v26.txt

    10/921

    xy=elimna(cbind(x1,y1))x1=xy[,1]y1=xy[,2]xy=elimna(cbind(x2,y2))x2=xy[,1]y2=xy[,2]if(xout){flago=identical(outfun,out)if(!flago)flag=outfun(x1,plotit=FALSE)$keepif(flago)flag=outpro(x1,STAND=STAND,plotit=FALSE)$keepx1=x1[flag]y1=y1[flag]if(!flago)flag=outfun(x2,plotit=FALSE)$keepif(flago)flag=outpro(x2,STAND=STAND,plotit=FALSE)$keep#flag=outfun(cbind(x2,y2))$keepx2=x2[flag]y2=y2[flag]}plot(c(x1,x2),c(y1,y2),type="n",xlab=xlab,ylab=ylab)points(x1,y1)points(x2,y2,pch="+")abline(regfun(x1,y1,...)$coef)abline(regfun(x2,y2,...)$coef,lty=2)}

    ghdist

  • 8/10/2019 Rallfun-v26.txt

    11/921

    wcov

  • 8/10/2019 Rallfun-v26.txt

    12/921

    ## tr is the amount of Winsorization#y

  • 8/10/2019 Rallfun-v26.txt

    13/921

    # Compute the standard error of qth sample quantile estimator# based on the single order statistic, x sub ([qn+.5]) (See Ch 3)## Store the data in vector# x, and the desired quantile in q# The default value for q is .5## op=1 Use Rosenblatt's shifted histogram# op=2 Use expected frequency curve# op=3 Use adaptive kernel density estimator#y

  • 8/10/2019 Rallfun-v26.txt

    14/921

    # M-estimators with Huber's Psi.# The default percentage bend is bend=1.28# The default number of bootstrap samples is nboot=100#if(SEED)set.seed(1) # set seed of random number generator so that# results can be duplicated.data

  • 8/10/2019 Rallfun-v26.txt

    15/921

    ## Compute M-estimator of location using Huber's Psi.# The default bending constant is 1.28#if(na.rm)x

  • 8/10/2019 Rallfun-v26.txt

    16/921

    list(ci=c(low,hi),crit=crit,se=se)}

    mestci

  • 8/10/2019 Rallfun-v26.txt

    17/921

    ival

  • 8/10/2019 Rallfun-v26.txt

    18/921

    cmat

  • 8/10/2019 Rallfun-v26.txt

    19/921

    kssig

  • 8/10/2019 Rallfun-v26.txt

    20/921

    test[jcom,4]

  • 8/10/2019 Rallfun-v26.txt

    21/921

    }for (i in 0:m){for (j in 0:n)if(i*j==0)umat[i+1,j+1]

  • 8/10/2019 Rallfun-v26.txt

    22/921

    ## Compute confidence intervals for the difference between deciles# of two independent groups. The simultaneous probability coverage is .95.# The Harrell-Davis estimate of the qth quantile is used.# The default number of bootstrap samples is nboot=200## The results are stored and returned in a 9 by 3 matrix,# the ith row corresponding to the i/10 quantile.# The first column is the lower end of the confidence interval.# The second column is the upper end.# The third column is the estimated difference between the deciles# (second group minus first).#plotit

  • 8/10/2019 Rallfun-v26.txt

    23/921

    # The results are stored and returned in a 9 by 4 matrix,# the ith row corresponding to the i/10 quantile.# The first column is the lower end of the confidence interval.# The second column is the upper end.# The third column is the estimated difference between the deciles# (second group minus first).# The fourth column contains the estimated standard error.## No missing values are allowed.#if(pr){print("NOTE: for higher power when sampling from a heavy-tailed dist.")print("or if the goal is to use an alpha value different from .05")print("use the function qdec2ci")}plotit

  • 8/10/2019 Rallfun-v26.txt

    24/921

    # If C=1, this function returns the .975 quantile of Student's t# distribution.#if(C-round(C)!=0)stop("The number of contrasts, C, must be an integer")if(C>=29)stop("C must be less than or equal to 28")if(C

  • 8/10/2019 Rallfun-v26.txt

    25/921

    3.04,3.07,3.11,3.13,3.16,3.18,3.21,3.23,3.25,3.27,3.29,3.30,3.32,3.33,3.35,3.36,3.37,3.39)m1[18,]

  • 8/10/2019 Rallfun-v26.txt

    26/921

    # or x is a matrix with columns corresponding to groups.## missing values are automatically removed.# Tied values are a ssumed to occur with probability zero.#library(MASS) # Needed for the function ginvif(!is.list(x))x

  • 8/10/2019 Rallfun-v26.txt

    27/921

    for (j in 1:J){if(j>i){for (l in 1:J){temp1

  • 8/10/2019 Rallfun-v26.txt

    28/921

    }cr

  • 8/10/2019 Rallfun-v26.txt

    29/921

    if(is.data.frame(x)) x

  • 8/10/2019 Rallfun-v26.txt

    30/921

    johan

  • 8/10/2019 Rallfun-v26.txt

    31/921

    wcor[i,j]

  • 8/10/2019 Rallfun-v26.txt

    32/921

    kron

  • 8/10/2019 Rallfun-v26.txt

    33/921

    qc

  • 8/10/2019 Rallfun-v26.txt

    34/921

    bptdsub

  • 8/10/2019 Rallfun-v26.txt

    35/921

    ic

  • 8/10/2019 Rallfun-v26.txt

    36/921

    }lindm

  • 8/10/2019 Rallfun-v26.txt

    37/921

    print("Taking bootstrap samples. Please wait.")data

  • 8/10/2019 Rallfun-v26.txt

    38/921

    11.56,11.65,11.74,11.82,11.89,11.97,12.07,12.11,12.17)m1[3,]

  • 8/10/2019 Rallfun-v26.txt

    39/921

    if(temp[find[1]]==0)smmcrit01nu[find[1]]){smmcrit01

  • 8/10/2019 Rallfun-v26.txt

    40/921

    n

  • 8/10/2019 Rallfun-v26.txt

    41/921

    }

    pbos

  • 8/10/2019 Rallfun-v26.txt

    42/921

    bi

  • 8/10/2019 Rallfun-v26.txt

    43/921

    ee

  • 8/10/2019 Rallfun-v26.txt

    44/921

    top

  • 8/10/2019 Rallfun-v26.txt

    45/921

  • 8/10/2019 Rallfun-v26.txt

    46/921

    # 1, 2, 3, ..., n## This function is used by other functions when computing# bootstrap estimates.## regfun is some regression method already stored in R# It is assumed that regfun$coef contains the intercept and slope# estimates produced by regfun. The regression methods written for# this book, plus regression functions in R, have this property.## x is assumed to be a matrix containing values of the predictors.#xmat

  • 8/10/2019 Rallfun-v26.txt

    47/921

    x=as.matrix(x)p=ncol(x)p1=p+1x=xy[,1:p]y=xy[,p1]plotit

  • 8/10/2019 Rallfun-v26.txt

    48/921

    if(max(abs(slopeadd),abs(b0add)) >=.0001)paste("failed to converge in",iter,"iterations")list(coef=c(b0,slope),resid=res)}

    anctgen=29)stop("At most 28 points can be compared")n1

  • 8/10/2019 Rallfun-v26.txt

    49/921

    if(m==0)m

  • 8/10/2019 Rallfun-v26.txt

    50/921

    # lines--a running interval smoother is used.## Assume data are in x1 y1 x2 and y2# Comparisons are made at the design points contained in the vector# pts#m1=elimna(cbind(x1,y1))x1=m1[,1]y1=m1[,2]m1=elimna(cbind(x2,y2))x2=m1[,1]y2=m1[,2]n1

  • 8/10/2019 Rallfun-v26.txt

    51/921

    # determine which values in x are near pt# based on fr * cov.mve## x is assumed to be an n by p matrix# pt is a vector of length p (a point in p-space).# m is cov.mve(x) computed by runm3d#library(MASS)if(!is.matrix(x))stop("Data are not stored in a matrix.")dis

  • 8/10/2019 Rallfun-v26.txt

    52/921

    # the first predictor, etc.## OUTPUT:#The first row reports the half-slope#ratios when the data are divided into two groups using the first predictor.#The first column is the half-slope ratio for the first predictor, the#second column is the half-slope ratio for the second predictor, and so forth.#The second row contains the half-slope ratios when the data are divided#into two groups using the second predictor, and so on.#x

  • 8/10/2019 Rallfun-v26.txt

    53/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    54/921

    # This is the modified M-regression estimator in Chapter 8## The predictors are assumed to be stored in the n by p matrix x.#x

  • 8/10/2019 Rallfun-v26.txt

    55/921

    p1

  • 8/10/2019 Rallfun-v26.txt

    56/921

    mat=elimna(mat)#if(sum(is.na(mat)>=1))stop("Missing values are not allowed.")J

  • 8/10/2019 Rallfun-v26.txt

    57/921

    m2

  • 8/10/2019 Rallfun-v26.txt

    58/921

    x

  • 8/10/2019 Rallfun-v26.txt

    59/921

    # Mee (1990).#if(!is.list(x))stop("Data are not stored in list mode")if(p!=length(x)){print("Warning: The number of groups in your data is not equal to JK")}jtk

  • 8/10/2019 Rallfun-v26.txt

    60/921

    # Compute the contrast matrix. Each row contains a 1, -1 and the rest 0# That is, all pairwise comparisons among K groups.#con

  • 8/10/2019 Rallfun-v26.txt

    61/921

    if(is.matrix(con)){if(length(x)!=nrow(con))stop("The number of rows in con is not equal to the number of groups.") }}if(is.list(x)){# put the data in an n by J matrixmat

  • 8/10/2019 Rallfun-v26.txt

    62/921

    isub

  • 8/10/2019 Rallfun-v26.txt

    63/921

    J

  • 8/10/2019 Rallfun-v26.txt

    64/921

    }data

  • 8/10/2019 Rallfun-v26.txt

    65/921

    ## corfun is some correlation function already stored in R#corbsub

  • 8/10/2019 Rallfun-v26.txt

    66/921

    set.seed(2)data

  • 8/10/2019 Rallfun-v26.txt

    67/921

    coef[1]

  • 8/10/2019 Rallfun-v26.txt

    68/921

    if(alpha==.025)crit

  • 8/10/2019 Rallfun-v26.txt

    69/921

    # # Now have an nboot by J matrix of bootstrap values. #test

  • 8/10/2019 Rallfun-v26.txt

    70/921

    ep0

  • 8/10/2019 Rallfun-v26.txt

    71/921

    flag=FALSE,plotit=FALSE){# Compute a confidence band for the shift function# Assuming two independent groups are being compared## The default critical value is the approximate .05 critical value## If flag equals F, for false, the exact probability coverage is not computed#x

  • 8/10/2019 Rallfun-v26.txt

    72/921

    text(temp[5], min(temp2), "o")}list(m=m,crit=crit,numsig=num,pc=pc)}

    runcor

  • 8/10/2019 Rallfun-v26.txt

    73/921

    #print("Taking bootstrap samples; please wait")data

  • 8/10/2019 Rallfun-v26.txt

    74/921

    v

  • 8/10/2019 Rallfun-v26.txt

    75/921

    }

    pow1

  • 8/10/2019 Rallfun-v26.txt

    76/921

    teststat = test, crit = crit, df = df)}

    ci2bin

  • 8/10/2019 Rallfun-v26.txt

    77/921

    lp

  • 8/10/2019 Rallfun-v26.txt

    78/921

    print ("Warning: Winsorizing with sample sizes less than 15")print("can result in poor control over the probability of a Type I error")}x

  • 8/10/2019 Rallfun-v26.txt

    79/921

    bvec

  • 8/10/2019 Rallfun-v26.txt

    80/921

    nvec[j]

  • 8/10/2019 Rallfun-v26.txt

    81/921

    if(nmin < 40) { ilow

  • 8/10/2019 Rallfun-v26.txt

    82/921

    gv1

  • 8/10/2019 Rallfun-v26.txt

    83/921

    mat[i,1]

  • 8/10/2019 Rallfun-v26.txt

    84/921

    isub[4]

  • 8/10/2019 Rallfun-v26.txt

    85/921

    mat[,3]

  • 8/10/2019 Rallfun-v26.txt

    86/921

    ## Compute a 1-alpha confidence interval for the trimmed mean## The default amount of trimming is tr=.2#if(pr){print("The p-value returned by the this function is based on the")print("null value specified by the argument null.value, which defaults to 0")}x

  • 8/10/2019 Rallfun-v26.txt

    87/921

    CC

  • 8/10/2019 Rallfun-v26.txt

    88/921

    # This function groups all values in column coln according to the# group numbers in column grpc and stores the results in list mode.## More than one column of data can sorted## grpc indicates the column of the matrix containing group id number#if(is.null(dim(m)))stop("Data must be stored in a matrix or data frame")if(is.na(grpc[1]))stop("The argument grpc is not specified")if(is.na(coln[1]))stop("The argument coln is not specified")if(length(grpc)!=1)stop("The argument grpc must have length 1")x

  • 8/10/2019 Rallfun-v26.txt

    89/921

    nuhat

  • 8/10/2019 Rallfun-v26.txt

    90/921

    ql

  • 8/10/2019 Rallfun-v26.txt

    91/921

    ## Do a two-sample permutation test based on means or any# other measure of location or scale indicated by the# argument est.## The default number of permutations is nboot=1000#x

  • 8/10/2019 Rallfun-v26.txt

    92/921

    tmean

  • 8/10/2019 Rallfun-v26.txt

    93/921

    HDEP

  • 8/10/2019 Rallfun-v26.txt

    94/921

    FV[I]

  • 8/10/2019 Rallfun-v26.txt

    95/921

    n

  • 8/10/2019 Rallfun-v26.txt

    96/921

    #=================================================

    # # X - A numeric matrix with N rows and NP columns # PNT - A numeric vector representing a point in the same space as # defined by X, so # length of T has to equal to NP. # NDIR - A number of samples to draw # EPS - Precision. # #================================== # --------------------------------------- # Initialize Number of singular samples # --------------------------------------- NSIN

  • 8/10/2019 Rallfun-v26.txt

    97/921

    NSIN

  • 8/10/2019 Rallfun-v26.txt

    98/921

    NP

  • 8/10/2019 Rallfun-v26.txt

    99/921

    # --------------------------------------- if (N > NP) { RES

  • 8/10/2019 Rallfun-v26.txt

    100/921

    outbox

  • 8/10/2019 Rallfun-v26.txt

    101/921

    }

    runm3d

  • 8/10/2019 Rallfun-v26.txt

    102/921

    xnmin,]iout

  • 8/10/2019 Rallfun-v26.txt

    103/921

    nm1

  • 8/10/2019 Rallfun-v26.txt

    104/921

    if (k < kk){jcom

  • 8/10/2019 Rallfun-v26.txt

    105/921

    # Maritz-Jarrett estimate of the standard error.## The default quantile is .5.# The default value for alpha is .05.#x=elimna(x)if(pr){if(sum(duplicated(x)>0))print("Duplicate values detected; use hdpb")}if(q =1)stop("q must be between 0 and 1")y

  • 8/10/2019 Rallfun-v26.txt

    106/921

    #temp

  • 8/10/2019 Rallfun-v26.txt

    107/921

    rb

  • 8/10/2019 Rallfun-v26.txt

    108/921

    p

  • 8/10/2019 Rallfun-v26.txt

    109/921

    pmat1){crit.level

  • 8/10/2019 Rallfun-v26.txt

    110/921

    z

  • 8/10/2019 Rallfun-v26.txt

    111/921

    nrow = nboot)datay

  • 8/10/2019 Rallfun-v26.txt

    112/921

    if(chk

  • 8/10/2019 Rallfun-v26.txt

    113/921

    ## Test the hypothesis of independence for# 1. all pairs of variables in matrix x, if y=NA, or# 2. between each variable stored in the matrix x and y.# This is done by repeated to calls to indt#x

  • 8/10/2019 Rallfun-v26.txt

    114/921

    # Missing values are automatically removed## op=1, use Rosenblatt's shifted histogram version of kernel estimate# op=2, use adaptive kernel estimate with initial estimate based# on expected frequency curve.#x

  • 8/10/2019 Rallfun-v26.txt

    115/921

    # indicating whether values in z would be# classified as coming from the first group.## op=1, use Rosenblatt's shifted histogram version of kernel estimate# op=2, use adaptive kernel estimate with initial estimate based# on expected frequency curve.#xsort

  • 8/10/2019 Rallfun-v26.txt

    116/921

    zhat[i]

  • 8/10/2019 Rallfun-v26.txt

    117/921

    }x

  • 8/10/2019 Rallfun-v26.txt

    118/921

    if(d==1){xord

  • 8/10/2019 Rallfun-v26.txt

    119/921

    list(ci.low=low,ci.up=hi,ci.coverage=cicov)}

    anova1

  • 8/10/2019 Rallfun-v26.txt

    120/921

    for (i in 1:ncol(m)){pbc

  • 8/10/2019 Rallfun-v26.txt

    121/921

    y}

    matsqrt

  • 8/10/2019 Rallfun-v26.txt

    122/921

    thall

  • 8/10/2019 Rallfun-v26.txt

    123/921

    print("Taking bootstrap samples. Please wait.")for(j in 1:J){if(pr)print(paste("Working on group ",j))mval[j]

  • 8/10/2019 Rallfun-v26.txt

    124/921

    # putting the points in ascending order.#xx=elimna(xx)fval1)fval

  • 8/10/2019 Rallfun-v26.txt

    125/921

    ## Let D=X_m-Y_m be the difference between# mth order statistics where X and Y are dependent.# Estimate standard error D with m=[qn+.5]# using adaptive kernel method## This function is used by qdtest#x

  • 8/10/2019 Rallfun-v26.txt

    126/921

    if(!is.matrix(x))stop("Data should be stored in a matrix")fhat

  • 8/10/2019 Rallfun-v26.txt

    127/921

    # of covariance is made when a single order statistic# is used to estimate the median.# y=NA, function returns squared standard error.#if(is.na(y[1]))val

  • 8/10/2019 Rallfun-v26.txt

    128/921

    pm1

  • 8/10/2019 Rallfun-v26.txt

    129/921

    h[j]

  • 8/10/2019 Rallfun-v26.txt

    130/921

    # and covariances when using the estimator# est.## SEED=TRUE, sets the seed of the random number generator.#if(SEED)set.seed(2)if(is.list(x))x

  • 8/10/2019 Rallfun-v26.txt

    131/921

    itop

  • 8/10/2019 Rallfun-v26.txt

    132/921

    if(side){if(prCRIT)print(paste("Symmetric Crit.val=",tval[icrit]))trimcibt

  • 8/10/2019 Rallfun-v26.txt

    133/921

    qdtest=20#if(!is.na(y[1]))x

  • 8/10/2019 Rallfun-v26.txt

    134/921

    h

  • 8/10/2019 Rallfun-v26.txt

    135/921

    ## For a J by K anova using quantiles with# repeated measures on both factors,# Perform all multiple comparisons for main effects# and interactions.## q=.5 by default meaning medians are compared# bop=F means bootstrap option not used;# with bop=T, function uses usual medians rather# rather than a single order statistic to estimate median# in conjunction with a bootstrap estimate of covariances# among sample medians.## The R variable data is assumed to contain the raw# data stored in a matrix or in list mode.# When in list mode data[[1]] contains the data# for the first level of both factors: level 1,1.# data[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# data[[K]] is the data for level 1,K# data[[K+1]] is the data for level 2,1, data[2K] is level 2,K, etc.## It is assumed that data has length JK, the total number of# groups being tested, but a subset of the data can be analyzed

    # using grp#Qa

  • 8/10/2019 Rallfun-v26.txt

    136/921

    conB

  • 8/10/2019 Rallfun-v26.txt

    137/921

    if(!is.list(x))stop("Data must be stored in a matrix or in list mode.")con

  • 8/10/2019 Rallfun-v26.txt

    138/921

    sintv20))print("Duplicate values detected; hdpb might have more power")}ci

  • 8/10/2019 Rallfun-v26.txt

    139/921

    ncon

  • 8/10/2019 Rallfun-v26.txt

    140/921

    # The R variable x is assumed to contain the raw# data stored in list mode or in a matrix.# If in list mode, x[[1]] contains the data# for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp#if(is.data.frame(x))x=as.matrix(x) if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    141/921

    }}}

    qdmcpdif

  • 8/10/2019 Rallfun-v26.txt

    142/921

    sigvec=zvec)if(sum(sigvec)

  • 8/10/2019 Rallfun-v26.txt

    143/921

    x

  • 8/10/2019 Rallfun-v26.txt

    144/921

    ancovam

  • 8/10/2019 Rallfun-v26.txt

    145/921

    cilow

  • 8/10/2019 Rallfun-v26.txt

    146/921

    #model5)stop("Current version is limited to 5 predictors")if(p==1)model[[1]]

  • 8/10/2019 Rallfun-v26.txt

    147/921

    ic

  • 8/10/2019 Rallfun-v26.txt

    148/921

    # consistency when choosing the correct model.

    # This function is used by other functions when computing# bootstrap estimates.#regboot

  • 8/10/2019 Rallfun-v26.txt

    149/921

    }pval

  • 8/10/2019 Rallfun-v26.txt

    150/921

    w[j]

  • 8/10/2019 Rallfun-v26.txt

    151/921

    bpmedse

  • 8/10/2019 Rallfun-v26.txt

    152/921

    h

  • 8/10/2019 Rallfun-v26.txt

    153/921

    sejk

  • 8/10/2019 Rallfun-v26.txt

    154/921

  • 8/10/2019 Rallfun-v26.txt

    155/921

    if(p!=length(grp))stop("Apparently a subset of the groups was specified that does not match the total number of groups indicated by the values for J and K.")tmeans

  • 8/10/2019 Rallfun-v26.txt

    156/921

    if(sum(con^2)==0){ncon

  • 8/10/2019 Rallfun-v26.txt

    157/921

    ci.upper"))temp2

  • 8/10/2019 Rallfun-v26.txt

    158/921

    list(p.value=test,est.dif=mvec[1]-mvec[2],ci.low=cilow,ci.up=ciup)}

    twobinom

  • 8/10/2019 Rallfun-v26.txt

    159/921

    }res

  • 8/10/2019 Rallfun-v26.txt

    160/921

    xx

  • 8/10/2019 Rallfun-v26.txt

    161/921

    # using the percentile bootstrap method.# By default, M-estimators are compared using 599 bootstrap samples.## The data are assumed to be stored in x in list mode. Thus,# x[[1]] contains the data for the first group, x[[2]] the data# for the second group, etc. Length(x)=the number of groups = J, say.##if(is.data.frame(x))x=as.matrix(x)if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    162/921

    mflag

  • 8/10/2019 Rallfun-v26.txt

    163/921

    gkcor

  • 8/10/2019 Rallfun-v26.txt

    164/921

    data

  • 8/10/2019 Rallfun-v26.txt

    165/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    166/921

    Qa.siglevel

  • 8/10/2019 Rallfun-v26.txt

    167/921

    # Test the hypothesis that q of the p predictors are equal to# some specified constants. By default, the hypothesis is that all# p predictors have a coefficient equal to zero.# The method is based on a confidence ellipsoid.# The critical value is determined with the percentile bootstrap method# in conjunction with Mahalanobis distance.#x

  • 8/10/2019 Rallfun-v26.txt

    168/921

    }list(test=test,crit=crit,p.value=sig.level,nullvec=nullvec,est=estsub,n=length(y))}

    reg2ci

  • 8/10/2019 Rallfun-v26.txt

    169/921

    # contains the bootstrap values for first predictor, etc.data

  • 8/10/2019 Rallfun-v26.txt

    170/921

    # conventional one-way anova#if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    171/921

    ## nboot indicates how many samples from a normal distribution# are used to approximate the adjustment.## Simulations suggest that this fucntion# continues to work well under non-normality.#if(SEED)set.seed(2)X

  • 8/10/2019 Rallfun-v26.txt

    172/921

    B

  • 8/10/2019 Rallfun-v26.txt

    173/921

    ## This function uses an adjusted p-value, the adjustment# being made assuming normality.## nboot indicates how many samples from a normal distribution# are used to approximate the adjustment.## Simulations suggest that this fucntion# continues to work well under non-normality.#if(SEED)set.seed(2)X

  • 8/10/2019 Rallfun-v26.txt

    174/921

    # regression using heteroscedastic method# recommended by Cribari-Neto (2004).#x

  • 8/10/2019 Rallfun-v26.txt

    175/921

    p.val

  • 8/10/2019 Rallfun-v26.txt

    176/921

    # By default, use normal distributions.##To get a g-and-h distribution# for the marginals, use mar.fun=ghdist.# Example rmul(30,p=4,rho=.3,mar.fun=ghdist,g=.5,h=.2) will# generate 30 vectors from a 4-variate distribution where the marginals# have a g-and-h distribution with g=.5 and h=.2.## This function is similar to ghmul, only here, generate the marginal values# and then transform the data to have correlation matrix cmat## cmat is the correlation matrix# if argument# rho is specified, the correlations are taken to# have a this common value.## Method (e.g. Browne, M. W. (1968) A comparison of factor analytic# techniques. Psychometrika, 33, 267-334.# Let U'U=R be the Cholesky decomposition of R. Generate independent data# from some dist yielding X. Then XU has population correlation matrix R#if(!is.na(rho)){if(abs(rho)>1)stop("rho must be between -1 and 1")cmat

  • 8/10/2019 Rallfun-v26.txt

    177/921

  • 8/10/2019 Rallfun-v26.txt

    178/921

    val=optim(START,spat.sub,x=x,method='BFGS')$parlist(center=val)}olswbtest

  • 8/10/2019 Rallfun-v26.txt

    179/921

    test}

    regpreinfinity.## The argument model should have list mode, model[[1]] indicates# which predictors are used in the first model. For example, storing# 1,4 in model[[1]] means predictors 1 and 4 are being considered.# If model is not specified, and number of predictors is at most 5,# then all models are considered.## If adz=T, added to the models to be considered is where

    # all regression slopes are zero. That is, use measure of location only# corresponding to# locfun.#if(pr){print("By default, least squares regression is used, ")print("But from Wilcox, R. R. 2008, Journal of Applied Statistics, 35, 1-8")print("Setting regfun=tsreg appears to be a better choice for general use.")print("That is, replace least squares with the Theil-Sen estimator")print("Note: Default for the argument error is now absfun")print(" meaning absolute error is used")print("To use squared error, set error=sqfun")}

    x

  • 8/10/2019 Rallfun-v26.txt

    180/921

    if(STAND)flag

  • 8/10/2019 Rallfun-v26.txt

    181/921

    # For every column of mat, move entry down 1#matn

  • 8/10/2019 Rallfun-v26.txt

    182/921

    n1

  • 8/10/2019 Rallfun-v26.txt

    183/921

    ing to the design point X=",pts[i]))if(length(g2)

  • 8/10/2019 Rallfun-v26.txt

    184/921

    plotCI

  • 8/10/2019 Rallfun-v26.txt

    185/921

    # segments(ul, y2 - smidge, ul, y2 + smidge, col=col, lwd=lwd) } invisible(list(x = x, y = y))}bdanova2

  • 8/10/2019 Rallfun-v26.txt

    186/921

    # Test the hypothesis that the distribution for each pairwise# difference has a measure of location = 0# By default, the median is used## The default number of bootstrap samples is nboot=500## op controls how depth is measured# op=1, Mahalanobis# op=2, Mahalanobis based on MCD covariance matrix# op=3, Projection distance# op=4, Projection distance using FORTRAN version## for arguments MM and cop, see pdis.#if(is.data.frame(x))x=as.matrix(x)if(is.matrix(x)){xx

  • 8/10/2019 Rallfun-v26.txt

    187/921

    output[dval,1]

  • 8/10/2019 Rallfun-v26.txt

    188/921

    stop("Data must be stored in list mode or a matrix.") for(j in 1:JK) { xx

  • 8/10/2019 Rallfun-v26.txt

    189/921

    lower

  • 8/10/2019 Rallfun-v26.txt

    190/921

    mat=matrix(0,nrow=p,ncol=p)id=c(1:idep)for(j in 1:J){mat[id,id]=covmtrim(x[id],tr=tr)id=id+idep}mat}bwwmatna

  • 8/10/2019 Rallfun-v26.txt

    191/921

    iup=iup+ad}y}bwwtrim

  • 8/10/2019 Rallfun-v26.txt

    192/921

    Qa=bwwtrim.sub(cmat, tmeans, v, h,p)Qa.siglevel

  • 8/10/2019 Rallfun-v26.txt

    193/921

    for(j in 1:J){for(k in 1:K){z=x[,ilow:iup]d=elimna(z)im=0for(l in 1:L){ic=ic+1im=im+1y[[ic]]=d[,im]}ilow=ilow+adiup=iup+ad}}y}bbwna

  • 8/10/2019 Rallfun-v26.txt

    194/921

    if(is.data.frame(data)) data

  • 8/10/2019 Rallfun-v26.txt

    195/921

    cmat

  • 8/10/2019 Rallfun-v26.txt

    196/921

    list(skew=sk,kurtosis=ku)}

    t3pval

  • 8/10/2019 Rallfun-v26.txt

    197/921

    n")if(!is.null(IV[1])){if(pr)print("Assuming x is a vector containing all of the data, the dependent variable")xi=elimna(cbind(x,IV))x=fac2list(xi[,1],xi[,2])}if(MAT){if(!is.matrix(x))stop("With MAT=T, data must be stored in a matrix")if(length(lev.col)!=1)stop("Argument lev.col should have 1 value")temp=selby(x,lev.col,var.col)x=temp$xgrp2=rank(temp$grpn)x=x[grp2]}if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    198/921

    # data[[KL+1]] is level 2,1,1, etc.## MAT=T, assumes data are stored in matrix with 3 columns indicating# levels of the three factors.# That is, this function calls selby2 for you.## The default amount of trimming is tr=.2## It is assumed that data has length JKL, the total number of# groups being tested.#if(is.data.frame(x))x=as.matrix(x)data=x #Yes, odd codeif(MAT){if(!is.matrix(data))stop("With MAT=T, data must be a matrix")if(length(lev.col)!=3)stop("Argument lev.col should have 3 values")temp=selby2(data,lev.col,var.col)lev1=length(unique(temp$grpn[,1]))lev2=length(unique(temp$grpn[,2]))lev3=length(unique(temp$grpn[,3]))gv=apply(temp$grpn,2,rank)gvad=100*gv[,1]+10*gv[,2]+gv[,3]grp=rank(gvad)if(pr){

    print(paste("Factor 1 has", lev1, "levels"))print(paste("Factor 2 has", lev2, "levels"))print(paste("Factor 3 has", lev3, "levels"))}if(J!=lev1)warning("J is being reset to the number of levels found")if(K!=lev2)warning("K is being reset to the number of levels found")if(L!=lev3)warning("K is being reset to the number of levels found")J=lev1K=lev2L=lev2data=temp$x}if(is.matrix(data))data=listm(data)

    if(!is.list(data))stop("Data is not stored in list mode")if(p!=length(data)){print("The total number of groups, based on the specified levels, is")print(p)print("The number of groups in data is")print(length(data))print("Warning: These two values are not equal")}tmeans

  • 8/10/2019 Rallfun-v26.txt

    199/921

    cj

  • 8/10/2019 Rallfun-v26.txt

    200/921

    m

  • 8/10/2019 Rallfun-v26.txt

    201/921

    x1 && pr)print("WARNING: more than 1 predictor, olstest might be better")if(nrow(x) != length(y))stop("Length of y does not match number of x values")m

  • 8/10/2019 Rallfun-v26.txt

    202/921

    v1=apply(x,2,scat)p=ncol(x)for(j in 1:p)x[,j]=(x[,j]-m1[j])/sqrt(v1[j])x}

    t2way

  • 8/10/2019 Rallfun-v26.txt

    203/921

    if(K!=lev2)warning("K is being reset to the number of levels found")J=lev1K=lev2x=temp$x}if(!is.null(IV1[1])){if(is.null(IV2[1]))stop("IV2 is NULL")if(pr)print("Assuming data is a vector containing all of the data; the dependentvariable")xi=elimna(cbind(x,IV1,IV2))J=length(unique(xi[,2]))K=length(unique(xi[,3]))x=fac2list(xi[,1],xi[,2:3])}if(is.matrix(x))x=listm(x)if(!is.list(x))stop("Data are not stored in list mode")if(p!=length(x)){print("The total number of groups, based on the specified levels, is")print(p)print("The number of groups is")print(length(x))print("Warning: These two values are not equal")}tmeans

  • 8/10/2019 Rallfun-v26.txt

    204/921

    # Do test for factor A by B interactioncmat

  • 8/10/2019 Rallfun-v26.txt

    205/921

    {while ((jtrial)){

    j=j+1}p[i]=j-1

    }j=h1for (i in 1:h2){

    while ((j>=1)&(calwork(y1[max(j,1)],y2[i],j,i,h1+1,eps)trial,rep(F,n-nn))acand=a[i]iwcand=iw[i]

    nn=length(acand)# nn_kcand_length(acand)

    wrest=wrest+wleft+wmid}

    }

    a[1:nn]=acand[1:nn]iw[1:nn]=iwcand[1:nn]}whmed

    }

    calwork

  • 8/10/2019 Rallfun-v26.txt

    208/921

    # Use the tbs estimator to# determine which points are outliers#if(!is.matrix(x))stop("x should be a matrix")x

  • 8/10/2019 Rallfun-v26.txt

    209/921

    M = c1.plus.M ){M

  • 8/10/2019 Rallfun-v26.txt

    210/921

    # print(c(iter,k,crit)) return(k)}rho.bt

  • 8/10/2019 Rallfun-v26.txt

    211/921

    chkit

  • 8/10/2019 Rallfun-v26.txt

    212/921

    ## Store the data in a matrix or data frame in a new# R variable having list mode.# Col 1 will be stored in y[[1]], col 2 in y[[2]], and so on.#if(is.null(dim(x)))stop("The argument x must be a matrix or data frame")y

  • 8/10/2019 Rallfun-v26.txt

    213/921

  • 8/10/2019 Rallfun-v26.txt

    214/921

    # x[[1]] contains the data for the first group, x[[2]] the data# for the second group, etc. Length(x)=the number of groups = J.# If stored in a matrix, the columns of the matrix correspond# to groups.## est is the measure of location and defaults to a M-estimator# ... can be used to set optional arguments associated with est## The argument grp can be used to analyze a subset of the groups# Example: grp=c(1,3,5) would compare groups 1, 3 and 5.## Missing values are allowed.#con

  • 8/10/2019 Rallfun-v26.txt

    215/921

  • 8/10/2019 Rallfun-v26.txt

    216/921

    for(j in 1:J){ell[j]

  • 8/10/2019 Rallfun-v26.txt

    217/921

    }Jm

  • 8/10/2019 Rallfun-v26.txt

    218/921

    dimnames(psihat)

  • 8/10/2019 Rallfun-v26.txt

    219/921

    id

  • 8/10/2019 Rallfun-v26.txt

    220/921

    testit

  • 8/10/2019 Rallfun-v26.txt

    221/921

    conB

  • 8/10/2019 Rallfun-v26.txt

    222/921

    testB

  • 8/10/2019 Rallfun-v26.txt

    223/921

    jm1

  • 8/10/2019 Rallfun-v26.txt

    224/921

  • 8/10/2019 Rallfun-v26.txt

    225/921

    x

  • 8/10/2019 Rallfun-v26.txt

    226/921

    alpha

  • 8/10/2019 Rallfun-v26.txt

    227/921

    ststat=test,n=length(x),df=df)}

    rmmcppbtm

  • 8/10/2019 Rallfun-v26.txt

    228/921

    }if(is.na(nboot)){if(d

  • 8/10/2019 Rallfun-v26.txt

    229/921

    icl

  • 8/10/2019 Rallfun-v26.txt

    230/921

    con

  • 8/10/2019 Rallfun-v26.txt

    231/921

    if(d==10 && alpha==.05 && nboot

  • 8/10/2019 Rallfun-v26.txt

    232/921

    psihat[d,3]

  • 8/10/2019 Rallfun-v26.txt

    233/921

    ## isub is a vector of length n,# a bootstrap sample from the sequence of integers# 1, 2, 3, ..., n## xcen is an n by J matrix containing the input data#val

  • 8/10/2019 Rallfun-v26.txt

    234/921

    center

  • 8/10/2019 Rallfun-v26.txt

    235/921

    # groups being tested, but a subset of the data can be analyzed# using grp#if(is.data.frame(data))data=as.matrix(data)x

  • 8/10/2019 Rallfun-v26.txt

    236/921

    }

    gvar

  • 8/10/2019 Rallfun-v26.txt

    237/921

    # estimates produced by regfun. The regression methods written for# this book, plus regression functions in R, have this property.## x is assumed to be a matrix containing values of the predictors.##xmat

  • 8/10/2019 Rallfun-v26.txt

    238/921

    pbcan

  • 8/10/2019 Rallfun-v26.txt

    239/921

    }dis

  • 8/10/2019 Rallfun-v26.txt

    240/921

    n

  • 8/10/2019 Rallfun-v26.txt

    241/921

    con

  • 8/10/2019 Rallfun-v26.txt

    242/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    243/921

    }ocor

  • 8/10/2019 Rallfun-v26.txt

    244/921

    print("Taking bootstrap samples. Please wait.")data

  • 8/10/2019 Rallfun-v26.txt

    245/921

    if(k

  • 8/10/2019 Rallfun-v26.txt

    246/921

    ## Do a smooth where x is discrete with a# relatively small number of values.#temp

  • 8/10/2019 Rallfun-v26.txt

    247/921

    output}

    wsp1reg

  • 8/10/2019 Rallfun-v26.txt

    248/921

    temp[p]

  • 8/10/2019 Rallfun-v26.txt

    249/921

    varvec[k]

  • 8/10/2019 Rallfun-v26.txt

    250/921

    # This method is faster than outmgv.#if(is.na(y[1]))m

  • 8/10/2019 Rallfun-v26.txt

    251/921

    cmanova

  • 8/10/2019 Rallfun-v26.txt

    252/921

    top

  • 8/10/2019 Rallfun-v26.txt

    253/921

    if (j < jj){for (k in 1:K){for (kk in 1:K){if (k < kk){jcom

  • 8/10/2019 Rallfun-v26.txt

    254/921

    if(chkit[1]>nullval || chkit[2]

  • 8/10/2019 Rallfun-v26.txt

    255/921

    outm[ic,3]

  • 8/10/2019 Rallfun-v26.txt

    256/921

    x

  • 8/10/2019 Rallfun-v26.txt

    257/921

    avec

  • 8/10/2019 Rallfun-v26.txt

    258/921

    phat

  • 8/10/2019 Rallfun-v26.txt

    259/921

    for(jj in 1:J){if(j < jj){ic

  • 8/10/2019 Rallfun-v26.txt

    260/921

    paste("The required number of observations for group",j," in the second stage is")paste(n.vec[j]-tempn[j]," but only ",nvec2[j]," are available")stop()}TT[j]

  • 8/10/2019 Rallfun-v26.txt

    261/921

    if(!is.list(x)) stop("Data must be stored in list mode or a matrix.") for(j in 1:JK) { xx

  • 8/10/2019 Rallfun-v26.txt

    262/921

    Fac.B[ic,1]

  • 8/10/2019 Rallfun-v26.txt

    263/921

    if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    264/921

    cont[j,ic]

  • 8/10/2019 Rallfun-v26.txt

    265/921

    psihat[ic,]

  • 8/10/2019 Rallfun-v26.txt

    266/921

    # data stored in list mode or in a matrix.# If in list mode, x[[1]] contains the data# for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    267/921

    nvec[j]

  • 8/10/2019 Rallfun-v26.txt

    268/921

  • 8/10/2019 Rallfun-v26.txt

    269/921

    # among dependent groups in a split-plot design# The analysis is done based on all pairs# of difference scores. The null hypothesis is that# all such differences have a typical value of zero.## The R variable x is assumed to contain the raw# data stored in list mode or in a matrix.# If in list mode, x[[1]] contains the data# for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    270/921

    # Now stack the data in an N by K matrix#x

  • 8/10/2019 Rallfun-v26.txt

    271/921

    kv

  • 8/10/2019 Rallfun-v26.txt

    272/921

    ## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    273/921

    con

  • 8/10/2019 Rallfun-v26.txt

    274/921

  • 8/10/2019 Rallfun-v26.txt

    275/921

    # and determine depth of the projected points.# The final depth of a point is its minimum depth# among all projections.## plotit=TRUE creates a scatterplot when working with# bivariate data and pts=NA## There are three options for computing the center of the# cloud of points when computing projections, assuming center=NA:## cop=2 uses MCD center# cop=3 uses median of the marginal distributions.# cop=4 uses MVE center## If a value for center is passed to this function,# this value is used to determine depths.## When plotting,# center is marked with a cross, +.#library(MASS)if(cop!=2 && cop!=3 && cop!=4)stop("Only cop=2, 3 or 4 is allowed")if(is.list(m))stop("Store data in a matrix; might use function listm")m

  • 8/10/2019 Rallfun-v26.txt

    276/921

    A

  • 8/10/2019 Rallfun-v26.txt

    277/921

    }

    opreg

  • 8/10/2019 Rallfun-v26.txt

    278/921

    }}sor

  • 8/10/2019 Rallfun-v26.txt

    279/921

    B

  • 8/10/2019 Rallfun-v26.txt

    280/921

    # Use kernel density estimate# Using the built-in S+ function density,## op=3: Use expected frequency curve.## op=4: Use adaptive kernel estimator#x1

  • 8/10/2019 Rallfun-v26.txt

    281/921

    SE){### Determine center correpsonding to two# independent groups, project all points onto line# connecting the centers,# then based on the projected distances,# estimate p=probability that a randomly sampled# point from group 1 is less than a point from group 2# based on the projected distances.## plotit=TRUE creates a plot of the projected data# pop=1 plot two dotplots based on projected distances# pop=2 boxplots# pop=3 expected frequency curve.# pop=4 adaptive kernel density## There are three options for computing the center of the# cloud of points when computing projections:# cop=1 uses Donoho-Gasko median# cop=2 uses MCD center# cop=3 uses median of the marginal distributions.## When using cop=2 or 3, default critical value for outliers

    # is square root of the .975 quantile of a# chi-squared distribution with p degrees# of freedom.## Donoho-Gasko (Tukey) median is marked with a cross, +.#if(is.null(dim(m1))||dim(m1)[2]

  • 8/10/2019 Rallfun-v26.txt

    282/921

    center2

  • 8/10/2019 Rallfun-v26.txt

    283/921

    #if(!is.matrix(mm1))stop("Data are assumed to be stored in a matrix having two ormore columns. For univariate data, use the function outbox or out")if(is.na(SEED))set.seed(2)if(!is.na(SEED))set.seed(SEED)val

  • 8/10/2019 Rallfun-v26.txt

    284/921

    m

  • 8/10/2019 Rallfun-v26.txt

    285/921

    val}

    lsqs2

  • 8/10/2019 Rallfun-v26.txt

    286/921

    temp[i]

  • 8/10/2019 Rallfun-v26.txt

    287/921

    qhatyx

  • 8/10/2019 Rallfun-v26.txt

    288/921

    xord

  • 8/10/2019 Rallfun-v26.txt

    289/921

    x3

  • 8/10/2019 Rallfun-v26.txt

    290/921

    #if(is.matrix(x2))x2

  • 8/10/2019 Rallfun-v26.txt

    291/921

    # This method is designed to be sensitive to# shifts in location.## Use Tukey's depth; bivariate case only.## cop=2 use MCD location estimator when# computing depth with function fdepth# cop=3 uses medians# cop=3 uses MVE## xpch="+" means when plotting the data, data from the first# group are indicated by a +# ypch="o" are data from the second group#if(is.list(x))x

  • 8/10/2019 Rallfun-v26.txt

    292/921

    xord

  • 8/10/2019 Rallfun-v26.txt

    293/921

    # cf. Fan, Annals of Statistics, 1993, 21, 196-217.#d

  • 8/10/2019 Rallfun-v26.txt

    294/921

    chkit= np1){vals

  • 8/10/2019 Rallfun-v26.txt

    295/921

    # ap=F first variable is tested versus all others# (for a total of p-1 tests).# pw=T, print message about high execution time# pw=F, suppress the message.#m

  • 8/10/2019 Rallfun-v26.txt

    296/921

    if(is.list(m))m

  • 8/10/2019 Rallfun-v26.txt

    297/921

    wrregfun}

    spat.sub

  • 8/10/2019 Rallfun-v26.txt

    298/921

    points(x,y)}if(!scat)plot(c(x,x),c(y,rmd),type="n",ylab=ylab,xlab=xlab)points(x,rmd,type="n")sx

  • 8/10/2019 Rallfun-v26.txt

    299/921

    xlab=xlab,ylab=ylab,...)$outputif(p>1){library(MASS)library(akima)np

  • 8/10/2019 Rallfun-v26.txt

    300/921

  • 8/10/2019 Rallfun-v26.txt

    301/921

    test2}

    adtests1

  • 8/10/2019 Rallfun-v26.txt

    302/921

    lta.sub

  • 8/10/2019 Rallfun-v26.txt

    303/921

    # This function returns the N values for theta that minimize FN# ICOUNT

  • 8/10/2019 Rallfun-v26.txt

    304/921

    DCHK REQMIN)break}} if(ICOUNT >= KCOUNT){ I1000

  • 8/10/2019 Rallfun-v26.txt

    305/921

    }if(IFLAG){for(J in 1:NN){P[,J]=(P[,J]+P[,ILO])*.5 XMIN

  • 8/10/2019 Rallfun-v26.txt

    306/921

    NN

  • 8/10/2019 Rallfun-v26.txt

    307/921

    if(ICOUNT >= KCOUNT){ I1000

  • 8/10/2019 Rallfun-v26.txt

    308/921

    XMIN

  • 8/10/2019 Rallfun-v26.txt

    309/921

    stein1.tr=.5)stop("Argument tr must be between 0 and .5")if(is.matrix(x))m

  • 8/10/2019 Rallfun-v26.txt

    310/921

    for (j in 1:ncol(m)){for (jj in 1:ncol(m)){if(j

  • 8/10/2019 Rallfun-v26.txt

    311/921

    for (j in 1:nrow(m)){A

  • 8/10/2019 Rallfun-v26.txt

    312/921

  • 8/10/2019 Rallfun-v26.txt

    313/921

    }rmd

  • 8/10/2019 Rallfun-v26.txt

    314/921

    n2

  • 8/10/2019 Rallfun-v26.txt

    315/921

    # compute test statisticv

  • 8/10/2019 Rallfun-v26.txt

    316/921

    # using remaining data.#if(is.na(SEED))set.seed(2)if(!is.na(SEED))set.seed(SEED)m

  • 8/10/2019 Rallfun-v26.txt

    317/921

    }}if(ncol(x)>2)plotit

  • 8/10/2019 Rallfun-v26.txt

    318/921

    # gval is critical value for projection-type outlier detection# method## ADJ=T, Adjust p-values as described in Section 11.1.5 of the text.#x

  • 8/10/2019 Rallfun-v26.txt

    319/921

    zvec

  • 8/10/2019 Rallfun-v26.txt

    320/921

    chkit= 2){temp4

  • 8/10/2019 Rallfun-v26.txt

    321/921

    m

  • 8/10/2019 Rallfun-v26.txt

    322/921

    y

  • 8/10/2019 Rallfun-v26.txt

    323/921

    ## cop=1 Donoho-Gasko median,# cop=2 MCD,# cop=3 marginal medians.# cop=4 MVE## For each point# consider the line between it and the center# project all points onto this line, and# check for outliers using## MM=F, a boxplot rule.# MM=T, rule based on MAD and median## 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.## Eliminate any outliers and compute means# using remaining data.#if(ncol(m1) != ncol(m2)){stop("Number of variables in group 1 does not equal the number in group 2.")}

    if(is.na(SEED))set.seed(2)#if(!is.na(SEED))set.seed(SEED)m1

  • 8/10/2019 Rallfun-v26.txt

    324/921

    ic

  • 8/10/2019 Rallfun-v26.txt

    325/921

    }}if(plotit){plot(x,y,xlab=xlab,ylab=ylab)if(np>0){ilow

  • 8/10/2019 Rallfun-v26.txt

    326/921

    ## Argument BA: When using dif=F, BA=T uses a correction term# when computing a p-value.#if(dif){if(pr)print("dif=T, so analysis is done on difference scores")temp

  • 8/10/2019 Rallfun-v26.txt

    327/921

    if(SEED)set.seed(2) # set seed of random number generator so that# results can be duplicated.xbars

  • 8/10/2019 Rallfun-v26.txt

    328/921

    points(bvec)totv

  • 8/10/2019 Rallfun-v26.txt

    329/921

    # The default number of bootstrap samples is nboot=599## This function uses functions trimparts and trimpartt written for this# book.####if(is.data.frame(x))x=as.matrix(x)if(pr){print("Note: confidence intervals are adjusted to control FWE")print("But p-values are not adjusted to control FWE")}con

  • 8/10/2019 Rallfun-v26.txt

    330/921

    testb

  • 8/10/2019 Rallfun-v26.txt

    331/921

    #if(!is.matrix(x))stop("X values should be stored in a matrix")if(ncol(x)==1)stop("There should be two or more predictors")temp

  • 8/10/2019 Rallfun-v26.txt

    332/921

    }rval}adcom

  • 8/10/2019 Rallfun-v26.txt

    333/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    334/921

    fhat.old

  • 8/10/2019 Rallfun-v26.txt

    335/921

    #if(!is.null(q))qval=qxy=elimna(cbind(x,y))if(ncol(xy)>2)stop("Only One Predictor Allowed")x=xy[,1]y=xy[,2]if(xout){x

  • 8/10/2019 Rallfun-v26.txt

    336/921

    y

  • 8/10/2019 Rallfun-v26.txt

    337/921

    # For MOM or M-estimators, use spmcpi which uses a bootstrap method## The R variable x is assumed to contain the raw# data stored in list mode or in a matrix.# If in list mode, x[[1]] contains the data# for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    338/921

    if(j

  • 8/10/2019 Rallfun-v26.txt

    339/921

    # first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    340/921

    ){## Plot regression surface using generalized additive model## sop=F, use usual linear model y~x1+x2...# sop=T, use splines#library(akima)library(mgcv)x

  • 8/10/2019 Rallfun-v26.txt

    341/921

    last}

    rgvar

  • 8/10/2019 Rallfun-v26.txt

    342/921

    se1

  • 8/10/2019 Rallfun-v26.txt

    343/921

  • 8/10/2019 Rallfun-v26.txt

    344/921

    output

  • 8/10/2019 Rallfun-v26.txt

    345/921

    ## Test all linear contrasts associated with# main effects for Factor A and B and all interactions based on trimmed means# By default,# tr=.2, meaning 20% trimming is used.# # The data are assumed to be stored in x in list mode or in a matrix. # If grp is unspecified, it is assumed x[[1]] contains the data # for the first level of both factors: level 1,1. # x[[2]] is assumed to contain the data for level 1 of the # first factor and level 2 of the second factor: level 1,2 # x[[j+1]] is the data for level 2,1, etc. # If the data are in wrong order, grp can be used to rearrange the # groups. For example, for a two by two design, grp

  • 8/10/2019 Rallfun-v26.txt

    346/921

    con

  • 8/10/2019 Rallfun-v26.txt

    347/921

    sig.level = dv[1:nboot])/nbootif(plotit && ncol(m1)==2){if(pop==2)rdplot(mdif,fr=fr)if(pop==1){plot(mdif[,1],mdif[,2],xlab="VAR 1",ylab="VAR 2",type="n")points(mdif[,1],mdif[,2],pch=".")points(center[1],center[2],pch="o")points(0,0,pch="+")}if(pop==3)akerdmul(mdif,fr=fr)}list(p.value=sig.level,center=tvec)}

    mwmw

  • 8/10/2019 Rallfun-v26.txt

    348/921

    center

  • 8/10/2019 Rallfun-v26.txt

    349/921

    }if(qval!=.5){START

  • 8/10/2019 Rallfun-v26.txt

    350/921

    # Plot of running interval smoother based on specified quantiles in# qval## fr controls amount of smoothing# tr is the amount of trimming## Missing values are automatically removed.#rmd1

  • 8/10/2019 Rallfun-v26.txt

    351/921

    if(plotit)plotfun(x,y-yhat,eout=eout,xout=xout,expand = 0.5,scale=FALSE,xlab="X",ylab="Y",zlab="",theta=50,phi=25,...)output}

    gvar2g

  • 8/10/2019 Rallfun-v26.txt

    352/921

    }if(p1==6){if(n1>=60)adalpha

  • 8/10/2019 Rallfun-v26.txt

    353/921

    ## Take a matrix having p columns and convert# it to a matrix having jval columns and np/jval rows# So take first jval columns, and rbind this with# next jval columns, etc.#x

  • 8/10/2019 Rallfun-v26.txt

    354/921

    # pts, a matrix that can be used to specify design points to be used# number of columns should equal number of covariates.## depfun determines how depth of a point is determinted,# default is projection depth## The output includes a matrix of sample sizes. The ith row# corresponds to the ith point used to compare groups.# The jth column indicates the number of points (the sample size)# that was found for the jth group. That is, how many points# in the jth group were found that are close to the design point# under consideration.#library(MASS)output

  • 8/10/2019 Rallfun-v26.txt

    355/921

    tempy

  • 8/10/2019 Rallfun-v26.txt

    356/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    357/921

    # The output includes a matrix of sample sizes. The ith row# corresponds to the ith point used to compare groups.# The jth column indicates the number of points (the sample size)# that was found for the jth group. That is, how many points# in the jth group were found that are close to the design point# under consideration.#if(SEED)set.seed(2) # set the seed so that MVE always gives same resultif(pr){if(op==1)print("Trimmed means are to be compared. For medians, use op=2")if(op==2)print("Medians are to be compared. For trimmed means, use op=1")if(op==3)print("20% trimmed means are compared. For medians, use op=4")if(op==4)print("medians are compared. For 20% trimmed means, use op=3")}output

  • 8/10/2019 Rallfun-v26.txt

    358/921

    xm

  • 8/10/2019 Rallfun-v26.txt

    359/921

  • 8/10/2019 Rallfun-v26.txt

    360/921

    output[,5]

  • 8/10/2019 Rallfun-v26.txt

    361/921

    if(plotit){plot(c(x,x[1],x[2]),c(vals,-5,5),xlab=xlab,ylab=ylab)xord

  • 8/10/2019 Rallfun-v26.txt

    362/921

    mat[it,]

  • 8/10/2019 Rallfun-v26.txt

    363/921

    ## This function performs an omnibus test using data corresponding# to K design points specified by the argument pts. If# pts=NA, K=5 points are chosen for you (see Introduction to Robust# Estimation and Hypothesis Testing.)# Null hypothesis is that conditional distribution of Y, given X for first# group, minus the conditional distribution of Y, given X for second# group is equal to zero.# The strategy is to choose K specific X values# and then test the hypothesis that all K differences are zero.## If you want to choose specific X values, Use the argument# pts# Example: pts=c(1,3,5) will use X=1, 3 and 5.## For multiple comparisons using these J points, use ancpb## Assume data are in x1 y1 x2 and y2## PRO=F, means Mahalanobis distance is used.# PRO=T, projection distance is used.## fr1 and fr2 are the spans used to fit a smooth to the data.#

    stop('USE ancGLOB')##gv1

  • 8/10/2019 Rallfun-v26.txt

    364/921

    if(SEED)set.seed(2)bvec

  • 8/10/2019 Rallfun-v26.txt

    365/921

    }nullv

  • 8/10/2019 Rallfun-v26.txt

    366/921

    #if(!is.matrix(x))stop("X values should be stored in a matrix")if(ncol(x)==1)stop("There should be two or more predictors")temp

  • 8/10/2019 Rallfun-v26.txt

    367/921

    # For p>1, method tests for each p whether residuals and x_j# have a horizontal regression line.## op2=F, tests for homogeneity using running interval smoother# op2=T, test of independence based on Y-M(Y), M(Y) some measure# of location given by argument est.# In general, op2=T should NOT be used when the goal is to test# the hypothesis of a homoscedastic error term.## op=1 test using regression method (function regci)# op=2 test using Winsorized correlation# tr is amount of winsorizing.# op=3 test using a wild boostrap method#x

  • 8/10/2019 Rallfun-v26.txt

    368/921

    rho c2^2]

  • 8/10/2019 Rallfun-v26.txt

    369/921

    # sigmamu is any user supplied function having the form# sigmamu(x,mu.too=F) and which computes a robust measure of# of dispersion if mu.too=F. If mu.too=T, it returns# a robust measure of location as well.# v is any robust covariance#if(!is.matrix(x))stop("x should be a matrix")x

  • 8/10/2019 Rallfun-v26.txt

    370/921

    sqrt.gamma

  • 8/10/2019 Rallfun-v26.txt

    371/921

    x

  • 8/10/2019 Rallfun-v26.txt

    372/921

    }splot

  • 8/10/2019 Rallfun-v26.txt

    373/921

    tbscor

  • 8/10/2019 Rallfun-v26.txt

    374/921

    if(test>=crit)p.value

  • 8/10/2019 Rallfun-v26.txt

    375/921

    ci

  • 8/10/2019 Rallfun-v26.txt

    376/921

  • 8/10/2019 Rallfun-v26.txt

    377/921

    deps

  • 8/10/2019 Rallfun-v26.txt

    378/921

    fkp

  • 8/10/2019 Rallfun-v26.txt

    379/921

    ## See Fan, Annals of Statistics, 1993, 21, 196-217.# cf. Bjerve and Doksum, Annals of Statistics, 1993, 21, 890-902## With a single predictor, this function calls locreg# See locreg for information about np and plotting#library(akima)x

  • 8/10/2019 Rallfun-v26.txt

    380/921

    epan

  • 8/10/2019 Rallfun-v26.txt

    381/921

    if(abs(X[J[1]] - X[J[2]]) < 1/100000000) {slope

  • 8/10/2019 Rallfun-v26.txt

    382/921

    cci

  • 8/10/2019 Rallfun-v26.txt

    383/921

    cltv gam.

    k

  • 8/10/2019 Rallfun-v26.txt

    384/921

    mds[, j]

  • 8/10/2019 Rallfun-v26.txt

    385/921

    if(outliers == T) {val

  • 8/10/2019 Rallfun-v26.txt

    386/921

    x

  • 8/10/2019 Rallfun-v26.txt

    387/921

    corrsim

  • 8/10/2019 Rallfun-v26.txt

    388/921

    medd2

  • 8/10/2019 Rallfun-v26.txt

    389/921

    covs

  • 8/10/2019 Rallfun-v26.txt

    390/921

    covsim2

  • 8/10/2019 Rallfun-v26.txt

    391/921

    # Click right mouse button to end the function.# Unix systems turn on graphics device eg enter# command "X11()" or "motif()" before using.# R users need to type "library(lqs)" before using.

    p

  • 8/10/2019 Rallfun-v26.txt

    392/921

    for(i in 1:steps) {md2

  • 8/10/2019 Rallfun-v26.txt

    393/921

  • 8/10/2019 Rallfun-v26.txt

    394/921

    # Rapidly plots 20 DD plots in a row.# Unix: type "X11()" or "motif()" to# turn on a graphics device.# RDi uses covmba for type = 1, rmba for type = 2, cov.mcd for type = 3

    med

  • 8/10/2019 Rallfun-v26.txt

    395/921

    val1

  • 8/10/2019 Rallfun-v26.txt

    396/921

    if((j1 - j2) >= 0) {ind

  • 8/10/2019 Rallfun-v26.txt

    397/921

    rmat

  • 8/10/2019 Rallfun-v26.txt

    398/921

    print("got OLS")l1fit

  • 8/10/2019 Rallfun-v26.txt

    399/921

    list(fycorr=fycorr)}

    gamper

  • 8/10/2019 Rallfun-v26.txt

    400/921

    lines(lowess(ESP,y),type="s") }

    llrplot

  • 8/10/2019 Rallfun-v26.txt

    401/921

  • 8/10/2019 Rallfun-v26.txt

    402/921

    }}

    lrdata

  • 8/10/2019 Rallfun-v26.txt

    403/921

    # change formula to x[,1]+ ... + x[,q] with qout

  • 8/10/2019 Rallfun-v26.txt

    404/921

    # Generates the classical mahalanobis distances.center

  • 8/10/2019 Rallfun-v26.txt

    405/921

    md2

  • 8/10/2019 Rallfun-v26.txt

    406/921

    #Use OLS on rows with md2

  • 8/10/2019 Rallfun-v26.txt

    407/921

    {# Forward response plot and residual plot.# R needs command "library(lqs)" if a robust estimator replaces lsfit.# Advance the view with the right mouse button.

    x

  • 8/10/2019 Rallfun-v26.txt

    408/921

    mplot

  • 8/10/2019 Rallfun-v26.txt

    409/921

    beta

  • 8/10/2019 Rallfun-v26.txt

    410/921

    {# compares new and classical PIs for multiple linear regression# if type = 1 for N(0,1) errors, 2 for t3 errors, 3 for exp(1) - 1 errors# 4 for uniform(-1,1) errors, 5 for (1-eps) N(0,1) + eps N(0,(1+shift)^2) errors# constant = 1 so there are p = q+1 coefficients

    b

  • 8/10/2019 Rallfun-v26.txt

    411/921

    pilen[i, 1] yf) cpicov

  • 8/10/2019 Rallfun-v26.txt

    412/921

    nmUM (med + k2 * madd))n

  • 8/10/2019 Rallfun-v26.txt

    413/921

    rdf

  • 8/10/2019 Rallfun-v26.txt

    414/921

    val

  • 8/10/2019 Rallfun-v26.txt

    415/921

    # Makes an RR plot. Needs the mbareg function.n

  • 8/10/2019 Rallfun-v26.txt

    416/921

    # a full description of the XploRe program can be found in (chapter 11)# 'XploRe: An interactive statistical computing environment',# W. Haerdle, S. Klinke, B.A. Turlach, Springer, 1995## This software can be freely used for non-commercial purposes and freely# distributed.#+-----------------------------------------------------------------------------+#| Thomas Koetter |#| Institut fuer Statistik und Oekonometrie |#| Fakultaet Wirtschaftswissenschaften |#| Humboldt-Universitaet zu Berlin, 10178 Berlin, GERMANY |#+-----------------------------------------------------------------------------+#| Tel. voice: +49 30 2468-321 |#| Tel. FAX: +49 30 2468-249 |#| E-mail: [email protected] |#+-----------------------------------------------------------------------------+

    n

  • 8/10/2019 Rallfun-v26.txt

    417/921

    slend[ns]

  • 8/10/2019 Rallfun-v26.txt

    418/921

    labs

  • 8/10/2019 Rallfun-v26.txt

    419/921

    x

  • 8/10/2019 Rallfun-v26.txt

    420/921

    for(i in 1:length(lam)) {if(lam[i] == 0)

    ytem

  • 8/10/2019 Rallfun-v26.txt

    421/921

    "40%", "30%", "20%", "10%", "0%")tem

  • 8/10/2019 Rallfun-v26.txt

    422/921

    skipcov

  • 8/10/2019 Rallfun-v26.txt

    423/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    424/921

    Mpca

  • 8/10/2019 Rallfun-v26.txt

    425/921

    Bp

  • 8/10/2019 Rallfun-v26.txt

    426/921

    for(i in 1:n)scores[i,]

  • 8/10/2019 Rallfun-v26.txt

    427/921

    covs

  • 8/10/2019 Rallfun-v26.txt

    428/921

    iter

  • 8/10/2019 Rallfun-v26.txt

    429/921

    limvec

  • 8/10/2019 Rallfun-v26.txt

    430/921

    }chi.int.p

  • 8/10/2019 Rallfun-v26.txt

    431/921

    gvarg

  • 8/10/2019 Rallfun-v26.txt

    432/921

    temp

  • 8/10/2019 Rallfun-v26.txt

    433/921

    if(is.null(B)){if(p>0 && p

  • 8/10/2019 Rallfun-v26.txt

    434/921

    # for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# x[[K]] is the data for level 1,K# x[[K+1]] is the data for level 2,1, x[[2K]] is level 2,K, etc.## If the data are in a matrix, column 1 is assumed to# correspond to x[[1]], column 2 to x[[2]], etc.## When in list mode x is assumed to have length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp# if(is.matrix(x)) { y

  • 8/10/2019 Rallfun-v26.txt

    435/921

    output[ic,1]

  • 8/10/2019 Rallfun-v26.txt

    436/921

    np

  • 8/10/2019 Rallfun-v26.txt

    437/921

    obj.old

  • 8/10/2019 Rallfun-v26.txt

    438/921

    # x[[1]] contains the data for the first group, x[[2]] the data# for the second group, etc. Length(x)=the number of groups = J, say.## Or the data can be stored in a matrix with J columns## By default, all pairwise comparisons are performed, but contrasts# can be specified with the argument con.# The columns of con indicate the contrast coefficients.# Con should have J rows, J=number of groups.# For example, con[,1]=c(1,1,-1,-1,0,0) and con[,2]=c(,1,-1,0,0,1,-1)# will test two contrasts: (1) the sum of the first two trimmed means is# equal to the sum of the second two, and (2) the difference between# the first two is equal to the difference between the trimmed means of# groups 5 and 6.## The default number of bootstrap samples is nboot=2000##con

  • 8/10/2019 Rallfun-v26.txt

    439/921

    if(d==3 && alpha==.05 && nboot==2000)crit

  • 8/10/2019 Rallfun-v26.txt

    440/921

    psihat[d,4]

  • 8/10/2019 Rallfun-v26.txt

    441/921

    ## xout=F, when plotting, keep leverage points# sm=F, when plotting, do not use bootstrap bagging## Assume data are in x1 y1 x2 and y2## fr1 and fr2 are the spans used by the smooth.## RNA=F, when computing bagged estimate, NA values are not removed# resulting in no estimate of Y at the specified design point,# RNA=T, missing values are removed and the remaining values are used.#xy=elimna(cbind(x1,y1))x1=xy[,1]y1=xy[,2]xy=elimna(cbind(x2,y2))x2=xy[,1]y2=xy[,2]#if(xout){flag

  • 8/10/2019 Rallfun-v26.txt

    442/921

    mat[i,2]

  • 8/10/2019 Rallfun-v26.txt

    443/921

    j

  • 8/10/2019 Rallfun-v26.txt

    444/921

    ## the iterative process stops when ||m_k - m_{k+1}|| < tol. ## maxit: maximum number of iterations ## init.m: starting value for m; typically coordinatewise median ## ## Ref: Hossjer and Croux (1995) ## "Generalizing Univariate Signed Rank Statistics for Testing ## and Estimating a Multivariate Location Parameter"; ## Non-parametric Statistics, 4, 293-308. ## ## Implemented by Kristel Joossens ## Many thanks to Martin Maechler for improving the program!

    ## slightly faster version of 'sweep(x, 2, m)': centr

  • 8/10/2019 Rallfun-v26.txt

    445/921

    } if (k > maxit) warning("iterations did not converge in ", maxit, " steps") if(trace == 1) cat("needed", k, "iterations with a total of", sum(nstps), "stepsize halvings\n")# return(m)list(center=m)}

    matl

  • 8/10/2019 Rallfun-v26.txt

    446/921

    # print.all=T reports all confidence intervals, the number of which can# be large.#if(!is.list(x) && !is.matrix(x))stop("store data in list mode or a matrix")if(SEED)set.seed(2)if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    447/921

    # print.all=F,# returns number sig, meaning number of confidence intervals that do not# contain zero,# the critical value used as well as the KS test statistics.# print.all=T reports all confidence intervals, the number of which can# be large.#if(!is.list(x) && !is.matrix(x))stop("store data in list mode or a matrix")if(SEED)set.seed(2)if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    448/921

    # grp indicates the groups to be compared. By default grp=c(1,2,3,4)# meaning that the first four groups are used with the difference between# the first two compared to the difference between the second two.# (Rows are being compared in a 2 by 2 design# To compare difference between groups 1 and 3 versus 2 and 4 (columns in# a 2 by 2 design), set grp=c(1,3,2,4).## print.all=F,# returns number sig, meaning number of confidence intervals that do not# contain zero,# the critical value used as well as the KS test statistics.# print.all=T reports all confidence intervals, the number of which can# be large.#if(!is.list(x) && !is.matrix(x))stop("store data in list mode or a matrix")if(SEED)set.seed(2)if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    449/921

    # x is assumed to be a matrix with columns corresponding to groups# or x and have list mode.## four groups are analyzed,## grp indicates the groups to be compared. By default grp=c(1,2,3,4)# meaning that the first four groups are used with the difference between# the first two compared to the difference between the second two.## For four variables stored in x,# this function plots the shift function for the first two# variables as well as the second two.## No disordinal interaction corresponds to the two shift functions being# identical. That is, the difference between the quantiles is always the same## When plotting, the median of x is marked with a + and the two# quaratiles are marked with o.## sm=T, shift function is smoothed using:# op!=1, running interval smoother,# otherwise use lowess.#if(is.matrix(x))x=listm(x)

    if(length(grp)!=4)stop("The argument grp must have 4 values")x=x[grp]for(j in 1:4)x[[j]]=elimna(x[[j]])pc

  • 8/10/2019 Rallfun-v26.txt

    450/921

    ival

  • 8/10/2019 Rallfun-v26.txt

    451/921

    if(is.null(y[1]))m

  • 8/10/2019 Rallfun-v26.txt

    452/921

    if(alpha==.1)crit

  • 8/10/2019 Rallfun-v26.txt

    453/921

    ## It returns a measure of location and scatter for the# multivariate data in x, which is assumed to have# p>-2 column and n rows.## This code is based on a very slight modificatiion of code originally# written by David Olive#x

  • 8/10/2019 Rallfun-v26.txt

    454/921

    con

  • 8/10/2019 Rallfun-v26.txt

    455/921

    test[jcom,1]

  • 8/10/2019 Rallfun-v26.txt

    456/921

    if(sum(sigvec)

  • 8/10/2019 Rallfun-v26.txt

    457/921

    # Compute a modified Theil--Sen regression estimator.# Use s-type initial estimate, eliminate points with# outlying residuals, then do regular Theil--Sen#x

  • 8/10/2019 Rallfun-v26.txt

    458/921

    # using a rank-based method that tests for equal distributions.## A between by within subjects design is assumed.# Levels of Factor A are assumed to be independent and# levels of Factor B are dependent.## The data are assumed to be stored in x in list mode or in a matrix.# If grp is unspecified, it is assumed x[[1]] contains the data# for the first level of both factors: level 1,1.# x[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second factor: level 1,2# x[[j+1]] is the data for level 2,1, etc.# If the data are in wrong order, grp can be used to rearrange the# groups. For example, for a two by two design, grp

  • 8/10/2019 Rallfun-v26.txt

    459/921

    if(ncon > 10){avec

  • 8/10/2019 Rallfun-v26.txt

    460/921

    Fac.AB[ic,4]

  • 8/10/2019 Rallfun-v26.txt

    461/921

    mat[i,3]

  • 8/10/2019 Rallfun-v26.txt

    462/921

    gv[[i]]

  • 8/10/2019 Rallfun-v26.txt

    463/921

    if(is.vector(m)){if(!is.list(m)){flag=(m==na.val)m[flag]=NA}}if(is.matrix(m)){for(j in 1:ncol(m)){x=m[,j]flag=(x==na.val)x[flag]=NAm[,j]=x}}if(is.list(m)){for(j in 1:length(m)){x=m[[j]]flag=(x==na.val)x[flag]=NAm[[j]]=x}}m}

    rm2mcp

  • 8/10/2019 Rallfun-v26.txt

    464/921

    # # Create the three contrast matrices #temp

  • 8/10/2019 Rallfun-v26.txt

    465/921

    temp[i]

  • 8/10/2019 Rallfun-v26.txt

    466/921

    if(!is.list(x))stop("Data must be stored in list mode or in matrix mode.")if(!is.na(grp)){ # Only analyze specified groups.xx

  • 8/10/2019 Rallfun-v26.txt

    467/921

    if(op==4)print(sig.level)list(sig.level=sig.level,output=output)}

    medind

  • 8/10/2019 Rallfun-v26.txt

    468/921

    0.001045346, 0.001347837, 0.001579373, 0.001864344),ncol=4,nrow=7,byrow=T)resmat3=matrix(c(0.071555715, 0.082937665, 0.089554679, 0.097538044,0.031060795, 0.035798539, 0.043862556, 0.053712151,0.019503635, 0.023776479, 0.027180121, 0.030991367,0.011030001, 0.013419347, 0.015557409, 0.017979524,0.005634478, 0.006804788, 0.007878358, 0.008807657,0.002552182, 0.003603778, 0.004275965, 0.005021989,0.001251044, 0.001531919, 0.001800608, 0.002037870),ncol=4,nrow=7,byrow=T)resmat4=matrix(c(0.093267532, 0.101584002, 0.108733965, 0.118340448,0.038677863, 0.045519806, 0.051402903, 0.060097046,0.024205231, 0.029360145, 0.034267265, 0.039381482,0.013739157, 0.015856343, 0.018065898, 0.019956084,0.006467562, 0.007781030, 0.009037972, 0.010127143,0.003197162, 0.003933525, 0.004656625, 0.005929469,0.001652690, 0.001926060, 0.002363874, 0.002657071),ncol=4,nrow=7,byrow=T)resmat5=matrix(c(0.117216934, 0.124714114, 0.129458602, 0.136456163,0.048838630, 0.055608712, 0.060580045, 0.067943676,0.030594644, 0.035003872, 0.040433885, 0.047648696,0.016940240, 0.019527491, 0.022047442, 0.025313443,0.008053039, 0.009778574, 0.011490394, 0.013383628,0.003760567, 0.004376294, 0.005097890, 0.005866240,

    0.001894616, 0.002253522, 0.002612405, 0.002938808),ncol=4,nrow=7,byrow=T)resmat6=matrix(c(0.136961531, 0.144120225, 0.149003907, 0.152667432,0.055909481, 0.062627211, 0.069978086, 0.081189957,0.034634825, 0.040740587, 0.044161376, 0.047722045,0.020165417, 0.023074738, 0.025881208, 0.028479913,0.009436297, 0.011246968, 0.013220963, 0.015100546,0.004644596, 0.005334418, 0.006040595, 0.007237195,0.002277590, 0.002635712, 0.002997398, 0.003669488),ncol=4,nrow=7,byrow=T)resmat7=matrix(c(0.156184672, 0.163226643, 0.171754686, 0.177142753,0.070117003, 0.077052773, 0.082728047, 0.090410797,0.041774517, 0.047379662, 0.053101833, 0.057674454,

    0.023384451, 0.026014421, 0.029609042, 0.032619018,0.010856382, 0.012567043, 0.013747870, 0.016257014,0.005164004, 0.006131755, 0.006868101, 0.008351046,0.002537642, 0.003044154, 0.003623654, 0.003974469),ncol=4,nrow=7,byrow=T)resmat8=matrix(c(0.178399742, 0.180006714, 0.193799396, 0.199585892,0.078032767, 0.085624186, 0.091511226, 0.102491785,0.045997886, 0.052181615, 0.057362163, 0.062630424,0.025895739, 0.029733034, 0.033764463, 0.037873655,0.012195876, 0.013663248, 0.015487587, 0.017717864,0.005892418, 0.006876488, 0.007893475, 0.008520783,0.002839731, 0.003243909, 0.003738571, 0.004124057),ncol=4,nrow=7,byrow=T)crit5=array(cbind(resmat1,resmat2,resmat3,resmat4,resmat5,resmat6,resmat7,

    resmat8),c(7,4,8))flag=Tcrit.val=NULLif(p > 8)flag=Fif(n=400)flag=Faval

  • 8/10/2019 Rallfun-v26.txt

    469/921

    asel=c(0,aval)ialpha=nalpha[aokay]critit=crit5[,ialpha,p]nvec

  • 8/10/2019 Rallfun-v26.txt

    470/921

    0.007334749, 0.008406468, 0.009392098, 0.010919651,0.003352200, 0.003814582, 0.004380562, 0.005252154,0.001703698, 0.002001713, 0.002338651, 0.002772864),ncol=4,nrow=7,byrow=T)resmat7=matrix(c(0.106573121, 0.113058950, 0.117388191, 0.121286795,0.052170054, 0.058363322, 0.064733684, 0.069749344,0.030696897, 0.035506926, 0.039265698, 0.044437674,0.016737307, 0.019605734, 0.021253610, 0.022922988,0.007767232, 0.009231789, 0.010340874, 0.011471110,0.003998261, 0.004590177, 0.005506926, 0.006217415,0.001903372, 0.002174748, 0.002519055, 0.002858655),ncol=4,nrow=7,byrow=T)resmat8=matrix(c(0.119571179, 0.126977461, 0.130120853, 0.133258294,0.059499563, 0.067185338, 0.071283297, 0.079430577,0.034310968, 0.039827130, 0.044451690, 0.048512464,0.018599530, 0.021093909, 0.023273085, 0.027471116,0.009135712, 0.010901687, 0.012288682, 0.013729545,0.004382249, 0.005191810, 0.005598429, 0.006484433,0.002196973, 0.002525918, 0.002818550, 0.003242426),ncol=4,nrow=7,byrow=T)crit5=array(cbind(resmat1,resmat2,resmat3,resmat4,resmat5,resmat6,resmat7,resmat8),c(7,4,8))flag=Tcrit.val=NULLif(p > 8)flag=F

    if(n=400)flag=Faval

  • 8/10/2019 Rallfun-v26.txt

    471/921

    ran.mat

  • 8/10/2019 Rallfun-v26.txt

    472/921

    psi

  • 8/10/2019 Rallfun-v26.txt

    473/921

    # function terminates.##if(is.matrix(x))x

  • 8/10/2019 Rallfun-v26.txt

    474/921

    for(it in 1:iter){for(ip in 1:p){res[,ip]

  • 8/10/2019 Rallfun-v26.txt

    475/921

    bval

  • 8/10/2019 Rallfun-v26.txt

    476/921

    if(p==2){regp2plot(x,y,regfun=ols,xlab=xlab,ylab=ylab,zlab=zlab)}}Ftest

  • 8/10/2019 Rallfun-v26.txt

    477/921

  • 8/10/2019 Rallfun-v26.txt

    478/921

    val2=NAx=xx[,iv]xy=elimna(cbind(x,y))x=xy[,1:2]y=xy[,3]if(xout){x

  • 8/10/2019 Rallfun-v26.txt

    479/921

    if(m==0)m

  • 8/10/2019 Rallfun-v26.txt

    480/921

    flag

  • 8/10/2019 Rallfun-v26.txt

    481/921

    res2=y1[!flag]-yh2[!flag]dep1=resdepth(x1,res1)dep2=resdepth(x1[!flag],res2)list(dep1=dep1,dep2=dep2)}

    ancsm1)stop("One covariate only is allowed")if(xout){flag1=outfun(x1,...)$keepflag2=outfun(x2,...)$keep

    x1=x1[flag1]y1=y1[flag1]x2=x2[flag2]y2=y2[flag2]}xy=elimna(cbind(x1,y1))x1=xy[,1]xord=order(x1)x1=x1[xord]y1=xy[xord,2]xy=elimna(cbind(x2,y2))x2=xy[,1]xord=order(x2)

    x2=x2[xord]y2=xy[xord,2]n1=length(y1)n2=length(y2)if(is.null(fr)){fr=1if(min(n1,n2)>150)fr=.2if(max(n1,n2)

  • 8/10/2019 Rallfun-v26.txt

    482/921

    }}if(plotit)runmean2g(x1,y1,x2,y2,fr=fr,est=est,sm=sm,xlab=xlab,ylab=ylab,LP=LP,...)dep=depthcom(x1,y1,x2,y2,est=est,fr=fr)n=min(n1,n2)pv=1-mean(crit.mat

  • 8/10/2019 Rallfun-v26.txt

    483/921

  • 8/10/2019 Rallfun-v26.txt

    484/921

    btest

  • 8/10/2019 Rallfun-v26.txt

    485/921

    crit=crit)p.value

  • 8/10/2019 Rallfun-v26.txt

    486/921

    # very poor outside rate per obs under normality.t1

  • 8/10/2019 Rallfun-v26.txt

    487/921

    z2=(y-mean(y))/sqrt(var(y))ans=olshc4sub(z1,z2,CN=CN)ci=ans$ci[2,3:4]ci}

    TWOpNOV

  • 8/10/2019 Rallfun-v26.txt

    488/921

    if(ncol(x)!=2)stop("x should be a matrix with two columns")xy=elimna(cbind(x,y))x1=xy[,1]x2=xy[,2]y=xy[,3]r12=cor(x1,y)r13=cor(x2,y)r23=cor(x1,x2)ci12=pcorhc4(x1,y,alpha=alpha,CN=CN)$cici13=pcorhc4(x2,y,alpha=alpha,CN=CN)$cicorhat=((r23-.5*r12*r13)*(1-r12^2-r13^2-r23^2)+r23^3)/((1-r12^2)*(1-r13^2))term1=2*corhat*(r12-ci12[1])*(ci13[2]-r13)term2=2*corhat*(r12-ci12[2])*(ci13[1]-r13)L=r12-r13-sqrt((r12-ci12[1])^2+(ci13[2]-r13)^2-term1)U=r12-r13+sqrt((r12-ci12[2])^2+(ci13[1]-r13)^2-term2)c(L,U)}sm2str.sub

  • 8/10/2019 Rallfun-v26.txt

    489/921

    pv=2*min(c(pv,1-pv))p.crit=.25*abs(vcor[1,2])+.05+(100-length(y))/10000p.crit=max(c(.05,p.crit))list(p.value=pv,p.crit=p.crit)}

    pcorhc4

  • 8/10/2019 Rallfun-v26.txt

    490/921

    x

  • 8/10/2019 Rallfun-v26.txt

    491/921

    # data[[L+1]] is the data for level 1,2,1. data[[2L]] is level 1,2,L.# data[[KL+1]] is level 2,1,1, etc.## The default amount of trimming is tr=.2## It is assumed that data has length JKL, the total number of# groups being tested.#if(is.data.frame(data))data=as.matrix(data)if(is.list(data))data=listm(elimna(matl(data)))if(is.matrix(data))data=listm(elimna(data))if(!is.list(data))stop("Data are not stored in list mode or a matrix")if(p!=length(data)){print("The total number of groups, based on the specified levels, is")print(p)print("The number of groups in data is")print(length(data))print("Warning: These two values are not equal")}tmeans

  • 8/10/2019 Rallfun-v26.txt

    492/921

    Qac.siglevel

  • 8/10/2019 Rallfun-v26.txt

    493/921

    if(!is.null(q))qval=qx=as.matrix(x)if(xout){flag

  • 8/10/2019 Rallfun-v26.txt

    494/921

    ## (y can be multivariate)#library(MASS)if(!is.matrix(y))stop("y is not a matrix")X

  • 8/10/2019 Rallfun-v26.txt

    495/921

    if(!xnum)par(xaxt="n")mval

  • 8/10/2019 Rallfun-v26.txt

    496/921

    p.value

  • 8/10/2019 Rallfun-v26.txt

    497/921

    # data[[2]] is assumed to contain the data for level 1 of the# first factor and level 2 of the second: level 1,2# data[[K]] is the data for level 1,K# data[[K+1]] is the data for level 2,1, data[2K] is level 2,K, etc.## It is assumed that data has length JK, the total number of# groups being tested, but a subset of the data can be analyzed# using grp#if(is.data.frame(x))x=as.matrix(x)if(is.list(x))x

  • 8/10/2019 Rallfun-v26.txt

    498/921

    x^2*dnorm(x)}ebarplot

  • 8/10/2019 Rallfun-v26.txt

    499/921

    # is intended to be rate=.05## When dealing with p-variate data, p>9, this adjustment can be crucial#m=elimna(m)n=nrow(m)if(SEED)set.seed(2)z=array(rmul(n*iter*ncol(m)),c(iter,n,ncol(m)))newq=0gtry=NAfor(itry in 1:ip){newq=newq+9/10^itrygtry[itry]=newq}gtry=c(.95,.975,gtry[-1])if(pr)print("Computing adjustment")for(itry in 1:ip){val=NAfor(i in 1:iter){temp=outpro(z[i,,],gval = sqrt(qchisq(gtry[itry],ncol(m))),center=center,plotit=FALSE,op=op,MM=MM,cop=cop,STAND=STAND)$out.idval[i]=length(temp)}erate=mean(val)/n

    if(erate

  • 8/10/2019 Rallfun-v26.txt

    500/921

    if(!is.matrix(x))stop("With y missing, x should be a matrix")}if(!is.null(y[1]))x

  • 8/10/2019 Rallfun-v26.txt

    501/921

    of groups.")mat

  • 8/10/2019 Rallfun-v26.txt

    502/921

    ic

  • 8/10/2019 Rallfun-v26.txt

    503/921

    # (Munzel and Brunner, Biometrical J., 2000, 42, 837--854## x can be a matrix with columns corresponding to groups## Have a J by K design with J independent levels and K dependent# measures## or it can have list mode.#newx=list()GV=matrix(c(1:p),ncol=K,byrow=TRUE)if(is.list(x)){temp=NAjk=0for(j in 1:J){temp=elimna(matl(x[GV[j,]]))for(k in 1:K){jk=jk+1newx[[jk]]=temp[,k]}}x=NAx=newx}if(is.matrix(x)){

    x=elimna(x)x

  • 8/10/2019 Rallfun-v26.txt

    504/921

    for (j in 2:J){jk

  • 8/10/2019 Rallfun-v26.txt

    505/921

    sam[j]=length(x[[j]])h[j]

  • 8/10/2019 Rallfun-v26.txt

    506/921

    if(flag){if(alpha==.05)crit

  • 8/10/2019 Rallfun-v26.txt

    507/921

    init$coef}ex=varfun(yhat)/varfun(y)str=sqrt(ex)hatv=NULLif(YHAT)hatv=yhatlist(results=init,Explanatory.Power=ex,Strength.Assoc=str,yhat=hatv)}

    smcorcom

  • 8/10/2019 Rallfun-v26.txt

    508/921

    temp2=tsreg(c(50,100),c(.21,.08))$coeftemp3=tsreg(c(30,50),c(.3,.21))$coefif(n1

  • 8/10/2019 Rallfun-v26.txt

    509/921

    r[,p]

  • 8/10/2019 Rallfun-v26.txt

    510/921

    library(stats)x

  • 8/10/2019 Rallfun-v26.txt

    511/921

    if(plotit){plot(x,y,xlab=xlab,ylab=ylab)lines(lowess(x,y,f=low.span))}yyy

  • 8/10/2019 Rallfun-v26.txt

    512/921

    ## pairs of observations, for which one value is missing, are NOT deleted.# Marginal trimmed means are compared# using all available data.#if(is.null(y)){if(!is.matrix(x))stop("y is null and x is not a matrix")y=x[,2]x=x[,1]}if(length(x)!=length(y))stop("The number of observations must be equal")m

  • 8/10/2019 Rallfun-v26.txt

    513/921

    }if(!is.null(y))x=cbind(x,y)if(ncol(x)!=2)print("warning: x has more than one column; columns 1 and 2 are used")n=nrow(x)test=yuendna(x,tr=tr)cen=xcen[,1]=cen[,1]-mean(x[,1],na.rm=TRUE,tr=tr)cen[,2]=cen[,2]-mean(x[,2],na.rm=TRUE,tr=tr)data=matrix(sample(n,n*nboot,replace=TRUE),ncol=nboot)tval=apply(data,2,FUN=rm2miss.sub,x=cen,tr=tr)tval=sort(abs(tval))icrit

  • 8/10/2019 Rallfun-v26.txt

    514/921

    ci[1]

  • 8/10/2019 Rallfun-v26.txt

    515/921

    d

  • 8/10/2019 Rallfun-v26.txt

    516/921

    dvecba

  • 8/10/2019 Rallfun-v26.txt

    517/921

    if(is.na(grp[1]))grp

  • 8/10/2019 Rallfun-v26.txt

    518/921

    if(n1==n2){temp=effectg.sub(x,y,locfun=locfun,varfun=varfun,...)e.pow=temp$Var.Explained}if(n1!=n2){N=min(c(n1,n2))vals=0for(i in 1:nboot)vals[i]=effectg.sub(sample(x,N),sample(y,N),locfun=locfun,varfun=varfun,...)$Var.Explainede.pow=mean(vals)}list(Explanatory.power=e.pow,Effect.Size=sqrt(e.pow))}

    winvarN

  • 8/10/2019 Rallfun-v26.txt

    519/921

    if(is.null(y)){if(is.matrix(x))xy=matl(x)}par(mfrow=c(2,2))par(oma=c(4,0,0,0))ebarplot(xy,xlab=eblabx,ylab=eblaby)boxplot(xy)g2plot(xy[[1]],xy[[2]])sband(xy[[1]],xy[[2]])par(mfrow=c(1,1))}

    yuenv2.5")if(is.null(y)){if(is.matrix(x) || is.data.frame(x)){y=x[,2]x=x[,1]}

    if(is.list(x)){y=x[[2]]x=x[[1]]}}library(MASS)if(SEED)set.seed(2)x

  • 8/10/2019 Rallfun-v26.txt

    520/921

    test1){x0=c(rep(1,length(x)),rep(2,length(y)))y0=c(x,y)e.pow=wincor(x0,y0,tr=tr)$cor^2}}#if(PB){bot=pbvar(pts)e.pow=top/bot}#}

    if(n1!=n2){N=min(c(n1,n2))vals=0for(i in 1:nboot)vals[i]=yuen.effect(sample(x,N),sample(y,N))$Var.Explainede.pow=loc.fun(vals)}if(plotit){plot(xx,pts,xlab=xlab,ylab=ylab)if(op)points(c(1,2),c(m1,m2))if(VL)lines(c(1,2),c(m1,m2))}list(ci=c(low,up),n1=n1,n2=n2,

    p.value=yuen,dif=dif,se=sqrt(q1+q2),teststat=test,crit=crit,df=df,Var.Explained=e.pow,Effect.Size=sqrt(e.pow))}

    yuen.effect.ci

  • 8/10/2019 Rallfun-v26.txt

    521/921

    icu

  • 8/10/2019 Rallfun-v26.txt

    522/921

    x[[j]]

  • 8/10/2019 Rallfun-v26.txt

    523/921

    tve