GARCH
Computes estimates of the parameters of a GARCH(p,q) model.
Required Arguments
W — Vector of length NOBS containing the observed time series data. (Input)
NP — Number of GARCH parameters, p. (Input)
NQ — Number of ARCH parameters, q. (Input)
XGUESS — Vector of length NP+NQ +1 containing the initial values for the parameter vector X. (Input)
X — Vector of length NP+NQ+1 containing the estimates for σ2, the ARCH parameters and the GARCH parameters. X(1) contains the estimate for σ2, X(2)X(NQ+1) contain the ARCH estimates, X(NQ+2)X(NP+NQ+1) contain the GARCH estimates. (Output)
Optional Arguments
SIG2MAX— Upperbound for σ2 , the first element of X. (Input)
Default: SIG2MAX = 10.
NOBS — Length of the observed time series. (Input)
Default: NOBS = size(W).
A — Value of Log‑likelihood function evaluated at X. (Output)
AIC — Akaike’s Information Criterion evaluated at X. (Output)
VAR — (NP+NQ+1) by (NP+NQ+1) matrix containing the variance‑covariance matrix. (Output)
NDIM — Column dimension (NP+NQ+1) of VAR. (Input) Default: NDIM = NP+NQ+1.
FORTRAN 90 Interface
Generic: CALL GARCH (W, NP, NQ, XGUESS, X [])
Specific: The specific interface names are S_GARCH and D_GARCH.
Description
The Generalized Autoregressive Conditional Heteroskedastic (GARCH) model for a time series {wt} is defined as
where zt’s are independent and identically distributed standard normal random variables,
The above model is denoted as GARCH(p,q). The βi and αi coeffecients will be referred to as GARCH and ARCH coefficents, respectively. When βi = 0, i = 1,2,…,p, the above model reduces to ARCH(q) which was proposed by Engle (1982). The nonnegativity conditions on the parameters imply a nonnegative variance and the condition on the sum of the βi’s and αis is required for wide sense stationarity.
In the empirical analysis of observed data, GARCH(1,1) or GARCH(1,2) models have often found to appropriately account for conditional heteroskedasticity (Palm 1996). This finding is similar to linear time series analysis based on ARMA models.
It is important to notice that for the above models positive and negative past values have a symmetric impact on the conditional variance. In practice, many series may have strong asymmetric influence on the conditional variance. To take into account this phenomena, Nelson (1991) put forward Exponential GARCH (EGARCH). Lai (1998) proposed and studied some properties of a general class of models that extended linear relationship of the conditional variance in ARCH and GARCH into nonlinear fashion.
The maximum likelihood method is used in estimating the parameters in GARCH(p,q). The log‑likelihood of the model for the observed series {wt} with length m = nobs is
Thus log(L) is maximized subject to the constraints on the αi, βi, and σ.
In this model, if q = 0, the GARCH model is singular since the estimated Hessian matrix is singular.
The initial values of the parameter vector x entered in vector xguess must satisfy certain constraints. The first element of xguess refers to σ2 and must be greater than zero and less than sig2max. The remaining p+q initial values must each be greater than or equal to zero and sum to a value less than one.
To guarantee stationarity in model fitting,
is checked internally. The initial values should selected from values between zero and one.
AIC is computed by
- 2 log (L) + 2(p+q+1),
where log(L) is the value of the log‑likelihood function.
In fitting the optimal model, the routine NNLPF as well as its associated subroutines are modified to find the maximum likelihood estimates of the parameters in the model. Statistical inferences can be performed outside the routine GARCH based on the output of the log‑likelihood function (A), the Akaike Information Criterion (AIC), and the variance‑covariance matrix (VAR).
Example
The data for this example are generated to follow a GARCH(2,1) process by using a standard normal random number generation routine WG2RCH . The data set is analyzed and estimates of sigma, the GARCH parameters, and the ARCH parameters are returned. The values of the Log‑likelihood function and Akaike’s Information Criterion are returned from the optional arguments A and AIC.
 
USE GARCH_INT
USE RNSET_INT
IMPLICIT NONE
 
INTERFACE
SUBROUTINE WG2RCH (W, NP, NQ, NOBS, X, Z, Y0, SIGMA)
INTEGER NP, NQ, NOBS
REAL(KIND(1D0)) W(:), X(:), Z(:), Y0(:), SIGMA(:)
END SUBROUTINE
END INTERFACE
 
INTEGER :: NP, NQ, NOBS, N
PARAMETER (NP=2, NQ=1, NOBS=1000)
PARAMETER (N=NP+NQ+1)
REAL(KIND(1D0)) :: A, AIC, Z(NOBS + 1000), Y0(NOBS + 1000), &
X0=(/1.3,0.2,0.3,0.4/)
XGUESS = (/1.0,0.1,0.2,0.3/)
CALL RNSET (182198625)
CALL WG2RCH (W, NP, NQ, NOBS, X0, Z, Y0, SIGMA)
CALL GARCH(W, NP, NQ, XGUESS, X, NOBS=NOBS, A=A, AIC=AIC)
WRITE(*,*)"Variance estimate is ", x(1)
WRITE(*,*)"ARCH(1) estimate is ", x(2)
WRITE(*,*)"GARCH(1) estimate is ", x(3)
WRITE(*,*)"GARCH(2) estimate is ", x(4)
WRITE(*,*)"Log-likelihood function is ", A
WRITE(*,*)"Akaike's Information Criterion is ", AIC
END
 
SUBROUTINE WG2RCH (W, NP, NQ, NOBS, X, Z, Y0, SIGMA)
USE RNNOR_INT
INTEGER NP, NQ, NOBS
REAL(KIND(1D0)) W(:), X(:), Z(:), Y0(:), SIGMA(:)
INTEGER I, J, L
REAL(KIND(1D0)) S1, S2, S3
! RNNOR GENERATES STANDARD NORMAL OBSERVATIONS
CALL RNNOR(Z, NOBS+1000)
! INITIAL VALUES
L = MAX(NP,NQ)
L = MAX(L,1)
DO I=1, L
Y0(I) = Z(I)*X(1)
END DO
! COMPUTE THE INITIAL VALUE OF SIGMA
S3 = 0.0;
IF (MAX(NP,NQ) .GE. 1) THEN
DO I=1, NP + NQ
S3 = S3 + X(I+1)
END DO
END IF
DO I=1, L
SIGMA(I) = X(1)/(1.0-S3)
END DO
DO I=L + 1, NOBS + 1000
S1 = 0.0
S2 = 0.0
IF (NQ .GE. 1) THEN
DO J=1, NQ
S1 = S1 + X(J+1)*Y0(I-J)*Y0(I-J)
END DO
END IF
IF (NP .GE. 1) THEN
DO J=1, NP
S2 = S2 + X(NQ+1+J)*SIGMA(I-J)
END DO
END IF
SIGMA(I) = X(1) + S1 + S2
Y0(I) = Z(I)*SQRT(SIGMA(I))
END DO
! DISCARD THE FIRST 1000 SIMULATED OBSERVATIONS
DO I=1, NOBS
W(I) = Y0(1000+I)
END DO
RETURN
END
Output
 
Variance estimate is 1.6915576416511892
ARCH(1) estimate is 0.24499571998823416
GARCH(1) estimate is 0.3372325349834042
GARCH(2) estimate is 0.3095905689822821
Log-likelihood function is -2707.072433499691
Akaike's Information Criterion is 5422.144866999382