MIL-HDBK-17-1F Volume 1,Chapter 8 Statistical Methods SUBROUTINE WBLEST(X.NOBS,ALPHA,BETA) 00000oo COMPUTE MLES FOR SHAPE PARAMETER(BETA)AND SCALE PARAMETER (ALPHA)BY SOLVING THE EQUATION G(BETA)=0,WHERE G IS A MONOTONICALLY INCREASING FUNCTION OF BETA. THE INITIAL ESTIMATE IS:RI=(1.28)/(STD.DEV.OF LOG(X)'S) AND THE TOLERANCE IS 2'RI/(106). DIMENSION X(NOBS) c RN FLOAT(NOBS) SUMY=00 sUMYsO=00 DO 2I=1,NOBS Y=ALOG(X0》 SUMY SUMY +Y SUMYSQ SUMYSQ+(Y2) 2 CONTINUE YSTD SORT((SUMYSQ-(SUMY2)/RN(RN-1.0)) XGM=EXP(SUMY/RN) 1=1.28 TL=2.0°.000001*R BETAM=RI GFM GFUNCT(X.NOBS.BETAM,XGM) IF G(BETAM).GE.0.DIVIDE THE INITIAL ESTIMATE BY 2 UNTIL THE ROOT IS BRACKETED BY BETAL ND BETAH. IF(GFM.GE.0.0)THEN D03J=1,20 BETAH=BETAM BETAM BETAM/2.0 GFM=GFUNCT(X.NOBS.BETAM.XGM) IF (GFM .LE.O.0)GO TO4 3 CONTINUE STOP 'GFM NEVER LE0' 4 CONTINUE BETAL-BETAM ENDIF IF G(BETAM).LT.0.MULTIPLY THE INITIAL ESTIMATE BY 2 UNTIL THE ROOT IS BRACKETED BY BETAL AND BETAH IF(GFM .LT.0.0)THEN D07J=1,20 BETAL-BETAM BETAM=BETAM2.O GFM-GFUNCT(X.NOBS.BETAM.XGM) IF(GFM .GE.0.0)GO TO8 7 CONTINUE STOP'GFM NEVER GE0 CONTINUE BETAH=BETAM ENDIF oU0U SOLVE THE EQUATION G(BETA)=O FOR BETA BY BISECTING THE INTERVAL(BETAL.BETAH)UNTIL THE TOLERANCE IS MET 10 CONTINUE BETAM=(BETAL BETAH)/2.0 GFM=GFUNCT(X.NOBS.BETAM.XGM) IF(GFMGE.0.0)THEN ENDH-BETAM IF(GFM.LT.0.0)THEN BETAL=BETAM ENDIF IF((BETAH-BETAL).GT.TOL)GO TO 10 FIGURE 8.3.4.2.1 FORTRAN routines for calculating two-parameter Weibull shape and shale parameter,estimates,continued on next page. 8-21
MIL-HDBK-17-1F Volume 1, Chapter 8 Statistical Methods 8-21 C------------------------------------------------------------------------------------------------- SUBROUTINE WBLEST(X,NOBS,ALPHA,BETA) C C COMPUTE MLES FOR SHAPE PARAMETER (BETA) AND SCALE PARAMETER C (ALPHA) BY SOLVING THE EQUATION G(BETA) = 0, WHERE G IS C A MONOTONICALLY INCREASING FUNCTION OF BETA. C THE INITIAL ESTIMATE IS: RI=(1.28)/(STD. DEV. OF LOG(X)'S) C AND THE TOLERANCE IS : 2*RI/(10**6). C DIMENSION X(NOBS) C RN = FLOAT(NOBS) SUMY = 0.0 SUMYSQ = O.O DO 2 I = 1, NOBS Y = ALOG(X(I)) SUMY = SUMY + Y SUMYSQ = SUMYSQ + (Y**2) 2 CONTINUE YSTD = SQRT((SUMYSQ - (SUMY**2)/RN)/(RN - 1.0)) XGM = EXP(SUMY/RN) RI = 1.28/YSTD TOL = 2.0*.000001*RI BETAM = Rl GFM = GFUNCT(X,NOBS,BETAM,XGM) C C IF G(BETAM) .GE. 0, DIVIDE THE INITIAL ESTIMATE BY 2 UNTIL C THE ROOT IS BRACKETED BY BETAL ND BETAH. C IF(GFM .GE. 0.0) THEN DO 3 J = 1, 20 BETAH = BETAM BETAM = BETAM/2.0 GFM = GFUNCT(X,NOBS,BETAM,XGM) IF (GFM .LE. O.0) GO TO 4 3 CONTINUE STOP 'GFM NEVER LE 0' 4 CONTINUE BETAL - BETAM ENDIF C C IF G(BETAM) .LT. 0, MULTIPLY THE INITIAL ESTIMATE BY 2 C UNTIL THE ROOT IS BRACKETED BY BETAL AND BETAH C IF(GFM .LT. 0.0) THEN DO 7 J = 1, 20 BETAL=BETAM BETAM=BETAM*2.O GFM=GFUNCT(X,NOBS,BETAM,XGM) IF(GFM .GE. 0.0) GO TO 8 7 CONTINUE STOP 'GFM NEVER GE 0' 8 CONTINUE BETAH = BETAM ENDIF C C SOLVE THE EQUATION G(BETA) = O FOR BETA BY BISECTING THE C INTERVAL (BETAL,BETAH) UNTIL THE TOLERANCE IS MET C 10 CONTINUE BETAM = (BETAL + BETAH) / 2.0 GFM = GFUNCT(X,NOBS,BETAM,XGM) IF(GFM .GE. 0.0) THEN BETAH = BETAM ENDIF IF(GFM .LT. 0.0) THEN BETAL = BETAM ENDIF IF((BETAH - BETAL) .GT. TOL) GO TO 10 FIGURE 8.3.4.2.1 FORTRAN routines for calculating two-parameter Weibull shape and shale parameter, estimates, continued on next page
MIL-HDBK-17-1F Volume 1,Chapter 8 Statistical Methods BETA=(BETAL BETAH)/2.0 ALPHA=FNALPH(X.NOBS.BETA.XGM) RETURN END FUNCTION FNALPH(X,NOBS,BETA.XGM) 0UU COMPUTE MLE FOR TWO-PARAMETER WEIBULL SCALE PARAMETER(ALPHA) XGM IS THE GEOMETRIC MEAN OF THE X'S DIMENSION X(NOBS) RN=FLOAT(NOBS) SUM=0.0 DO 201=1,NOBS SUMZSUMZ I (X(I/XGM)"BETA 20 CONTINUE FNALPH =XGM*(SUMZ/RN)(1./BETA) Function GFUNCT(X,NOBS.BETA.XGM) COMPUTE G FUNCTION USED IN ESTIMATING THE TWO-PARAMETER WEIBULL oOU SHAPE PARAMETER (BETA). XGC IS THE GEOMETRIC MEAN OF THE X'S USED IN ESTIMATING ALPHA. DIMENSION X(NOBS) RN=FLOAT(NOBS) ALPHA=FNALPH(X.NOBS,BETA.XGM) SUMYZ=0.0 DO 101=1.NOBS SUMYZ SUMYZ+ALOG(X(I))((X(I/ALPHA)"BETA-1.) 10 CONTINUE GFUNCT=(SUMYZ/RN)-1.0/BETA RETURN END FIGURE 8.3.4.2.1 FORTRAN routines for calculating two-parameter Weibull shape and shale parameter,estimates,concluded. Equation 8.3.4.2.1(d)is a monotonically decreasing continuous function of B.Designate the left- hand side of Equation 8.3.4.2.1(d)divided by n as G(B)and obtain a solution for B by the following itera- tive procedure.Let Sy denote the standard deviation of y,...,yn where y=In(xi)for i=1,...,n.Calcu- late I=1.28/S,as an initial guess at the solution and calculate G(I).If G(I)>0,then find the smallest posi- tive integer k such that G(1/2k)<0 and let L =I/22 and H I/2k-1.If G(I)<0,then find the smallest positive integer k such that G(2k)>0 and let L=2I and H=2I.In either case.the interval (L,H) contains the solution to G(B)=0.Now calculate G(M)where M=(L+H)/2.If G(M)=0,then the solu- tion is B=M.If G(M)>0,then let H=M.If G(M)<0 then let L=M.The new interval (L,H)still contains the solution to G(B)=0 but is only half as long as the old interval.Calculate a new M-value and begin the process of interval halving again.The process is repeated until H-L 21/105.The solution to G(B)=0 is then taken to be M=(L+H)/2.The solution is in error by at most 1/10. 8-22
MIL-HDBK-17-1F Volume 1, Chapter 8 Statistical Methods 8-22 C BETA = (BETAL + BETAH) / 2.0 ALPHA = FNALPH(X,NOBS,BETA,XGM) RETURN END C------------------------------------------------------------------------------------------------- FUNCTION FNALPH(X,NOBS,BETA,XGM) C C COMPUTE MLE FOR TWO-PARAMETER WEIBULL SCALE PARAMETER (ALPHA) C XGM IS THE GEOMETRIC MEAN OF THE X'S C DIMENSION X(NOBS) RN = FLOAT(NOBS) C SUMZ = 0.0 DO 20 I = 1, NOBS SUMZ = SUMZ I (X(l)/XGM)**BETA 20 CONTINUE C FNALPH = XGM*(SUMZ/RN)**(1./BETA) C RETURN END C------------------------------------------------------------------------------------------------- C------------------------------------------------------------------------------------------------- Function GFUNCT(X,NOBS,BETA,XGM) C C COMPUTE G FUNCTION USED IN ESTIMATING THE TWO-PARAMETER WEIBULL C SHAPE PARAMETER (BETA). C XGC IS THE GEOMETRIC MEAN OF THE X'S USED IN ESTIMATING ALPHA. C DIMENSION X(NOBS) RN = FLOAT(NOBS) C ALPHA = FNALPH(X,NOBS,BETA,XGM) SUMYZ = 0.0 DO 10 I = 1, NOBS SUMYZ = SUMYZ + ALOG(X(I))*((X(I)/ALPHA)**BETA - 1.) 10 CONTINUE C GFUNCT = (SUMYZ/RN) - 1.0/BETA C RETURN END C------------------------------------------------------------------------------------------------- FIGURE 8.3.4.2.1 FORTRAN routines for calculating two-parameter Weibull shape and shale parameter, estimates, concluded. Equation 8.3.4.2.1(d) is a monotonically decreasing continuous function of β . Designate the lefthand side of Equation 8.3.4.2.1(d) divided by n as G( β) and obtain a solution for β by the following iterative procedure. Let Sy denote the standard deviation of 1 n y ,..., y where y1 i = ln(x ) for i = 1,...,n. Calculate I = 1.28/Sy as an initial guess at the solution and calculate G(I). If G(I) > 0, then find the smallest positive integer k such that G(1/ 2 )<0 k and let L = I/ 22 and H = I/ 2k-1 . If G(I) < 0, then find the smallest positive integer k such that G(2 I) > 0 k and let L = 2 k-1 I and H = 2 kI. In either case, the interval (L,H) contains the solution to G( β) = 0 . Now calculate G(M) where M = (L + H)/2. If G(M) = 0, then the solution is β = M. If G(M) > 0, then let H = M. If G(M) < 0 then let L = M. The new interval (L,H) still contains the solution to G( β) = 0 but is only half as long as the old interval. Calculate a new M-value and begin the process of interval halving again. The process is repeated until H-L < 2I/106 . The solution to G( β) = 0 is then taken to be M = (L + H)/2. The solution is in error by at most I/106 .
MIL-HDBK-17-1F Volume 1,Chapter 8 Statistical Methods 8.3.4.2.2 Goodness-of-fit test for the two-parameter Weibull distribution The two-parameter Weibull distribution is considered by comparing the cumulative Weibull distribution function (Section 8.1.4)that best fits the data with the cumulative distribution function of the data.Using the shape and scale parameter estimates from Section 8.3.4.2.1,let fori=l.,n 8.3.4.2.2(a) The Anderson-Darling test statistic is AD-含[a-eo小-zoa小-n 8.3.4.2.2(b) and the observed significance level is 0SL=1/1+exp[-0.10+1.24In(AD+4.48AD} 8.3.4.2.2(c where AD 8.3.4.2.2(d) This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a two-parameter Weibull distribution.If OSL<0.05, one may conclude (at a five percent risk of being in error)that the population does not have a two- parameter Weibull distribution.Otherwise,the hypothesis that the population has a two-parameter Weibull distribution is not rejected.For further information on this procedure,see Reference 8.3.4.2. 8.3.4.2.3 Basis values for the two-parameter Weibull distribution If the unstructured data set is from a population with a two-parameter Weibull distribution,the B-basis value is B=qex 8.3.4.2.3(a) n where 9=a0.10536) 8.3.4.2.3(b) and V is the value in Table 8.5.8 corresponding to a sample of size n.A numerical approximation to the v values is given in Equation 8.5.8(h). To calculate the A-basis value,use the appropriate V value from Table 8.5.9 substituting 8.3.4.2.3(c) for8.3.4.2.3(b). 9=a0.010051/p 8.3.4.2.3(c) 8.3.4.3 Normal distribution In order to compute a basis value for a normally distributed population,it is necessary to obtain esti- mates of the population mean and standard deviation.Section 8.3.4.3.1 gives the equations for calculat- ing these parameters.Section 8.3.4.3.2 provides the procedure for goodness-of-fit for the normal distri- 8-23
MIL-HDBK-17-1F Volume 1, Chapter 8 Statistical Methods 8-23 8.3.4.2.2 Goodness-of-fit test for the two-parameter Weibull distribution The two-parameter Weibull distribution is considered by comparing the cumulative Weibull distribution function (Section 8.1.4) that best fits the data with the cumulative distribution function of the data. Using the shape and scale parameter estimates from Section 8.3.4.2.1, let z(i) (i) = x / , for i = 1,...,n β α 8.3.4.2.2(a) The Anderson-Darling test statistic is n (i) (n+1-i) i=1 1- 2i AD = n 1- exp( ) - - n z z n ∑ − A 8.3.4.2.2(b) and the observed significance level is { } OSL = 1/ 1+ exp[-0.10 +1.24ln( ) + 4.48 ] * * AD AD 8.3.4.2.2(c) where * AD = 1+ 0.2 n AD F H G I K J 8.3.4.2.2(d) This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a two-parameter Weibull distribution. If OSL ≤ 0.05, one may conclude (at a five percent risk of being in error) that the population does not have a twoparameter Weibull distribution. Otherwise, the hypothesis that the population has a two-parameter Weibull distribution is not rejected. For further information on this procedure, see Reference 8.3.4.2. 8.3.4.2.3 Basis values for the two-parameter Weibull distribution If the unstructured data set is from a population with a two-parameter Weibull distribution, the B-basis value is B = qexp -V β n R S | T | U V | W | 8.3.4.2.3(a) where q = (0.10536) 1/ α β 8.3.4.2.3(b) and V is the value in Table 8.5.8 corresponding to a sample of size n. A numerical approximation to the V values is given in Equation 8.5.8(h). To calculate the A-basis value, use the appropriate V value from Table 8.5.9 substituting 8.3.4.2.3(c) for 8.3.4.2.3(b). 1/ q (0.01005) ˆ ˆ β =α 8.3.4.2.3(c) 8.3.4.3 Normal distribution In order to compute a basis value for a normally distributed population, it is necessary to obtain estimates of the population mean and standard deviation. Section 8.3.4.3.1 gives the equations for calculating these parameters. Section 8.3.4.3.2 provides the procedure for goodness-of-fit for the normal distri-
MIL-HDBK-17-1F Volume 1,Chapter 8 Statistical Methods bution,and Section 8.3.4.3.3 gives the procedure for calculating basis values.The example problem in Section 8.3.7.2 demonstrates these procedures. 8.3.4.3.1 Estimating the mean and standard deviation parameters for the normal distribution The population mean and standard deviation are estimated using the sample mean x and sample standard deviation s. X=一∑X ni=1 12(x-x S= n-1=1 8.3.4.3.2 Goodness-of-fit test for the normal distribution The normal distribution is considered by comparing the cumulative normal distribution function(Sec- tion 8.1.4)that best fits the data with the cumulative distribution function of the data.Let 20-0~x for i=1,....n 8.3.4.3.2(a) where x)is the ith smallest sample observation,x is the sample average,and s is the sample standard deviation. The Anderson-Darling test statistic is 0-含2ta小f-aa-n 8.3.4.3.2(b) where Fo is the standard normal distribution function(Equation 8.1.4(e)).The observed significance level is OSL=1/{1+exp[-0.48+0.781n(AD*)+4.58AD*]} 8.3.4.3.2(c) where AD" 8.3.4.3.2(d) This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a normal distribution.If OSL<0.05,one may con- clude (at a five percent risk of being in error)that the population is not normally distributed.Otherwise, the hypothesis that the population is normally distributed is not rejected.For further information on this procedure,see Reference 8.3.4.2. 8.3.4.3.3 Basis values for the normal distribution If the unstructured data set is from a population with a normal distribution,the B-basis value is B=X-kBS 8.3.4.3.3(a where kB is the appropriate one-sided tolerance-limit factor from Table 8.5.10.A numerical approximation to the kB values is given in Equation 8.5.10. 8-24
MIL-HDBK-17-1F Volume 1, Chapter 8 Statistical Methods 8-24 bution, and Section 8.3.4.3.3 gives the procedure for calculating basis values. The example problem in Section 8.3.7.2 demonstrates these procedures. 8.3.4.3.1 Estimating the mean and standard deviation parameters for the normal distribution The population mean and standard deviation are estimated using the sample mean x and sample standard deviation s. x = 1 n x i=1 n ∑ i s = 1 n-1 ( i=1 n ∑ x -x) i 2 8.3.4.3.2 Goodness-of-fit test for the normal distribution The normal distribution is considered by comparing the cumulative normal distribution function (Section 8.1.4) that best fits the data with the cumulative distribution function of the data. Let z(i) = s , for i = 1,...,n x x (i) − 8.3.4.3.2(a) where x(i) is the ith smallest sample observation, x is the sample average, and s is the sample standard deviation. The Anderson-Darling test statistic is AD = 1-2i n ln F (z ) + ln 1- f (z ) -n i=1 n ∑ o t 0 (i) 0 (n+1-i) 8.3.4.3.2(b) where F0 is the standard normal distribution function (Equation 8.1.4(e)). The observed significance level is OSL = 1/ 1+ exp[-0.48 + 0.78ln(AD*) + 4.58AD*] l q 8.3.4.3.2(c) where * AD = 1+ 0.2 n AD F H G I K J 8.3.4.3.2(d) This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a normal distribution. If OSL ≤ 0.05, one may conclude (at a five percent risk of being in error) that the population is not normally distributed. Otherwise, the hypothesis that the population is normally distributed is not rejected. For further information on this procedure, see Reference 8.3.4.2. 8.3.4.3.3 Basis values for the normal distribution If the unstructured data set is from a population with a normal distribution, the B-basis value is B= - xks B 8.3.4.3.3(a) where kB is the appropriate one-sided tolerance-limit factor from Table 8.5.10. A numerical approximation to the kB values is given in Equation 8.5.10
MIL-HDBK-17-1F Volume 1,Chapter 8 Statistical Methods To calculate the A-basis value,replace ke with the appropriate value of kA from Table 8.5.11 or the numerical approximation in Equation 8.5.11. 8.3.4.4 Lognormal distribution The lognormal distribution is a positively skewed distribution that is simply related to the normal distri- bution.If something is lognormally distributed,then its logarithm is normally distributed.The natural(base e)logarithm is used in MIL-HDBK-17.See Section 8.1.4 for the definition of the lognormal distribution. The example problem in Section 8.3.7.3 demonstrates the application of the procedures in Section 8.3.4.3 for a lognormal distribution. In order to fit test the goodness-of fit of the lognormal distribution,take the logarithm of the data and perform the Anderson-Darling test for normality from Section 8.3.4.3.Using the natural logarithm,let 20= ln(区o)-XL,fori=l,,n 8.3.4.4(a SL where x(is the ith smallest sample observation,xL and sL are the mean and standard deviation of the In(xi)values. The Anderson-Darling statistics is computed using Equation 8.3.4.3(b)and the observed significance level(OSL)is computed using Equation 8.3.4.3(c).This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a lognormal distribution.If OSL<0.05,one may conclude(at a five percent risk of being in error)that the population is not lognormally distributed.Otherwise,the hypothesis that the population is lognormally distributed is not rejected.For further information on this procedure,see Reference 8.3.4.2. The following procedure should be used to calculate basis values for unstructured data that is as- sumed to be a sample from a lognormal population.The equations presented in Section 8.3.4.3 are used to calculate the basis values.However,the calculations are performed using the logarithms of the data rather than the original observations.The computed B-basis value must then be transformed back to the original units by applying the inverse of the log transformation which was used. 8.3.4.5 Nonparametric basis values These procedures should be used to compute basis values for unstructured data when one is unwill- ing to assume a particular population model,usually because the Weibull,normal,and lognormal models all provide inadequate fits to the data.One of two methods should be used,depending on the sample size. 8.3.4.5.1 Nonparametric basis values for large samples To calculate a B-basis value for n>28,determine the value r corresponding to the sample size n from Table 8.5.12.For sample sizes between tabulated values,select the r value associated with the largest tabulated sample size that is smaller than the actual n.The B-basis value is the rth lowest observation in the data set.For example,in a sample of size n=30,the lowest(r 1)observation is the B-basis value. A numerical approximation to the tabulated r values as a function of n is given in Section 8.5.12.The ex- ample problem in Section 8.3.7.4 demonstrates this procedure.Further information on this procedure may be found in Reference 8.3.4.5.1. For n>298,an A-basis value can calculated using the sample procedure,with the r value selected from Table 8.5.13. 8-25
MIL-HDBK-17-1F Volume 1, Chapter 8 Statistical Methods 8-25 To calculate the A-basis value, replace kB with the appropriate value of kA from Table 8.5.11 or the numerical approximation in Equation 8.5.11. 8.3.4.4 Lognormal distribution The lognormal distribution is a positively skewed distribution that is simply related to the normal distribution. If something is lognormally distributed, then its logarithm is normally distributed. The natural (base e) logarithm is used in MIL-HDBK-17. See Section 8.1.4 for the definition of the lognormal distribution. The example problem in Section 8.3.7.3 demonstrates the application of the procedures in Section 8.3.4.3 for a lognormal distribution. In order to fit test the goodness-of fit of the lognormal distribution, take the logarithm of the data and perform the Anderson-Darling test for normality from Section 8.3.4.3. Using the natural logarithm, let (i) L z = ln( ) - s , for i = 1,...,n x x (i) L 8.3.4.4(a) where x(i) is the ith smallest sample observation, xL and sL are the mean and standard deviation of the ln(xi) values. The Anderson-Darling statistics is computed using Equation 8.3.4.3(b) and the observed significance level (OSL) is computed using Equation 8.3.4.3(c). This OSL measures the probability of observing an Anderson-Darling statistic at least as extreme as the value calculated if in fact the data are a sample from a lognormal distribution. If OSL ≤ 0.05, one may conclude (at a five percent risk of being in error) that the population is not lognormally distributed. Otherwise, the hypothesis that the population is lognormally distributed is not rejected. For further information on this procedure, see Reference 8.3.4.2. The following procedure should be used to calculate basis values for unstructured data that is assumed to be a sample from a lognormal population. The equations presented in Section 8.3.4.3 are used to calculate the basis values. However, the calculations are performed using the logarithms of the data rather than the original observations. The computed B-basis value must then be transformed back to the original units by applying the inverse of the log transformation which was used. 8.3.4.5 Nonparametric basis values These procedures should be used to compute basis values for unstructured data when one is unwilling to assume a particular population model, usually because the Weibull, normal, and lognormal models all provide inadequate fits to the data. One of two methods should be used, depending on the sample size. 8.3.4.5.1 Nonparametric basis values for large samples To calculate a B-basis value for n > 28, determine the value r corresponding to the sample size n from Table 8.5.12. For sample sizes between tabulated values, select the r value associated with the largest tabulated sample size that is smaller than the actual n. The B-basis value is the rth lowest observation in the data set. For example, in a sample of size n = 30, the lowest (r = 1) observation is the B-basis value. A numerical approximation to the tabulated r values as a function of n is given in Section 8.5.12. The example problem in Section 8.3.7.4 demonstrates this procedure. Further information on this procedure may be found in Reference 8.3.4.5.1. For n > 298, an A-basis value can calculated using the sample procedure, with the r value selected from Table 8.5.13