Skip to content

Commit

Permalink
bugfix in QuasiconventionalCI
Browse files Browse the repository at this point in the history
  • Loading branch information
johnros committed Aug 21, 2013
1 parent 6f6ae12 commit 1c86c03
Showing 1 changed file with 6 additions and 6 deletions.
12 changes: 6 additions & 6 deletions selectiveCI/R/adaptedAssaf.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ ShortestAR <- function(theta,cutoff,alpha){
# theta2 - cutoff cannot be greater than qnorm(1 - alpha/2)!

if (theta<0) {
tmp <- Recall(-theta,cutoff,alpha)
tmp <- Recall(theta=-theta, cutoff=cutoff, alpha=alpha)
A <- -rev(tmp$A)
l <- tmp$l
}
Expand Down Expand Up @@ -84,7 +84,7 @@ ShortestCI <- function(x, sigsq, cutoff, alpha) {
stopifnot(abs(x) > cutoff)

if (x<0) {
tmp <- Recall(-x,sigsq,cutoff,alpha)
tmp <- Recall(x=-x, sigsq=sigsq, cutoff=cutoff, alpha=alpha)
lower <- -tmp$upper
upper <- -tmp$lower
} else {
Expand Down Expand Up @@ -285,7 +285,7 @@ QuasiConventionalAR <- function(theta, lambda, cutoff, alpha){
thetaprime1 <- uniroot(f, c(b, theta1))$root

if (theta<0) {
tmp <- Recall(-theta,lambda,cutoff,alpha)
tmp <- Recall(theta=-theta, lambda=lambda, cutoff=cutoff, alpha=alpha)
A <- -rev(tmp)
} else {

Expand Down Expand Up @@ -338,7 +338,7 @@ QuasiConventionalAR <- function(theta, lambda, cutoff, alpha){
# alpha (level of the test)
QuasiConventionalCI <- function(x, sigsq, lambda ,cutoff ,alpha){
if (x<0) {
tmp <- Recall(-x,sigsq,lambda,cutoff,alpha)
tmp <- Recall(x=-x, sigsq=sigsq, lambda=lambda, cutoff=cutoff, alpha=alpha)
lower <- -tmp$upper
upper <- -tmp$lower
} else {
Expand Down Expand Up @@ -402,7 +402,7 @@ QuasiConventionalCI <- function(x, sigsq, lambda ,cutoff ,alpha){
lower <- uniroot(f,c(0 - 1e-1, thetamax - 1e-1)) $ root
}
if (x >= xprime3 ) {
lower <- ShortestCI(x,cutoff,alpha)$lower
lower <- ShortestCI(x=x, sigsq=sigsq, cutoff=cutoff, alpha=alpha)$lower
}

#obtain upper end of CI
Expand All @@ -420,7 +420,7 @@ QuasiConventionalCI <- function(x, sigsq, lambda ,cutoff ,alpha){
return(CI)
}
## Testing:
#QuasiConventionalCI(x=2, sigsq=1, lambda=2, cutoff=1, alpha=0.05)
#QuasiConventionalCI(x=-2, sigsq=1, lambda=2, cutoff=1, alpha=0.05)



Expand Down

0 comments on commit 1c86c03

Please sign in to comment.