G02HKF (PDF version)
G02 Chapter Contents
G02 Chapter Introduction
NAG Library Manual

NAG Library Routine Document

G02HKF

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

G02HKF computes a robust estimate of the covariance matrix for an expected fraction of gross errors.

2  Specification

SUBROUTINE G02HKF ( N, M, X, LDX, EPS, COV, THETA, MAXIT, NITMON, TOL, NIT, WK, IFAIL)
INTEGER  N, M, LDX, MAXIT, NITMON, NIT, IFAIL
REAL (KIND=nag_wp)  X(LDX,M), EPS, COV(M*(M+1)/2), THETA(M), TOL, WK(N+M*(M+5)/2)

3  Description

For a set of n observations on m variables in a matrix X, a robust estimate of the covariance matrix, C, and a robust estimate of location, θ, are given by
C=τ2ATA-1,
where τ2 is a correction factor and A is a lower triangular matrix found as the solution to the following equations:
zi=Axi-θ,
1n i= 1nwzi2zi=0,
and
1ni=1nuzi2zi ziT -I=0,
where xi is a vector of length m containing the elements of the ith row of X,
zi is a vector of length m,
I is the identity matrix and 0 is the zero matrix,
and w and u are suitable functions.
G02HKF uses weight functions:
ut= aut2, if ​t<au2 ut=1, if ​au2tbu2 ut= but2, if ​t>bu2
and
wt= 1, if ​tcw wt= cwt, if ​t>cw
for constants au, bu and cw.
These functions solve a minimax problem considered by Huber (see Huber (1981)). The values of au, bu and cw are calculated from the expected fraction of gross errors, ε (see Huber (1981) and Marazzi (1987)). The expected fraction of gross errors is the estimated proportion of outliers in the sample.
In order to make the estimate asymptotically unbiased under a Normal model a correction factor, τ2, is calculated, (see Huber (1981) and Marazzi (1987)).
The matrix C is calculated using G02HLF. Initial estimates of θj, for j=1,2,,m, are given by the median of the jth column of X and the initial value of A is based on the median absolute deviation (see Marazzi (1987)). G02HKF is based on routines in ROBETH; see Marazzi (1987).

4  References

Huber P J (1981) Robust Statistics Wiley
Marazzi A (1987) Weights for bounded influence regression in ROBETH Cah. Rech. Doc. IUMSP, No. 3 ROB 3 Institut Universitaire de Médecine Sociale et Préventive, Lausanne

5  Parameters

1:     N – INTEGERInput
On entry: n, the number of observations.
Constraint: N>1.
2:     M – INTEGERInput
On entry: m, the number of columns of the matrix X, i.e., number of independent variables.
Constraint: 1MN.
3:     X(LDX,M) – REAL (KIND=nag_wp) arrayInput
On entry: Xij must contain the ith observation for the jth variable, for i=1,2,,N and j=1,2,,M.
4:     LDX – INTEGERInput
On entry: the first dimension of the array X as declared in the (sub)program from which G02HKF is called.
Constraint: LDXN.
5:     EPS – REAL (KIND=nag_wp)Input
On entry: ε, the expected fraction of gross errors expected in the sample.
Constraint: 0.0EPS<1.0.
6:     COV(M×M+1/2) – REAL (KIND=nag_wp) arrayOutput
On exit: a robust estimate of the covariance matrix, C. The upper triangular part of the matrix C is stored packed by columns. Cij is returned in COVj×j-1/2+i, ij.
7:     THETA(M) – REAL (KIND=nag_wp) arrayOutput
On exit: the robust estimate of the location parameters θj, for j=1,2,,m.
8:     MAXIT – INTEGERInput
On entry: the maximum number of iterations that will be used during the calculation of the covariance matrix.
Constraint: MAXIT>0.
9:     NITMON – INTEGERInput
On entry: indicates the amount of information on the iteration that is printed.
NITMON>0
The value of A, θ and δ (see Section 7) will be printed at the first and every NITMON iterations.
NITMON0
No iteration monitoring is printed.
When printing occurs the output is directed to the current advisory message unit (see X04ABF).
10:   TOL – REAL (KIND=nag_wp)Input
On entry: the relative precision for the final estimates of the covariance matrix.
Constraint: TOL>0.0.
11:   NIT – INTEGEROutput
On exit: the number of iterations performed.
12:   WK(N+M×M+5/2) – REAL (KIND=nag_wp) arrayWorkspace
13:   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,N1,
orM<1,
orN<M,
orLDX<N,
orEPS<0.0,
orEPS1.0,
orTOL0.0,
orMAXIT0.
IFAIL=2
On entry,a variable has a constant value, i.e., all elements in a column of X are identical.
IFAIL=3
The iterative procedure to find C has failed to converge in MAXIT iterations.
IFAIL=4
The iterative procedure to find C has become unstable. This may happen if the value of EPS is too large for the sample.

7  Accuracy

On successful exit the accuracy of the results is related to the value of TOL; see Section 5. At an iteration let
(i) d1= the maximum value of the absolute relative change in A
(ii) d2= the maximum absolute change in uzi2
(iii) d3= the maximum absolute relative change in θj
and let δ=maxd1,d2,d3. Then the iterative procedure is assumed to have converged when δ<TOL.

8  Further Comments

The existence of A, and hence C, will depend upon the function u (see Marazzi (1987)); also if X is not of full rank a value of A will not be found. If the columns of X are almost linearly related, then convergence will be slow.

9  Example

A sample of 10 observations on three variables is read in and the robust estimate of the covariance matrix is computed assuming 10% gross errors are to be expected. The robust covariance is then printed.

9.1  Program Text

Program Text (g02hkfe.f90)

9.2  Program Data

Program Data (g02hkfe.d)

9.3  Program Results

Program Results (g02hkfe.r)


G02HKF (PDF version)
G02 Chapter Contents
G02 Chapter Introduction
NAG Library Manual

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