source: trunk/fsource/histogram2d.for @ 606

Last change on this file since 606 was 451, checked in by vondreele, 13 years ago
File size: 1.3 KB
Line 
1      SUBROUTINE HISTOGRAM2D(N,X,Y,Z,NXBINS,NYBINS,XLIM,YLIM,DX,DY,
2     1  NST,HST)
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
21
22      IMPLICIT NONE
23      INTEGER*8   N
24      REAL*4      X(0:N-1),Y(0:N-1),Z(0:N-1)
25      INTEGER*8   NXBINS,NYBINS
26      REAL*8      XLIM(0:1),YLIM(0:1)
27      REAL*4      NST(0:NXBINS-1,0:NYBINS-1)
28      REAL*4      HST(0:NXBINS-1,0:NYBINS-1)
29
30      INTEGER*4   I,J,K
31      REAL*8      DX,DY
32      REAL*4      DDX,DDY
33      DO K=0,N-1
34C        if ( mod(k,8000) .eq. 0 )
35C     1    print *,k,x(k),xlim,y(k),ylim
36        IF ( ( X(K).GE.XLIM(0) .AND. X(K).LT.XLIM(1) ) .AND.
37     1    ( Y(K).GE.YLIM(0) .AND. Y(K).LT.YLIM(1) )) THEN
38          DDX = (X(K)-XLIM(0))/DX
39          I = INT(DDX)
40          DDY = (Y(K)-YLIM(0))/DY
41          J = INT(DDY)
42          NST(I,J) = NST(I,J)+1.0
43          HST(I,J) = HST(I,J)+Z(K)
44C          if ( mod(k,8000) .eq. 0 )
45C     1      print *,i,j,nst(i,j),hst(i,j)
46        END IF
47      END DO
48      RETURN
49      END
Note: See TracBrowser for help on using the repository browser.