source: trunk/fsource/histosigma2d.for @ 4257

Last change on this file since 4257 was 451, checked in by vondreele, 13 years ago
File size: 1.5 KB
Line 
1      SUBROUTINE HISTOSIGMA2D(N,X,Y,Z,NXBINS,NYBINS,XLIM,YLIM,DX,DY,
2     1  NST,HST,AMAT,QMAT)
3
4Cf2py intent(in) n
5Cf2py intent(in) x
6Cf2py depend(n) x
7Cf2py intent(in) y
8Cf2py depend(n) y
9Cf2py intent(in) z
10Cf2py depend(n) z
11Cf2py intent(in) nxbins
12Cf2py intent(in) nybins
13Cf2py intent(in) xlim       
14Cf2py intent(in) ylim
15Cf2py intent(in) dx
16Cf2py intent(in) dy
17Cf2py intent(in,out) nst
18Cf2py depend(nxbins,nybins) nst
19Cf2py intent(in,out) hst
20Cf2py depend(nxbins,nybins) hst
21Cf2py intent(in,out) amat
22Cf2py depend(nxbins,nybins) amat
23Cf2py intent(in,out) qmat
24Cf2py depend(nxbins,nybins) qmat
25
26      IMPLICIT NONE
27      INTEGER*8   N
28      REAL*4      X(0:N-1),Y(0:N-1),Z(0:N-1)
29      INTEGER*8   NXBINS,NYBINS
30      REAL*8      XLIM(0:1),YLIM(0:1)
31      REAL*4      NST(0:NXBINS-1,0:NYBINS-1)
32      REAL*4      HST(0:NXBINS-1,0:NYBINS-1)
33      REAL*4      AMAT(0:NXBINS-1,0:NYBINS-1)
34      REAL*4      QMAT(0:NXBINS-1,0:NYBINS-1)
35
36      INTEGER*4   I,J,K
37      REAL*8      DX,DY
38      REAL*4      DDX,DDY,AOLD
39      DO K=0,N-1
40        IF ( ( X(K).GE.XLIM(0) .AND. X(K).LT.XLIM(1) ) .AND.
41     1    ( Y(K).GE.YLIM(0) .AND. Y(K).LT.YLIM(1) )) THEN
42          DDX = (X(K)-XLIM(0))/DX
43          I = INT(DDX)
44          DDY = (Y(K)-YLIM(0))/DY
45          J = INT(DDY)
46          NST(I,J) = NST(I,J)+1.0
47          HST(I,J) = HST(I,J)+Z(K)
48          AOLD = AMAT(I,J)
49          AMAT(I,J) = AOLD+(Z(K)-AOLD)/NST(I,J)
50          QMAT(I,J) = QMAT(I,J)+(Z(K)-AOLD)*(Z(K)-AMAT(I,J))
51        END IF
52      END DO
53      RETURN
54      END
Note: See TracBrowser for help on using the repository browser.