[Gmm-commits] r235 - in pkg/momentfit: R man vignettes

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Apr 9 20:04:44 CEST 2024


Author: chaussep
Date: 2024-04-09 20:04:43 +0200 (Tue, 09 Apr 2024)
New Revision: 235

Modified:
   pkg/momentfit/R/allClasses.R
   pkg/momentfit/R/gel.R
   pkg/momentfit/R/gelfit-methods.R
   pkg/momentfit/R/momentModel-methods.R
   pkg/momentfit/man/gelfit-class.Rd
   pkg/momentfit/man/lambdaAlgo.Rd
   pkg/momentfit/man/systemGmm.Rd
   pkg/momentfit/vignettes/gelS4.Rnw
   pkg/momentfit/vignettes/gelS4.pdf
   pkg/momentfit/vignettes/gmmS4.pdf
   pkg/momentfit/vignettes/weak.pdf
Log:
fixing problems with confidence intervals

Modified: pkg/momentfit/R/allClasses.R
===================================================================
--- pkg/momentfit/R/allClasses.R	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/R/allClasses.R	2024-04-09 18:04:43 UTC (rev 235)
@@ -208,7 +208,10 @@
 setClass("gelfit", representation(theta = "numeric", convergence = "numeric",
                                   lambda = "numeric", lconvergence = "numeric",
                                   call="callORNULL", gelType="list", vcov="list",
-                                  model="momentModel", restrictedLam="integer"))
+                                  model="momentModel", restrictedLam="integer",
+                                  argsCall="list"),
+         prototype=list(argsCall=list(iniTheta="gmm", theta0=NULL, lambda0=NULL,
+                                      vcov=FALSE)))
 
 setClass("summaryGel", representation(coef="matrix", specTest = "specTest",
                                       model="momentModel", lambda="matrix",

Modified: pkg/momentfit/R/gel.R
===================================================================
--- pkg/momentfit/R/gel.R	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/R/gel.R	2024-04-09 18:04:43 UTC (rev 235)
@@ -128,7 +128,7 @@
 getLambda <- function (gmat, lambda0=NULL, gelType=NULL, rhoFct=NULL, 
                        tol = 1e-07, maxiter = 100, k = 1, method="BFGS", 
                        algo = c("nlminb", "optim", "Wu"), control = list(),
-                       restrictedLam=integer()) 
+                       restrictedLam=integer(), ...) 
 {
     if (!is.null(gelType))
     {

Modified: pkg/momentfit/R/gelfit-methods.R
===================================================================
--- pkg/momentfit/R/gelfit-methods.R	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/R/gelfit-methods.R	2024-04-09 18:04:43 UTC (rev 235)
@@ -33,7 +33,11 @@
             fit <- suppressWarnings(update(obj, cstLHS=R))
         } else {
             mod <- restModel(obj at model, R)
-            fit <- suppressWarnings(update(obj, newModel=mod))
+            args <- c(list(model=mod, gelType=obj at gelType$name,
+                           rhoFct=obj at gelType$rhoFct),
+                      obj at argsCall)
+            args$theta0 <- coef(obj)[-which]
+            fit <- suppressWarnings(do.call(gelFit, args))            
         }
         test <- c(specTest(fit, type=type)@test)[1]-test0
         test-qchisq(level, 2)
@@ -43,9 +47,16 @@
                          test0=test0, level=level), silent=TRUE)
         b <- coef(object)[which]
         if (inherits(r, "try-error"))
+        {
             c(NA,NA)
-        else
-            b*(1-r$root) + p[i,]*r$root        
+            mess <- "Could not compute the confidence area: \n"
+            mess <- paste(mess, "uniroot failed to find the interval bounds inside ",
+                          "+- fact*SD around the estimate, with fact=", fact, ". ",
+                          "Try changing the value of fact")
+            warning(mess, call.=FALSE)
+        } else {
+            b*(1-r$root) + p[i,]*r$root
+        }
     }, mc.cores=cores))
     do.call(rbind, res)
 }
@@ -80,8 +91,11 @@
             fit2 <- suppressWarnings(update(fit, cstLHS=R))
         } else {
             model <- restModel(fit at model, R)
-            fit2 <- suppressWarnings(update(fit, newModel=model,
-                                            theta0=coef(fit)[-which]))
+            args <- c(list(model=model, gelType=fit at gelType$name,
+                           rhoFct=fit at gelType$rhoFct),
+                      fit at argsCall)
+            args$theta0 <- coef(fit)[-which]
+            fit2 <- suppressWarnings(do.call(gelFit, args))
         }
         test <- specTest(fit2, type=type, ...)@test[1] - test0
         crit <- qchisq(level, 1)
@@ -98,12 +112,11 @@
     if (any(c(class(res1), class(res2)) == "try-error"))
     {
         test <- c(NA,NA)
-        mess <- "Could not compute the confidence interval because: \n"
-        if (inherits(res1,"try-error"))
-            mess <- paste(mess, "(1) ", res1[1], "\n", sep="")
-        if (inherits(res2,"try-error"))
-            mess <- paste(mess, "(2) ", res2[1], "\n", sep="")
-        warning(mess)        
+        mess <- "Could not compute the confidence interval: \n"
+        mess <- paste(mess, "uniroot failed to find the interval bounds inside ",
+                      "+- fact*SD around the estimate, with fact=", fact, ". ",
+                      "Try changing the value of fact")
+        warning(mess, call.=FALSE)        
     } else {
         test <- sort(c(res1$root, res2$root))
     }
@@ -438,12 +451,8 @@
               if (!is.null(Call))
                   names(object) <- as.character(Call)[2]
               g <- as.formula(paste(names(object),"~1",sep=""))
-              n <- nrow(object)
-              s <- sd(object[[1]], na.rm=TRUE)/sqrt(n)
-              m <- mean(object[[1]], na.rm=TRUE)
               mod <- momentModel(g, ~1, vcov=vcov, data=object)
-              fit <- gelFit(model=mod, gelType=gelType,
-                            tControl=list(method="Brent",lower=m-s,upper=m+s))
+              fit <- suppressWarnings(gelFit(model=mod, gelType=gelType))
               ans <- confint(fit, parm=1, level=level, type=type,
                              fact=fact, corr=corr)
               rownames(ans at interval) <- names(object)

Modified: pkg/momentfit/R/momentModel-methods.R
===================================================================
--- pkg/momentfit/R/momentModel-methods.R	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/R/momentModel-methods.R	2024-04-09 18:04:43 UTC (rev 235)
@@ -1372,6 +1372,10 @@
                   Call <- NULL
               spec <- modelDims(model)
               initTheta = match.arg(initTheta)
+              argsCall <- c(list(initTheta=initTheta, theta0=theta0, lambda0=lambda0,
+                                 vcov=vcov),
+                            list(...))
+                  
               if (is.null(theta0))
               {
                   if (initTheta == "gmm")
@@ -1390,7 +1394,8 @@
                             lambda=res$lambda, call=Call,
                             gelType=list(name=gelType, rhoFct=rhoFct),
                             vcov=list(), model=model,
-                            restrictedLam = res$restrictedLam)
+                            restrictedLam = res$restrictedLam,
+                            argsCall=argsCall)
               if (vcov)
                   gelfit at vcov <- vcov(gelfit)
               gelfit

Modified: pkg/momentfit/man/gelfit-class.Rd
===================================================================
--- pkg/momentfit/man/gelfit-class.Rd	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/man/gelfit-class.Rd	2024-04-09 18:04:43 UTC (rev 235)
@@ -21,6 +21,7 @@
     \item{\code{vcov}:}{Object of class \code{"list"} ~~ }
     \item{\code{model}:}{Object of class \code{"momentModel"} ~~ }
     \item{\code{restrictedLam}:}{Object of class \code{"integer"} ~~ }
+    \item{\code{argsCall}:}{Object of class \code{"list"} ~~ }
   }
 }
 \section{Methods}{

Modified: pkg/momentfit/man/lambdaAlgo.Rd
===================================================================
--- pkg/momentfit/man/lambdaAlgo.Rd	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/man/lambdaAlgo.Rd	2024-04-09 18:04:43 UTC (rev 235)
@@ -24,7 +24,7 @@
 getLambda(gmat, lambda0=NULL, gelType=NULL, rhoFct=NULL, 
           tol = 1e-07, maxiter = 100, k = 1, method="BFGS", 
           algo = c("nlminb", "optim", "Wu"), control = list(),
-          restrictedLam=integer()) 
+          restrictedLam=integer(), ...) 
 }
 \arguments{
 \item{gmat}{The \eqn{n \times q} matrix of moments}
@@ -65,6 +65,8 @@
 
 \item{restrictedLam}{A vector of integers indicating which
   \code{"lambda"} are restricted to be equal to 0.}
+
+\item{...}{Arguments to pass to other methods. Currently not used.}
   
 }
 

Modified: pkg/momentfit/man/systemGmm.Rd
===================================================================
--- pkg/momentfit/man/systemGmm.Rd	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/man/systemGmm.Rd	2024-04-09 18:04:43 UTC (rev 235)
@@ -7,7 +7,7 @@
 objects, estimating them and peforming hypothesis tests.
 }
 \details{
-Instread of repeating the same example for each method, we are going
+Instead of repeating the same example for each method, we are going
 through all methods and classes for systems of equations.
 }
   
@@ -44,7 +44,7 @@
 ## All info using the summary method
 ## which includes equation by equation measures of
 ## the instrument stengths
-summary(res)
+\dontrun{summary(res)}
 
 ### When the error id iid (homoscedastic), we have a
 ### FIVE estimator with 2SLS  as the first step
@@ -81,9 +81,9 @@
 
 ## testing the restriction
 
-hypothesisTest(res, res1, type="LR")
-hypothesisTest(res, res1, type="LM")
-hypothesisTest(res, res1, type="Wald")
+\dontrun{hypothesisTest(res, res1, type="LR")}
+\dontrun{hypothesisTest(res, res1, type="LM")}
+\dontrun{hypothesisTest(res, res1, type="Wald")}
 
 }
 \keyword{FIVE}

Modified: pkg/momentfit/vignettes/gelS4.Rnw
===================================================================
--- pkg/momentfit/vignettes/gelS4.Rnw	2024-04-02 19:26:26 UTC (rev 234)
+++ pkg/momentfit/vignettes/gelS4.Rnw	2024-04-09 18:04:43 UTC (rev 235)
@@ -968,8 +968,8 @@
 res
 @ 
 
-The following is not run because it creates some misterious error when
-the package is checked. Beside that, it works perfectly. Try it.
+We can plot the confidence region using the \textit{plot} method
+associated with the object created by \textit{confint}:
 
 \begin{center}
 \begin{minipage}{.7\textwidth}

Modified: pkg/momentfit/vignettes/gelS4.pdf
===================================================================
(Binary files differ)

Modified: pkg/momentfit/vignettes/gmmS4.pdf
===================================================================
(Binary files differ)

Modified: pkg/momentfit/vignettes/weak.pdf
===================================================================
(Binary files differ)



More information about the Gmm-commits mailing list