+ All Categories
Home > Documents > Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

Date post: 25-Aug-2016
Category:
Upload: michael-thompson
View: 212 times
Download: 0 times
Share this document with a friend
8
Ca.~a.ttrs ,o Geosc~cn Vol 4 pp ]33-M0 Perltu~a Press lad 19'111 P,nnt~l m Gnnn Britain DUPAN 3, A SUBROUTINE FOR THE INTERPRETATION OF DUPLICATED DATA IN GEOCHEMICAL ANALYSIS MICHAEL THOMPSON Apphed Geochemistry Research Group Department of Geolog~ Imperial College London SW7 2BP. England (Recelt, ed 7 October 1977 rettsed 16 March 1978) Abstract--Duphcated analyttcal results, properly obtained can be used to estimate analytical standard devtatlon as a functton of concentration of the analyte, wtth dtstmct advantage to other methods A computer program ts gtven which performs the necessary calculattons and also enables the mveshgator to detect serious devtahons from the theoretscal model assumed Key words FORTRAN. Subroutine, Regresstonanalysas.Geochem,stry, Analytical Control INTRODUCTION A new apphcatton of duphcat,on as a method for est,- mating prectston tn geochemtcal analysts has been demonstrated recently (Thompson and Howarth. 1973, 1976) Some of the methods prevtously employed have been shown to be btassed opttmtsttcally due to the expertmental destgn and data-recordmg practtces In ad- dttton most methods assume that analyttcal variance Is homoscedasttt., that ts constant for various parts of the concentratton range, or ts constant if the data are Iogtransformed (Mtes~.h, 1967) Netther assumptton ts true m general, although seemingly homoscedasttc data have been detected tn partt~.ular s,tuattom, when the concentratton range exhtbtted by the analyte was small The correct use of duphcated analyttcal data, as outlmed by Thompson and Howarth (1978), can gtve esttmates of analyncal prectston whtch are free from opttmtsttc btas, and whtch express the standard devtatton corresponding to a parttcular concentratton of the analyte as a linear functton Thts hnear functton has been determmed m practtce to be a sattsfactory model for expresston of the vanatton Although a graphical procedure may be used for the esttmanon of the prectston parameters, a more thorough stansttcal analysts of the data can be made by computer The subroutme descrtbed here was developed to carry out thts analysts and enable the user to detect serious devtanons from the normal dtstnbutton of error, the hnear functton or systemattc bias between the dupl,cate parrs THE SUBROUTINE The FORTRAN IV subroutme ts hsted wtth full tn- source documentatton m Appendtx I, and has been used extenstvely in the Apphed Geochemtstry Research Group m mvesttgattons into analyttcal error it has been evolved through the course of several years use, and the vartous features m tt represent responses to practtcal problems frequently encountered Input arguments Input to the subroutine ts through arguments alone The prmctpal arguments are two hsts, XA and XB. which contain the corresponding first and second analyttcal results of each duphcate parr, and the variable NOBS whtch gtves the number of observattons m XA and XB NOBS should be normally at least 50 for sattsfactory results The other mput arguments are NM wht~.h controls the way the data are grouped for regresston (a value of I1 ts recommended, see next ~ectton), NOP, the number used for the Iogtcal output unzt (a line printer or equtvalent), and ITITLE, a hst contammg a heading for the output m the format 8AI~ Output and operation o/the subroutine All results generated by DUPAN 3 are wrttten on the scratch file NOP whtch is tdentified normally as output m the calhng program The output has the features descrtbed here, unless the subroutine is called with unworkable values of the input parameters, tn whtch instance a warning message ts printed and control retur- ned to the calhng program Bias lest A prehmmary test is needed for systemattc btas be- tween the first and second observatton, whtch we have determined usually to be present to a small extent unless complete randomization of all the duphcates was carried out before the chemtcal analysts Thts systemattc error, tf stgntficantly large, can mvahdate the prectston estimate whtch ts meant to detect random error only The btas test ts based upon the number of instances m whtch the first observatton ts greater than the duphcate If there ts no btas thts number (m) should be close to one half of the total number of parrs (n), and the frequency dtstrtbutton of posstble results should correspond wtth successtve terms m the bmomtal expanston of [(112)+ (I/2)]" The probabdtty of obtammg a particular devtatton from n/2 or greater can be calculated exactly According to the Central Ltmtt Theorem, the bmomtal dtstrtbutton ts asymptottcally normal for large n (here n > 50), and ts close even for small n as when probabthty ts 05 (as 333
Transcript
Page 1: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

Ca.~a.ttrs ,o Geosc~cn Vol 4 pp ]33-M0 Perltu~a Press lad 19'111 P,nnt~l m Gnnn Britain

DUPAN 3, A SUBROUTINE FOR THE INTERPRETATION OF DUPLICATED DATA IN GEOCHEMICAL ANALYSIS

MICHAEL THOMPSON Apphed Geochemistry Research Group Department of Geolog~ Imperial College London SW7 2BP. England

(Recelt, ed 7 October 1977 rettsed 16 March 1978)

Abstract--Duphcated analyttcal results, properly obtained can be used to estimate analytical standard devtatlon as a functton of concentration of the analyte, wtth dtstmct advantage to other methods A computer program ts gtven which performs the necessary calculattons and also enables the mveshgator to detect serious devtahons from the theoretscal model assumed

Key words FORTRAN. Subroutine, Regresston analysas. Geochem,stry, Analytical Control

INTRODUCTION A new apphcatton of duphcat,on as a method for est,- mating prectston tn geochemtcal analysts has been demonstrated recently (Thompson and Howarth. 1973, 1976) Some of the methods prevtously employed have been shown to be btassed opttmtsttcally due to the expertmental destgn and data-recordmg practtces In ad- dttton most methods assume that analyttcal variance Is homoscedasttt., that ts constant for various parts of the concentratton range, or ts constant if the data are Iogtransformed (Mtes~.h, 1967) Netther assumptton ts true m general, although seemingly homoscedasttc data have been detected tn partt~.ular s,tuattom, when the concentratton range exhtbtted by the analyte was small The correct use of duphcated analyttcal data, as outlmed by Thompson and Howarth (1978), can gtve esttmates of analyncal prectston whtch are free from opttmtsttc btas, and whtch express the standard devtatton corresponding to a parttcular concentratton of the analyte as a linear functton

Thts hnear functton has been determmed m practtce to be a sattsfactory model for expresston of the vanatton

Although a graphical procedure may be used for the esttmanon of the prectston parameters, a more thorough stansttcal analysts of the data can be made by computer The subroutme descrtbed here was developed to carry out thts analysts and enable the user to detect serious devtanons from the normal dtstnbutton of error, the hnear functton or systemattc bias between the dupl,cate parrs

THE SUBROUTINE

The FORTRAN IV subroutme ts hsted wtth full tn- source documentatton m Appendtx I, and has been used extenstvely in the Apphed Geochemtstry Research Group m mvesttgattons into analyttcal error it has been evolved through the course of several years use, and the vartous features m tt represent responses to practtcal problems frequently encountered

Input arguments Input to the subroutine ts through arguments alone

The prmctpal arguments are two hsts, XA and XB. which contain the corresponding first and second analyttcal results of each duphcate parr, and the variable NOBS whtch gtves the number of observattons m XA and XB NOBS should be normally at least 50 for sattsfactory results The other mput arguments are

NM wht~.h controls the way the data are grouped for regresston (a value of I1 ts recommended, see next ~ectton), NOP, the number used for the Iogtcal output unzt (a line printer or equtvalent), and ITITLE, a hst contammg a heading for the output m the format 8AI~

Output and operation o/the subroutine All results generated by DUPAN 3 are wrttten on the

scratch file NOP whtch is tdentified normally as output m the calhng program The output has the features descrtbed here, unless the subroutine is called with unworkable values of the input parameters, tn whtch instance a warning message ts printed and control retur- ned to the calhng program

Bias lest A prehmmary test is needed for systemattc btas be-

tween the first and second observatton, whtch we have determined usually to be present to a small extent unless complete randomization of all the duphcates was carried out before the chemtcal analysts Thts systemattc error, tf stgntficantly large, can mvahdate the prectston estimate whtch ts meant to detect random error only

The btas test ts based upon the number of instances m whtch the first observatton ts greater than the duphcate If there ts no btas thts number (m) should be close to one half of the total number of parrs (n), and the frequency dtstrtbutton of posstble results should correspond wtth successtve terms m the bmomtal expanston of [(112)+ (I/2)]" The probabdtty of obtammg a particular devtatton from n/2 or greater can be calculated exactly According to the Central Ltmtt Theorem, the bmomtal dtstrtbutton ts asymptottcally normal for large n (here n > 50), and ts close even for small n as when probabthty ts 05 (as

333

Page 2: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

334 M THo~4PSON

here) The mean and standard devtatton of the Gausstan approxtmatton are 11/2 and v'n/2 respectively The obser- ed incidence (m) ~s converted into the standardized normal devmte (mcorporalang the usual contmmty cor- rection) whtch ts pnntcd The probabthty of ob~nmg a result of fro[ or greater can be ob~ned from the usual tables for the areas m the tads of the normal d~stnbuuon

Regresston of standard devtatton on concentration Th~s ~s estunated by the method devised by Thompson

and Howarth (1973) The anthmettc means of, and ab- solute dtfferences between, each parr of observattons are calculated, the means are sorted mto ascending order. and the d~fferences into the corresponding order by means of the subroutine SHSRTB The subroutine MLIST then d~v~des the sorted hsts of means and d~fferences into groups of eleven results, and determines the mean of each group of means, and the medtan of each group of d~fferences For each group the medmn mult~phed by I 047 ts an esamate of the standard dewa- tton wtthm the concentratton range covered A regres- sion of the standard devmaon estimates on the means then ~s earned out by the subroutine LINEAR, and the results are pnnted, together wtth the standard errors of the coettiuents

The use of the median of the d~fferences rather than the mean ts jusafied by its relattve freedom from the effect of a small proportion of outlying results or 'flters', whtch may be present m analyttcal data, and by the fact that ~t ~s numerically almost equal to the standard devla- t~on (Thompson and Howarth, 1976)

decde ranges of the pair mean values The dtfference axts hkewlse ts dtv]ded into decde ranges but for a half-normal dmstnbut~on, of whtch the parameters ate defined by the relaUonsh~p obtained from the regresston The concentraaon values inserted into the regresston equatzon are the grand mean values of concentrauon for each decde concentraaon range Thus. for data fitting the theoretical model, the dtstnbuuon of points among the cells of the contingency table should be undorm apart from chance dev~attons from the expectauon Scruple mspectmon ~s suflioent to detect senous dev~auons from the model A detaded study of the effect of the various possible devtatlons upon the appearance of the table ts ~ven m Hov, arth and Thompson (1976) The effect usu- ally encountered ~s that of excesstve rounding-off of data. which produces an abnormal number of empty cells, especially at low concentrations However the in- terpretation of an abnormal contingency table may be ddScult, and tt should be taken essenttally as an m- dlcat,on that further study of the data ~s requtred

LIMITATIONS

I f the number of duphcated results exceeds 1004) the dimension of XC m DUPAN 3 must be increased cor- respondingly and stmdarly the dtmensJons of AM and BM must exceed the value of NOBS/NMED In subrou- tine MLIST the dtmenslons of AM, BM. BUF, and DUM must exceed NOBS/NMED Subroutine LINEAR may produce maccurate results tf u,,ed on computers w~th short word lengths, and under these con&tlons should be replaced

Test of the relattonshtp obtained The relattonsh~p obtained by regression could be

misleading under abnormal ctrcum,,tances and th~s test ~s a raptd devtce for detecting these condttmns, which are (t) marked devtattons from Gausstan error dtsmbutton, (u) a nonhnear relattonshJp between standard devJatton and concentraaon, (ut) systemattc bins between the duphcates, and 0v) analysts m one batch of matertals of two widely dtffermg matrix types (m effect trying to measure two dtfferent preclstons m one expenment) Devmtlons from Gausstan dlstnbutlon are dzscussed by Thompson and Howarth (1976) and are hkely to arise only m s~tuatlons of (a) excessive rounding--off of nmsy data, (b) coarse heterogeneous samples wtth the analyte concentrated m one phase, or (c) a htgh proportton of 'fliers' m the data Orcumstance (a) may not be avoided always, but (b) and (c) should be minimal m good analy- acal practice Nonhnear relattonshtps are possible theoretically, but we have not encountered data where the regression was Improved by nonlinear terms Syste- matzc btas should be detected m advance by the b~as test, but should not be present m a properly randomized experiment Experiments revolving samples with two d~fferent matrix-types should be avotded m thts type of work

The test ~tself ts eqmvalent to a scatter plot of absolute difference versus the mean for each pan" of results, but the field ~s dtvtded on both axes to form a 10x 10 contingency table The concentration ax~s ~s d~vlded into

E X S , ~

Appendtces 2 and 3 hst examples of output from DUPAN 3 Appendix 2 shows results from a computer- stmulated data set whtch conforms (except for samphng error) with the model assumed The contingency table shows a chance dtstnbutton of observations m each cell Appendtx 3 shows the results obtained on duplicate analyses of stream sedtments for zinc covenng a concentration range between 125 and 6200ppm The bins test shows clearly that there Js a systematic effect operating, although probably not of great magmtude The contingency table shows data points tending to cluster into parucular cells wtth an abnormal number of zeros at lower concentrattons This Js typtcal of data which has been rounded or truncated, and they had indeed been rounded to the nearest 5 ppm or 3 sJgmficant figures

Acl~no~ledgment--The computing and program development were ¢arrted out on the CDC 7314 faohty at the Imperial College Computer Centre

REFERENCES Howarth, R J. and Thompson. M, 1976 Duphcate analysts m

geochem,cal practice, part 2 Analyst, v I01, no 1206, p 669-709

Mlesch, A T 1967, Theory of error m geochemical exploratlon U S Geol Survey Prof Paper 574A, t7p

Thompson, M and Howarth, R J, 1973, The rapid est,matlon and control of preclslon by duphcate determinations Analyst, v 98 no 1164 p 153-160

Page 3: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

DUP ~N 3, a subroutine for the interpretation of duphcated data m g¢ochcmlcaJ anaJysas 335

Thompson. M. and Howazlh. i~ J. 1~6 duphcate ~na/vs~s m Thompson M and Howarlh R J 1978 A new approach to ~h¢ 8¢ochcm~c~,l pract:c¢ p~t 1 Ana/yst v 101. no 1206. p estunat:on ot" a~ytlcaJ pr¢c:smn Jour Geochemical Expl. 690-.698 v 9. p 23-30

~PPENDIX I

1 C C

C C

2

22

21

SUBROUTINE DUPAN3 (X~, XI3, HOBS, NM, NOP, ITITL E) A 1

P U R P ( ~ - A 3 F IND STANDARD DEVIATION AS A FUNCTION OF CONCENTRATION FROM A 4 DUPLICATE ANALYSES, AND PROVIDE USER WITH SUFFICIENT STATIST- A 5 -ICS TD CHECK DATA AGAINST THE MODEL OF ERROR USED, IE, A 6 GAUSSIAH DIST;~IBUTION AND LINEAR FUNCTION. A 7

A B SPECIAL METHODS- A 9

SEE (1) THOMPSON AHD HOWARTH, ANALYST, 1976,101,690-698. A 10 (2) HOWRRTH AND THOMPSON, AMALYST, 1976,101,699-709. A 11

A 12 USAGE- A 13

CALL DUPAH3 (XA , XB , HOBS , MM, MOP , ITITLE) A 14 A 15

INPUT ARGUMENT5 - A 16 XA = LIST OF ANALYTICAL RESULTS A 17 )(B = LIST DF CORRESPONDING DUPLICATE RESULTS A 10 HOBS = LENGTH OF LISTS )CA, X3 A 19 NM = NUMBER OF VALUES IN EACH GROUP FOR MEDIAN DETERMIN- A 20

ATION. NMED MUST BE ODD, AND FALL BETWEEN 3 AND A 21 HOBS/3. SUGGESTED VALUE = 11 A 22

MOP = NUMBER FOR LOGICAL OUTPUT UNIT A A 2 2 ITITLE = ARRAY CONTAINING A HEADING FOR THE OUTPUT (8AI0) A B22

A 23 SUBROUTINES CALLED - A 24

SHSRTB A 25 ML IST A 26 L INEAR A 27

A 2B AUTHOR - A 29

MICHAEL THOMPSON, IMPERIAL COLLEGE, LONDON,SW? 2BP. JAN 1977 A 30

DIMENSION XA(NOBS) , XB(HOBS) , KOUNT(IO) , NKOUNT(tO) , DEv(IO) , A 32 11TITLE (O) A A32

A 33 THE FOLLOWING MUST BE INCREASED IF HOBS EXCEEDS 1000 A 34

DIMENSION XC (1000) A 35 A 36

THE FOLLOWING MUST BE INCREASED OF MOBS/MMED EXCEEDS 333 A 37 DIMENSION AM(333) , BM(333) A 38

A 3g INTEGER OPU A 40 DATA RUTU/I.414214/ A A40 DATA DEV/O. 1259,0.2533,0.3854,0.5244,0.6744,O.8415,1.0365,1.2817,1 A 41

1 . 6 4 5 0 , 1 0 0 . / A 42 N=NOBS A 43 NMED=NM A A43 OPU=NOP A B43 WRITE ( 6 P U , 2 2 ) ITITLE A C43 FORMAT (IH1, BAIO) A 44 WRITE (OPU, I) A 45 FORMRT (27HOANALYSIS OF DUPLICATE D A T A / / ) A 46

A A45 CHA~GE EVEN tIMED TO ODD A B45

I F ( ( N M E D . A N D . - 1 ) .NE.NMED) GO TO 4 A C46 NMED = MMED + I A 47 WRITE (OPU, 21) rIMED A 48 FORMAT( 44HOWRRNI~G - ORIGINAL VALUE OF NMED CHANGED TO, I 6 ) A 49

A 5 0 CHECK THAT NMED HA~ A LEGAL VALUE A 51

4 I F (rIMED . GE . 3 . F~O . N,,'MMED . GE . 3) GO TO 2 A 52 WRITE (BPU, 3) A 53

3 FORMAT( 56HOOUPAN3 CALLED WITH ILLEGAL VALUE OF NMED - TASK DROPPE A 54 1D) A 55

RETURN A 56 A 57

FORM LISTS OF MEANS AND DIFFERENCES A 5B DO 5 J = l ,N A 59

CAGEO Vo~ 4 No 4--8

Page 4: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

336 M THOMPSON

AN-- (XA (J) +)(3 ( J ) ) ,"2. A 60 BN--XA (J) -XB (J) A 61 XA (J) =AN A 62

5 XB (J) --BM C A B3

A 64 C BIAS TEST - COUNT POSISTIV~ DIFFERENCES A 65

AM=O. A B6 DO 6 J=I,M A 67 IF (XB(J).GT.O.) AN=AN+I. A 68 IF O(B(J).EQ.D.) AN=AN+O.5 A 6g

6 CONTINUE A 70 HA=AN A 71

C A 72 C TEST AGAINST NORMAL APPROXIMATION TO BINOMIAL DISTRIBUTION A 73

BH=N A 74 BMEAN=O. 5~BN A 75 BSD=SQRT (BN) ~0.5 A 76 TA= (ABS (AN--BMEAN) +0.5)/BSD A 77 WRITE (@PU,7) H,HMED,NA,TA ~ 70

7 FORMAT (43HOTEGT FOR BIAS BETWEEN CORRESP@NDIHG VALUES//3OHO P A 79 IAIRS OF OBSERVATIONS , I15, IOX, 15HPAIRS PER GROUP, I15/30HO PO A BO 2SITIVE DIFFERENCES ,I15/30H0 NORMALISED VALUE ,F15.4 A 81 3/ / ) A 8 2

C A 83 C GET ABSOLUTE DIFFERENCES A 84

DO B J = I , N A 85 @ XB (J) =ABS (XI~ (J)) A 86

C A B7 C SORT PAIRS BY CONCENTRATION A BB

CALL SHSRTB (XA,XB,H) A 89 C A 90 C FIND CONCENTRATION MEANS AND DIFFERENCE MEDIANS A 91

CALL MLIST (XA,XB,AM,BM, N,M,HMED) A 92 C A 93 C REGRESSION @F MEDIANS @M MEANS A 94

CALL LINEAR (AM, BM,M, A ,B, SA, SO, OPU) A 95 C A 96 C DERIVE COEFFICIENTS "OR WORKING EQUATION A 97

AN:I .047 A 98 A=AXAN A 99 B=B:C'AN A 100 SA--SAXAM A I O I SB=SB:C, AN A 102 TA=A/SA A 103 TO=B/SO A 104 MM=M-2 A A104 WRITE (@PU,9) A,SA,TA,B,SB,TB,MM A 105

9 FORMAT (BOHOREGRESSION OF STANDARD DEVIATION ON COHCENTRATIOH///IBX A 106 1,11HINTERCEPT ,F15.6, 10X,14HSTANDARD ERROR,F15.6, IOX,THT-VALUE,FI A 107 25.6//6X,11HCOEFFICIENT,F15.B,IOX, 14HSTANDARD ERROR,F15.6,10X,THT-V A 108 3ALUE,FIS.6//BX,SOHDEGREES @F FREEDOM FOR T-VALUES A 109 4 ,115 / / ) A AI09

C A 110 C FORM LIST OF NORMALISED DIFFERENCES A 111

DO 10 J=I,N A 112 10 X~(J)=XB(J)/(RUTUX(A+B~XA(J))) A 113

C A 114 C . PRODUCE CONTINGENCY TABLE A 115

NDEC:N/IO A 116

EXP=FLOAT (HDEC)/10. A 117 WRITE (OPU,11) EXP A 11B

11 FORMAT (26HOTEST ADEQUACY OF EQUATION// 6X,26HCELL EXPECTATION FOR A 119 1 MODEL,FIB.I// ) A 120 WRITE (OPU,12) ( ( J ) , J= l , tO ) A 121

12 FORMAT (7X,6HDECILE,6X, 19HCONCENTRATION RANGE, 14X,27HDIFFEREMCE DE A 122 ICILE FOR M3DEL//46X, IOI4/ / ) A 123

] A 124 COUNT OBSERVATIONS FALLING IN EACH CELL A 125

DO 13 J=I,10 A 126 13 MKOUNT (J) =0 A 127

DO 18 J=I,10 A 128 JB=J~r, IDEC A 129 JA=JB-NDEC+I A 130 DO 14 K=1,10 A 131

14 KOUNT (K) =0 A 132 DO 17 K=JA,J6 A 133

Page 5: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

15 16 17 IB 19

2 0

DL P AN 3 A subroutine for the mterprc~auon of duphcated data m geochemical anahsm

DO 15 L=1,10 I F (X~(K).LT.DEV(L)) GO TO 16 CONTINUE KOUMT (L) =KOUMT (L) +I MKOUMT (L) =MKOUMT (L) +I WRITE (OPU,19) J,XA(JA),XA(J8), (KOUNT(K),K=I,10) FORMAT (1HO,IIO,lP,2EIS.4,SX, IOI4) WRITE (OPU,20) (NKOUNT(K),K=I,lO) FORMAT (/28X,13HCOLUM~ TOTALS,SX, IOI4) RETURN END SUBROUTINE LIMEAR(X,Y,M,A,B,SA,SB,IOU~

SUBROUTINE FOR SIMPLE LINEAR REGRESSION ARGUMEMTS X

Y N A 8

58 5A lOUT

INDEPENDENT VARIABLE DEPENDENT VARIABLE NUMBER ~F OBSERVATIONS INTERCEPT COEFFICIENT

STANDARD ERROR OF B STANDARD ERROR OF A LOGICAL UNIT NUMBER FOR OUTPUT

CAUTION - MORE SOPHISTICATED VERSIONS MAy BE NEEDED FOR COMPUTERS WITH VERY SHORT WORD LENGTHS

~c~cK~ ~ - ~ x ~ x ~ x ~ x ~ x x x x x x x x x x x x ~ x x x x ~ x x x x x x ~ x DIMENSION X(~), Y(M) IF (M.LT.3) GO TO 2

C C ZERO SUMS

SUMX=O. SUMY=O. SUMXX=O SUMYY=O. SUMXY=O.

C C FORM SUMS,AND SU~ OF SQUARES AND CROSS PRODUCTS

DO I I=l ,M SUMX=SUMX+X (I) 5UMY=SUMY+Y (I) SUMXX=SUMXX+X (I) ~X ( I ) SUMYY=SUMYY+Y ( I ) ~cy ( I ) SUM)CY=SUM)(Y+X (I) ~Y (I)

I COMTIr~UE C C COMPUTE STATISTICS

Q=N

)(BAR=SUMX/~ YBAR=SUMY/O YY=SUMYY-O CYBAR'~YBAR XX=SUhDCK-Q KXBARXXbAR XY=SUMXY-O ~XBAR~YBAR IF (XX.LT.I.E-20) GO TO 4 IF (YY LT.I E-2O) GO TO 4 B = XY/XX A=YBAR~X]3AR SO=SORT ( (YY- 5~XY) / (O-20~ ) SB=SD/SQRT 000 SA=SD~'SQRT (SUMYO(/(XXX'Q, ) SY=SQRT (YY/(Q-I. O) ) SX=SQRT (XX/(Q-I 0) ) RETURN

C C ERROR MESSAGES AND DEFAULT VALUES

2 WRITE (IOUT,3) 3 FORMAT (75H LINEAR CALLED WITH INSUFFICIENT OBSERVATIONS - DEFAULT

i STATISTICS RETURNED) GO TO 6

4 W;~ITE (IOUT,5) 5 FORMAT (69H LINEAR CALLED WITH CONSTANT ~'VARIABLE x - DEFAULT STATI

1STICS RETURMED) 6 A=B=SD=SB=SA=SY=SX = 1.

RETURN END

337

A 134 A 135 A 136 A 137 A 13B A 139 A 140 A 141 A 142 A 143 A 144 B I B 2 8 3 B 4 8 8 6 B 7 8 8 8 g B I0 8 AIO B 810 B ClO 8 D10 B 11 8 12 8 13 8 14 B 19 B 16 B 17 8 18 8 19 B 20 8 21 B 22 B 23 8 24 8 25 B 26 B 27 8 2B 8 29 8 30 8 31 8 32 B 33 B 34 B 39 8 36 8 37 B 38 8 3g 8 4O 8 41 B 42 B 43 B 44 B 4~ B 46 8 47 B 48 B 49 B 50 B 51 B 52 8 53 B 54 B 55 B 56 B 57 B 58 B 5g

Page 6: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

338 M THOMPSON

C C C C C C

C C C C C C

C C

C

SUBROUTIINE 5HSRT8 (f i , B,IN) C t

SORT5 R L I S T R (LEMGTN M) IMT~ IMCREASIMG ORDER, Afro A L I S T B OF C 3 CORRESPOMDIMG VALUES IMTO THE SAME ~RDER C 4

C R4 BASED ON ACM ALGORITHM MO. 201 C B4

DIMEMSIOM A (M) , B (M) C 6 M=2~M-1 C 7 M=M/2 C 8 IF" (M.EQ.O) RETURN C g K=f~--M C 10 DO 3 J=I,K C 11 DO 2 I I = I , J , M C 12 I--J- (I I - l ) C 13 IM=I+M C 14 IF (A(IM) .GT.A(1)) GO TO 3 C 15 W=A (1) C 16 A (1) =A (IM) C 17 A (IM) =W C 18 W=B (1) C Ig B (I) =B (IM) C 20 B (IM) =W C 21 COHTIHUE C 22 COMTIHUE C 23 GO TO I C 24 EHD C 25 SUBR(3UTIME MLIST (A,B,RM,BM,M,M,L) D i

SPLITS AM ORDERED L I S T ~F VALUES A (LEMGTH IN) IMT{~ GROUPS D 3 (LEMGTH L) AMD CALCULATES THE MEAM (AM) OF EACH GROUP. ALSO D 4 CALCULATES THE MEDIAIN VALUE (BM) OF" EACH GROUP OF THE D 5 CORRESPOMD~MG LIST B D 6 ~ " . ; C ~ C ' A ~ ' ~ X ' A ~ ~ C ~ ~ ~ ~ ~ ~ ~ D 7 DIMEMSIOM A (H) , B (M) D 8

D g THE FOLLOWIING MUST BE IHCREASED IF M/1. EXCEEDb 100 D 10

DIMEINSIOM AM(tO0), BM(lOO), BUF(100), DUM(IOO) D 11 D 12

DATA DUM/IOO~I. / D 13 Jd=O D 14 AL=L D 15 DO 2 J=I,M,L D 16 J J = J J + l D 17 JA=J+L-I D 18 IF (JA.GT.~) GO TO 3 D 19 ASUM=O. D 20 DO I K=J,JA D 21 ASUM=ASUM-H~ (K) D 22 KK=K-J+I D ~3 BUF (KK) -B <K) D 24 AM (J J) =ASUht/AL D 25 CALL 5HSRTB (BUF,DUM,L) D 26 LL=L/2+I D 27 BM (J J) =BUF (L L ) D 28 COMTIMUE D 29 M=M/L D 30 RETURM D 31 EMD D 32

Page 7: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

DUP?~N 3, A subrouune for the mterp re ta~n of duphcated data in geochemlcad anaJysLs 339

A P P E N D I X 2

T14IS IS R T~T I~ DUP/~3 wITN SZMULATED DATA

~PA.YSI5 O#= OIJPLICATE I)~TA

TEST F[~R 6IAS ~[TWEEM COf~ i : ~HO|P IG VCK.UES

PAIR~ OF (]IBSERVCITII)HS 722

P ~ I T I V [ 01FFE f -a~ l~5 385

~OmM~LISED ~#.UE 1 6236

PAIRS PER GROUP 11

R[GI~S$10N Or 5Tl=k"lOC~O DEVIATIOM ON CI~'h~J[MTI~ATION

INTER~JEPT 3 2~I1813 $TnMDARO ERROR

CI3~FFICIEMT 093r~68 STAMDRRD ERROR

DEGREES ~ FREEC~]MFOR T-vCK.UES

969946 T-VALUE

006517 T-VALUE

63

T[ST AO£OUACY Of" E Q U A T I ~

CJELL E)3:~ECTATIOPI F ~ HBOEL

DEC ILE CI3flC£N11~AT ION R~'¢3[

7 2

DIFFERENCE OECILE FOR r"OOEL

1 2 3 4 5 6 7 6 9 10

1 8 . 5276E+00 2 ge87E+O 1

2 3 0323E~01 4 1561E+01

3 4 1566£+01 5 34egE+Ol

4 5 3529£+01 6 4479£+01

5 6 4636£+01 7 6159£+01

6 7 6168£+01 g 07(~+01

7 9.16~71E+01 I. 0827E+02

6 1 0 6 ~ + 0 2 1 3841£+02

9 1 • 38421[ +02 1 • 9379£+02

I0 1 9468E+02 4 6515E+02

COl. UI'IN T~ITRL S

11 5 6 5 10 6 7 6 4 5

11 10 2 12 4 4 6 ? 6 6

9 9 g 3 7 g 5 6 8 7

6 3 8 15 4 6 4 12 ? 7

I0 7 8 4 4 9 ? 6 6 9

6 6 g 6 6 14 6 4 6 5

6 7 II 8 7 8 0 7 12 4

3 6 12 6 5 6 10 6 8 8

6 7 8 7 9 6 6 8 6 5

? 10 7 5 g 8 8 6 4 8

79 72 62 73 67 78 61 73 6g 66

3 284192

I0 966338

Page 8: Dupan 3, a subroutine for the interpretation of duplicated data in geochemical analysis

3JA) M THOWPSOP,

5T~EA~ SEDIPIEnT5 Rn~Y$JEO FOR ZINC (PPt'O

~W'~ALYSIS OF DUPLICATE C~qTA

APPENDIX 3

TEST V[]~ BIAS 8ETI~EEH C E ~ I ~ E ~ O I ~ G V~.LfES

PAIRS OF OBSERVATIONS 722

POSITIVE D I F F E R E d 5 435

HORPIqLI,SED VALUE 5 r'rj824

PAIRS PER GROUP 11

REGRESSION OF 5TA~OARD DEVIATION OH COnCEnTRATIOn

INTERCEPT 3 214656 ST~',IOARO ERROR

COEFFICIENT 087442 STA~OARO ERROR

DEGREE5 OF VREEOOH FOR T-VALUF5

% 35204(] T-VALUE

008882 T-VALUE

63

TEST AOEOUACY GV EOUATI0~

CELL E)0:)ECTATI0n F0R PI00EL

OECILE COMCEn'rRATION RANGE

7 2

OIFYEREnCE OECILE V0R HBOEL

1 2 3 4 5 6 7 8 9 l 0

I I 2500E+01 4 OO00E+O|

2 4 O000E+OI 5 2500E+01

3 5 2500E+01 8 2500E+01

4 6 2500E+.01 7 5000E+01

5 7 5000E+01 9. O000E+OI

6 9 O000E+OI i 0500E+02

7 1 0500E+02 I 2500E+02

8 I 2500E+02 I 5250E+~2

9 I 5500£+02 2 1500E+02

I0 2 1500E+02 6 . 2000E+03

COLUMN TOTAL 5

25 0 0 0 8 2 G 7 18 12

18 0 0 I~ 0 0 15 0 2 25

15 0 0 15 0 0 17 2 2 21

12 0 4 4 0 32 0 2 6 12

9 0 11 0 17 7 4 2 6 16

21 0 7 0 22 0 2 8 I 11

5 0 7 3 24 2 5 8 ~ 13

]0 8 0 17 I 4 6 3 2 21

5 5 13 14 3 9 I 8 6 8

4 7 7 10 3 3 8 5 7 18

124 20 49 75 78 5g 58 45 5.5 157

2 37761g

g 84'4475


Recommended