G13DJF (PDF version)
G13 Chapter Contents
G13 Chapter Introduction
NAG Library Manual

NAG Library Routine Document

G13DJF

Note:  before using this routine, please read the Users' Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent details.

+ Contents

    1  Purpose
    7  Accuracy

1  Purpose

G13DJF computes forecasts of a multivariate time series. It is assumed that a vector ARMA model has already been fitted to the appropriately differenced/transformed time series using G13DDF. The standard deviations of the forecast errors are also returned. A reference vector is set up so that, should future series values become available, the forecasts and their standard errors may be updated by calling G13DKF.

2  Specification

SUBROUTINE G13DJF ( K, N, Z, KMAX, TR, ID, DELTA, IP, IQ, MEAN, PAR, LPAR, QQ, V, LMAX, PREDZ, SEFZ, REF, LREF, WORK, LWORK, IWORK, LIWORK, IFAIL)
INTEGER  K, N, KMAX, ID(K), IP, IQ, LPAR, LMAX, LREF, LWORK, IWORK(LIWORK), LIWORK, IFAIL
REAL (KIND=nag_wp)  Z(KMAX,N), DELTA(KMAX,*), PAR(LPAR), QQ(KMAX,K), V(KMAX,*), PREDZ(KMAX,LMAX), SEFZ(KMAX,LMAX), REF(LREF), WORK(LWORK)
CHARACTER(1)  TR(K), MEAN

3  Description

Let the vector Zt = z1t,z2t,,zktT , for t=1,2,,n, denote a k-dimensional time series for which forecasts of Zn+1,Zn+2,,Zn+lmax are required. Let Wt = w1t,w2t,,wktT  be defined as follows:
wit=δiBzit*,  i=1,2,,k,
where δiB is the differencing operator applied to the ith series and where zit* is equal to either zit, zit or logezit depending on whether or not a transformation was required to stabilize the variance before fitting the model.
If the order of differencing required for the ith series is di, then the differencing operator for the ith series is defined by δiB=1-δi1B-δi2B2--δidiBdi where B is the backward shift operator; that is, BZt=Zt-1. The differencing parameters δij, for i=1,2,,k and j=1,2,,di, must be supplied by you. If the ith series does not require differencing, then di=0.
Wt is assumed to follow a multivariate ARMA model of the form:
Wt-μ=ϕ1Wt-1-μ+ϕ2Wt-2-μ++ϕpWt-p-μ+εt-θ1εt-1--θqεt-q, (1)
where εt = ε1t,ε2t,,εktT , for t=1,2,,n, is a vector of k residual series assumed to be Normally distributed with zero mean and positive definite covariance matrix Σ. The components of εt are assumed to be uncorrelated at non-simultaneous lags. The ϕi and θj are k by k matrices of parameters. The matrices ϕi, for i=1,2,,p, are the autoregressive (AR) parameter matrices, and the matrices θi, for i=1,2,,q, the moving average (MA) parameter matrices. The parameters in the model are thus the p (k by k) ϕ-matrices, the q (k by k) θ-matrices, the mean vector μ and the residual error covariance matrix Σ. The ARMA model (1) must be both stationary and invertible; see G13DXF for a method of checking these conditions.
The ARMA model (1) may be rewritten as
ϕBδBZt*-μ=θBεt,
where ϕB and θB are the autoregressive and moving average polynomials and δB denotes the k by k diagonal matrix whose ith diagonal elements is δiB and Zt* = z 1t * , z2t* zkt* T .
This may be rewritten as
ϕBδBZt*=ϕBμ+θBεt
or
Zt*=τ+ψ Bεt=τ+εt+ψ1εt- 1+ψ2εt- 2+
where ψB=δ-1Bϕ-1BθB and τ=δ-1Bμ is a vector of length k.
Forecasts are computed using a multivariate version of the procedure described in Box and Jenkins (1976). If Z^n*l denotes the forecast of Zn+l*, then Z^n*l is taken to be that linear function of Zn*,Zn-1*, which minimizes the elements of Eenlenl where enl=Zn+l*-Z^n*l is the forecast error. Z^n*l is referred to as the linear minimum mean square error forecast of Zn+l*.
The linear predictor which minimizes the mean square error may be expressed as
Z^n*l=τ+ψlεn+ψl+1εn-1+ψl+2εn-2+.
The forecast error at t for lead l is then
enl=Zn+l*-Z^n*l=εn+l+ψ1εn+l-1+ψ2εn+l-2++ψl-1εn+1.
Let d=maxdi, for i=1,2,,k. Unless q=0 the routine requires estimates of εt, for t=d+1,,n, which are obtainable from G13DDF. The terms εt are assumed to be zero, for t=n+1,,n+lmax. You may use G13DKF to update these lmax forecasts should further observations, Zn+1,Zn+2,, become available. Note that when lmax or more further observations are available then G13DJF must be used to produce new forecasts for Zn+lmax+1,Zn+lmax+2,, should they be required.
When a transformation has been used the forecasts and their standard errors are suitably modified to give results in terms of the original series, Zt; see Granger and Newbold (1976).

4  References

Box G E P and Jenkins G M (1976) Time Series Analysis: Forecasting and Control (Revised Edition) Holden–Day
Granger C W J and Newbold P (1976) Forecasting transformed series J. Roy. Statist. Soc. Ser. B 38 189–203
Wei W W S (1990) Time Series Analysis: Univariate and Multivariate Methods Addison–Wesley

5  Parameters

The output quantities K, N, KMAX, IP, IQ, PAR, NPAR, QQ and V from G13DDF are suitable for input to G13DJF.
1:     K – INTEGERInput
On entry: k, the dimension of the multivariate time series.
Constraint: K1.
2:     N – INTEGERInput
On entry: n, the number of observations in the series, Zt, prior to differencing.
Constraint: N3.
The total number of observations must exceed the total number of parameters in the model; that is
  • if MEAN='Z', N×K>IP+IQ×K×K+K×K+1/2;
  • if MEAN='M', N×K>IP+IQ×K×K+K+K×K+1/2,
(see the parameters IP, IQ and MEAN).
3:     Z(KMAX,N) – REAL (KIND=nag_wp) arrayInput
On entry: Zit must contain, zit, the ith component of Zt, for i=1,2,,k and t=1,2,,n.
Constraints:
  • if TRi='L', Zit>0.0;
  • if TRi='S', Zit0.0, for i=1,2,,k and t=1,2,,n.
4:     KMAX – INTEGERInput
On entry: the first dimension of the arrays Z, DELTA, QQ, V, PREDZ and SEFZ as declared in the (sub)program from which G13DJF is called.
Constraint: KMAXK.
5:     TR(K) – CHARACTER(1) arrayInput
On entry: TRi indicates whether the ith time series is to be transformed, for i=1,2,,k.
TRi='N'
No transformation is used.
TRi='L'
A log transformation is used.
TRi='S'
A square root transformation is used.
Constraint: TRi='N', 'L' or 'S', for i=1,2,,k.
6:     ID(K) – INTEGER arrayInput
On entry: IDi must specify, di, the order of differencing required for the ith series.
Constraint: 0IDi<N-maxIP,IQ, for i=1,2,,k.
7:     DELTA(KMAX,*) – REAL (KIND=nag_wp) arrayInput
Note: the second dimension of the array DELTA must be at least max1,d, where d=maxIDi.
On entry: if IDi>0, then DELTAij must be set equal to δij, for j=1,2,,di and i=1,2,,k.
If d=0, DELTA is not referenced.
8:     IP – INTEGERInput
On entry: p, the number of AR parameter matrices.
Constraint: IP0.
9:     IQ – INTEGERInput
On entry: q, the number of MA parameter matrices.
Constraint: IQ0.
10:   MEAN – CHARACTER(1)Input
On entry: MEAN='M', if components of μ have been estimated and MEAN='Z', if all elements of μ are to be taken as zero.
Constraint: MEAN='M' or 'Z'.
11:   PAR(LPAR) – REAL (KIND=nag_wp) arrayInput
On entry: must contain the parameter estimates read in row by row in the order ϕ1,ϕ2,,ϕp, θ1,θ2,,θq, μ.
Thus,
  • if IP>0, PARl-1×k×k+i-1×k+j must be set equal to an estimate of the i,jth element of ϕl, for l=1,2,,p, i=1,2,,k and j=1,2,,k;
  • if IQ>0, PARp×k×k+l-1×k×k+i-1×k+j must be set equal to an estimate of the i,jth element of θl, for l=1,2,,q, i=1,2,,k and j=1,2,,k;
  • if MEAN='M', PARp+q×k×k+i must be set equal to an estimate of the ith component of μ, for i=1,2,,k.
Constraint: the first IP×K×K elements of PAR must satisfy the stationarity condition and the next IQ×K×K elements of PAR must satisfy the invertibility condition.
12:   LPAR – INTEGERInput
On entry: the dimension of the array PAR as declared in the (sub)program from which G13DJF is called.
Constraints:
  • if MEAN='Z', LPARmax1,IP+IQ×K×K;
  • if MEAN='M', LPARIP+IQ×K×K+K.
13:   QQ(KMAX,K) – REAL (KIND=nag_wp) arrayInput/Output
On entry: QQij must contain an estimate of the i,jth element of Σ. The lower triangle only is needed.
Constraint: QQ must be positive definite.
On exit: if IFAIL1, then the upper triangle is set equal to the lower triangle.
14:   V(KMAX,*) – REAL (KIND=nag_wp) arrayInput
Note: the second dimension of the array V must be at least max1,N-d, where d=maxIDi.
On entry: Vit must contain an estimate of the ith component of εt+d, for i=1,2,,k and t=1,2,,n-d.
If q=0, V is not used.
15:   LMAX – INTEGERInput
On entry: the number, lmax, of forecasts required.
Constraint: LMAX1.
16:   PREDZ(KMAX,LMAX) – REAL (KIND=nag_wp) arrayOutput
On exit: PREDZil contains the forecast of zi,n+l, for i=1,2,,k and l=1,2,,lmax.
17:   SEFZ(KMAX,LMAX) – REAL (KIND=nag_wp) arrayOutput
On exit: SEFZil contains an estimate of the standard error of the forecast of zi,n+l, for i=1,2,,k and l=1,2,,lmax.
18:   REF(LREF) – REAL (KIND=nag_wp) arrayOutput
On exit: the reference vector which may be used to update forecasts using G13DKF. The first LMAX-1×K×K elements contain the ψ weight matrices, ψ1,ψ2,,ψlmax-1. The next K×LMAX elements contain the forecasts of the transformed series Z^n+1*,Z^n+2*,, Z^n+lmax* and the next K×LMAX contain the variances of the forecasts of the transformed variables. The last K elements are used to store the transformations for the series.
19:   LREF – INTEGERInput
On entry: the dimension of the array REF as declared in the (sub)program from which G13DJF is called.
Constraint: LREFLMAX-1×K×K+2×K×LMAX+K.
20:   WORK(LWORK) – REAL (KIND=nag_wp) arrayWorkspace
21:   LWORK – INTEGERInput
On entry: the dimension of the array WORK as declared in the (sub)program from which G13DJF is called.
Constraint: if r=maxIP,IQ and d=maxIDi, for i=1,2,,k, LWORKmaxKrKr+2, IP+d+2K2+N+LMAXK.
22:   IWORK(LIWORK) – INTEGER arrayWorkspace
23:   LIWORK – INTEGERInput
On entry: the dimension of the array IWORK as declared in the (sub)program from which G13DJF is called.
Constraint: LIWORKK×maxIP,IQ.
24:   IFAIL – INTEGERInput/Output
On entry: IFAIL must be set to 0, -1​ or ​1. If you are unfamiliar with this parameter you should refer to Section 3.3 in the Essential Introduction for details.
For environments where it might be inappropriate to halt program execution when an error is detected, the value -1​ or ​1 is recommended. If the output of error messages is undesirable, then the value 1 is recommended. Otherwise, if you are not familiar with this parameter, the recommended value is 0. When the value -1​ or ​1 is used it is essential to test the value of IFAIL on exit.
On exit: IFAIL=0 unless the routine detects an error or a warning has been flagged (see Section 6).

6  Error Indicators and Warnings

If on entry IFAIL=0 or -1, explanatory error messages are output on the current error message unit (as defined by X04AAF).
Errors or warnings detected by the routine:
IFAIL=1
On entry,K<1,
orN<3,
orKMAX<K,
orIDi<0 for some i=1,2,,k,
orIDiN-maxIP,IQ for some i=1,2,,k,
orIP<0,
orIQ<0,
orMEAN'M' or 'Z',
orLPAR<IP+IQ×K×K+K, and MEAN='M',
orLPAR<IP+IQ×K×K and MEAN='Z',
orN×KIP+IQ×K×K+K+KK+1/2, and MEAN='M',
orN×KIP+IQ×K×K+KK+1/2 and MEAN='Z',
orLMAX<1,
orLREF<LMAX-1×K×K+2×K×LMAX+K,
orLWORK is too small,
orLIWORK is too small.
IFAIL=2
On entry,at least one of the first k elements of TR is not equal to 'N', 'L' or 'S'.
IFAIL=3
On entry, one or more of the transformations requested cannot be computed; that is, you may be trying to log or square-root a series, some of whose values are negative.
IFAIL=4
On entry, either QQ is not positive definite or the autoregressive parameter matrices are extremely close to or outside the stationarity region, or the moving average parameter matrices are extremely close to or outside the invertibility region. To proceed, you must supply different parameter estimates in the arrays PAR and QQ.
IFAIL=5
This is an unlikely exit brought about by an excessive number of iterations being needed to evaluate the eigenvalues of the matrices required to check for stationarity and invertibility; see G13DXF. All output parameters are undefined.
IFAIL=6
This is an unlikely exit which could occur if QQ is nearly non positive definite. In this case the standard deviations of the forecast errors may be non-positive. To proceed, you must supply different parameter estimates in the array QQ.
IFAIL=7
This is an unlikely exit. For one of the series, overflow will occur if the forecasts are computed. You should check whether the transformations requested in the array TR are sensible. All output parameters are undefined.

7  Accuracy

The matrix computations are believed to be stable.

8  Further Comments

The same differencing operator does not have to be applied to all the series. For example, suppose we have k=2, and wish to apply the second order differencing operator 2 to the first series and the first-order differencing operator  to the second series:
w1t=2z1t= 1-B 2z1t=1-2B+B2Z1t,   and w2t=z2t=1-Bz2t.
Then d1=2,d2=1, d=maxd1,d2=2, and
DELTA= δ11 δ12 δ21 = 2 -1 1 .
Note:  although differencing may already have been applied prior to the model fitting stage, the differencing parameters supplied in DELTA are part of the model definition and are still required by this routine to produce the forecasts.
G13DJF should not be used when the moving average parameters lie close to the boundary of the invertibility region. The routine does test for both invertibility and stationarity but if in doubt, you may use G13DXF, before calling this routine, to check that the VARMA model being used is invertible.
On a successful exit, the output quantities K, LMAX, KMAX, REF and LREF will be suitable for input to G13DKF.

9  Example

This example computes forecasts of the next five values in two series each of length 48. No transformation is to be used and no differencing is to be applied to either of the series. G13DDF is first called to fit an AR(1) model to the series. The mean vector μ is to be estimated and ϕ12,1 constrained to be zero.

9.1  Program Text

Program Text (g13djfe.f90)

9.2  Program Data

Program Data (g13djfe.d)

9.3  Program Results

Program Results (g13djfe.r)


G13DJF (PDF version)
G13 Chapter Contents
G13 Chapter Introduction
NAG Library Manual

© The Numerical Algorithms Group Ltd, Oxford, UK. 2012