Ajout de la fonction de GMM itératif
This commit is contained in:
parent
6ee762daea
commit
79246138f2
8 changed files with 101 additions and 20 deletions
|
@ -7,12 +7,13 @@
|
|||
|
||||
#' Estimated covariance matrix
|
||||
#' @param conditions.vector Vector of moment conditions
|
||||
#' @param n Sample size
|
||||
#' @param ... Parameters of the vector of moment conditions
|
||||
#' @param param Vector of estimated parameters
|
||||
#' @param sample Individual data sample
|
||||
#' @param ... Functions of the vector of moment conditions
|
||||
#' @return A square covariance matrix
|
||||
#'
|
||||
#' @author François Pelletier
|
||||
covariance.GMM <- function(conditions.vector,n,...)
|
||||
covariance.GMM <- function(conditions.vector,param,sample...)
|
||||
{
|
||||
t(conditions.vector(...)) %*% conditions.vector(...) / n
|
||||
t(conditions.vector(param,sample,...)) %*% conditions.vector(param,sample,...) / length(sample)
|
||||
}
|
39
R/iterative.GMM.R
Normal file
39
R/iterative.GMM.R
Normal file
|
@ -0,0 +1,39 @@
|
|||
# TODO: Add comment
|
||||
#
|
||||
# Author: francois
|
||||
###############################################################################
|
||||
|
||||
|
||||
#' @param start Starting values for the parameters and lagrangian
|
||||
#' @param conditions.vector Vector of moment conditions
|
||||
#' @param sample Individual data sample
|
||||
#' @param ... Functions of the vector of moment conditions
|
||||
#' @param W Weighting matrix
|
||||
#' @param R Linear constraint matrix of coefficients
|
||||
#' @param r Linear constraint constants
|
||||
#' @param max.iter Maximum number of iterations
|
||||
#' @param epsilon Minimum precision level
|
||||
#' @return A list containing the optimized vector of parameter and corresponding covariance matrix
|
||||
#'
|
||||
#' @author François Pelletier
|
||||
iterative.GMM <- function(start,conditions.vector,sample,...,
|
||||
W,R,r,max.iter=50,epsilon=1E-6)
|
||||
{
|
||||
theta1 <- optim.GMM(start,conditions.vector,sample,...,W,R,r)
|
||||
i <- 1
|
||||
repeat
|
||||
{
|
||||
theta2 <- optim.GMM(theta1,conditions.vector,sample,...,W,R,r)
|
||||
S <- covariance.GMM(conditions.vector,param,sample,...)
|
||||
if(sqrt(sum((theta1-theta2)^2))<epsilon)
|
||||
return(list(par=theta2,cov=S))
|
||||
else if (i>max.iter)
|
||||
stop("Iterative GMM does not converge")
|
||||
else
|
||||
{
|
||||
theta1 <- theta2
|
||||
i <- i+1
|
||||
}
|
||||
|
||||
}
|
||||
}
|
|
@ -6,19 +6,20 @@
|
|||
###############################################################################
|
||||
|
||||
#' Objective function for the GMM method
|
||||
#' @param param Vector of parameters to optimize
|
||||
#' @param param.lagrangian Vector of parameters and Lagrangian to optimize
|
||||
#' @param conditions.vector Vector of moment conditions
|
||||
#' @param ... Parameters of the vector of moment conditions
|
||||
#' @param sample Individual data sample
|
||||
#' @param ... Functions of the vector of moment conditions
|
||||
#' @param W Weighting matrix
|
||||
#' @param R Linear constraint matrix of coefficients
|
||||
#' @param r Linear constraint constants
|
||||
#' @return A scalar value
|
||||
#'
|
||||
#' @author François Pelletier
|
||||
objective.GMM <- function(param.lagrangian,conditions.vector,num.param,...,
|
||||
objective.GMM <- function(param.lagrangian,conditions.vector,sample,...,
|
||||
W=diag(length(conditions.vector)),R=0,r=0)
|
||||
{
|
||||
param <- param.lagrangian[1:num.param]
|
||||
lagrangian <- param.lagrangian[num.param+1:length(param.lagrangian)]
|
||||
colMeans(conditions.vector(param,...)) %*% ginv(W) %*% colMeans(conditions.vector(param,...))+ abs(t(R %*% param - r) %*% lagrangian)
|
||||
colMeans(conditions.vector(param,sample,...)) %*% ginv(W) %*% colMeans(conditions.vector(param,sample,...))+ abs(t(R %*% param - r) %*% lagrangian)
|
||||
}
|
|
@ -2,14 +2,15 @@
|
|||
#'
|
||||
#' @param start Starting values for the parameters and lagrangian
|
||||
#' @param conditions.vector Vector of moment conditions
|
||||
#' @param number of parameters of the distribution
|
||||
#' @param ... Parameters of the vector of moment conditions
|
||||
#' @param sample Individual data sample
|
||||
#' @param ... Functions of the vector of moment conditions
|
||||
#' @param W Weighting matrix
|
||||
#' @param R Linear constraint matrix of coefficients
|
||||
#' @param r Linear constraint constants
|
||||
#' @return une liste contenant le résultat de l'optimisation
|
||||
#'
|
||||
#' @author François Pelletier
|
||||
optim.GMM <- function(start,conditions.vector,num.param,...,W,R,r)
|
||||
optim.GMM <- function(start,conditions.vector,sample,...,W,R,r)
|
||||
{
|
||||
optim(c(start,objective.GMM,conditions.vector,num.param,...,W,R,r))
|
||||
optim(start,objective.GMM,conditions.vector,sample,...,W,R,r)
|
||||
}
|
|
@ -2,12 +2,14 @@
|
|||
\alias{covariance.GMM}
|
||||
\title{Estimated covariance matrix}
|
||||
\usage{
|
||||
covariance.GMM(conditions.vector, n, ...)
|
||||
covariance.GMM(conditions.vector, param, sample...)
|
||||
}
|
||||
\arguments{
|
||||
\item{conditions.vector}{Vector of moment conditions}
|
||||
|
||||
\item{n}{Sample size}
|
||||
\item{param}{Vector of estimated parameters}
|
||||
|
||||
\item{sample}{Individual data sample}
|
||||
|
||||
\item{...}{Parameters of the vector of moment conditions}
|
||||
}
|
||||
|
|
34
man/iterative.GMM.Rd
Normal file
34
man/iterative.GMM.Rd
Normal file
|
@ -0,0 +1,34 @@
|
|||
\name{iterative.GMM}
|
||||
\alias{iterative.GMM}
|
||||
\usage{
|
||||
iterative.GMM(start, conditions.vector, sample, ..., W, R, r, max.iter = 50,
|
||||
epsilon = 1e-06)
|
||||
}
|
||||
\arguments{
|
||||
\item{start}{Starting values for the parameters and
|
||||
lagrangian}
|
||||
|
||||
\item{conditions.vector}{Vector of moment conditions}
|
||||
|
||||
\item{sample}{Individual data sample}
|
||||
|
||||
\item{...}{Functions of the vector of moment conditions}
|
||||
|
||||
\item{W}{Weighting matrix}
|
||||
|
||||
\item{R}{Linear constraint matrix of coefficients}
|
||||
|
||||
\item{r}{Linear constraint constants}
|
||||
|
||||
\item{max.iter}{Maximum number of iterations}
|
||||
|
||||
\item{epsilon}{Minimum precision level}
|
||||
}
|
||||
\value{
|
||||
A list containing the optimized vector of parameter and
|
||||
corresponding covariance matrix
|
||||
}
|
||||
\author{
|
||||
François Pelletier
|
||||
}
|
||||
|
|
@ -2,15 +2,18 @@
|
|||
\alias{objective.GMM}
|
||||
\title{Objective function for the GMM method}
|
||||
\usage{
|
||||
objective.GMM(param.lagrangian, conditions.vector, num.param, ...,
|
||||
objective.GMM(param.lagrangian, conditions.vector, sample, ...,
|
||||
W = diag(length(conditions.vector)), R = 0, r = 0)
|
||||
}
|
||||
\arguments{
|
||||
\item{param}{Vector of parameters to optimize}
|
||||
\item{param.lagrangian}{Vector of parameters and
|
||||
Lagrangian to optimize}
|
||||
|
||||
\item{conditions.vector}{Vector of moment conditions}
|
||||
|
||||
\item{...}{Parameters of the vector of moment conditions}
|
||||
\item{sample}{Individual data sample}
|
||||
|
||||
\item{...}{Functions of the vector of moment conditions}
|
||||
|
||||
\item{W}{Weighting matrix}
|
||||
|
||||
|
|
|
@ -2,7 +2,7 @@
|
|||
\alias{optim.GMM}
|
||||
\title{Optimization with constraints for GMM methos}
|
||||
\usage{
|
||||
optim.GMM(start, conditions.vector, num.param, ..., W, R, r)
|
||||
optim.GMM(start, conditions.vector, sample, ..., W, R, r)
|
||||
}
|
||||
\arguments{
|
||||
\item{start}{Starting values for the parameters and
|
||||
|
@ -10,9 +10,9 @@ optim.GMM(start, conditions.vector, num.param, ..., W, R, r)
|
|||
|
||||
\item{conditions.vector}{Vector of moment conditions}
|
||||
|
||||
\item{number}{of parameters of the distribution}
|
||||
\item{sample}{Individual data sample}
|
||||
|
||||
\item{...}{Parameters of the vector of moment conditions}
|
||||
\item{...}{Functions of the vector of moment conditions}
|
||||
|
||||
\item{W}{Weighting matrix}
|
||||
|
||||
|
|
Loading…
Reference in a new issue