source: CPL/oasis3/trunk/src/mod/oasis3/src/grstat.f @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 4.9 KB
Line 
1      SUBROUTINE grstat (pcorx, pcory, psgr, kmsk, kngx, kngy, cdtyp,
2     $                   pdr, psr, phhi, kvma)
3C****
4C               *****************************
5C               * OASIS ROUTINE  -  LEVEL T *
6C               * -------------     ------- *
7C               *****************************
8C
9C**** *grstat* - Statistic routine
10C
11C     Purpose:
12C     -------
13C     Given a grid, calculate the average grid square size,
14C     the total surface and the inverse of sum of surface elements squared.
15C
16C**   Interface:
17C     ---------
18C       *CALL*  *grstat (pcorx, pcory, psgr, kmsk, kngx, kngy
19C                        pdr, psr, phhi, kvma)*
20C
21C     Input:
22C     -----
23C                pcorx : the grid points longitude (real 2D)
24C                pcory : the grid points latitude (real 2D)
25C                psgr  : surface elements (real 2D)
26C                kmsk  : the grid mask (integer 2D)
27C                kngx  : the grid size in direction 1
28C                kngy  : the grid size in direction 2
29C                cdtyp : type of source grid 
30C                kvma  : integer value of the mask 
31C
32C     Output:
33C     ------
34C                pdr   : the average grid square size
35C                psr   : the total surface
36C                phhi  : inverse of sum of surface elements squared
37C
38C     Workspace:
39C     ---------
40C     None
41C
42C     Externals:
43C     ---------
44C     sqdis
45C
46C     Reference:
47C     ---------
48C     O. Thual, Simple ocean-atmosphere interpolation. 
49C               Part A: The method, EPICOA 0629 (1992)
50C               Part B: Software implementation, EPICOA 0630 (1992)
51C
52C     See also OASIS manual (1995)
53C
54C     History:
55C     -------
56C       Version   Programmer     Date      Description
57C       -------   ----------     ----      ----------- 
58C       1.1       O. Thual       94/01/01  created
59C       2.0       L. Terray      95/12/26  modified : to suit OASIS 2.0
60C
61C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
62C
63C* ---------------------------- Include files ---------------------------
64C
65
66      USE mod_kinds_oasis
67      USE mod_unit
68C
69C* ---------------------------- Argument declarations -------------------
70C
71      REAL (kind=ip_realwp_p) pcorx(kngx,kngy), pcory(kngx,kngy)
72      REAL (kind=ip_realwp_p) psgr(kngx,kngy)
73      INTEGER (kind=ip_intwp_p) kmsk(kngx,kngy)
74      CHARACTER*1 cdtyp
75C
76C* ---------------------------- Local declarations ----------------------
77C
78      CHARACTER*1 cltyp
79C
80C* ---------------------------- Poema verses ----------------------------
81C
82C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
83C
84C*    1. Initialization
85C        --------------
86C   
87      ivma = kvma
88      cltyp = cdtyp
89C
90C
91C*    2. Interdistances only for unmasked points
92C        ---------------------------------------
93C
94C* Average distance squared in x-direction
95C
96      ztot2 = 0.
97      icount = 0
98      DO 210 j2 = 1, kngy
99      zsum = 0.
100      DO 220 j1 = 1, kngx-1
101        IF (kmsk(j1,j2) .NE. ivma) THEN
102            iadd = 0
103            IF (cltyp .ne. 'D') iadd = 1
104C* For reduced grid, calculate distance only in the x-direction between
105C* points located on same latitude circle.
106            IF (cltyp .eq. 'D' .and. pcory(j1,j2) .eq. pcory(j1+1,j2))
107     $          iadd = 1
108C* For U grid, the average distance will be calculated based on all
109C* consecutive points.
110            IF (iadd .eq. 1) then
111                zdis = sqdis(pcorx(j1,j2), pcory(j1,j2),
112     $                   pcorx(j1+1,j2), pcory(j1+1,j2))
113                icount = icount + iadd
114                zsum = zsum + zdis
115            ENDIF
116        ENDIF
117 220  CONTINUE
118      ztot2 = ztot2 + zsum
119 210  CONTINUE
120      WRITE(nulan, *)'In grstat, icount= ', icount
121      ztot2 = ztot2 / float(icount)
122C
123C* Average distance squared in y-direction
124C
125      IF ((cltyp .eq. 'D') .or. (cltyp .eq. 'U')) THEN
126          pdr = ztot2
127          ztot1 = 0.
128      ELSE
129          ztot1 = 0.
130          icount = 0
131          DO 230 j1 = 1, kngx
132            zsum = 0.
133            DO 240 j2 = 1, kngy-1
134              IF(kmsk(j1,j2) .NE. ivma) THEN
135                  zdis = sqdis(pcorx(j1,j2), pcory(j1,j2),
136     $                   pcorx(j1,j2+1), pcory(j1,j2+1))
137                  icount = icount + 1
138                  zsum = zsum + zdis
139              ENDIF
140 240        CONTINUE
141            ztot1 = ztot1 + zsum
142 230      CONTINUE
143          ztot1 = ztot1 / float(icount)
144C
145C* Get average grid square size
146C
147          pdr = (ztot1 + ztot2) / 2.
148      ENDIF
149
150C
151C
152C*    3. Surface and <hh>^-1
153C        -------------------
154C
155      zsurf = 0.
156      zhhi = 0.
157      DO 310 j2 = 1, kngy
158        DO 320 j1 = 1, kngx
159          IF (kmsk(j1,j2) .NE. ivma) THEN
160              zsurf = zsurf + psgr(j1,j2)
161              zhhi = zhhi + psgr(j1,j2) * psgr(j1,j2)
162          ENDIF
163 320    CONTINUE
164 310  CONTINUE
165C
166C* Get total surface and inverse of sum of elements squared
167C
168      psr = zsurf
169      IF (zhhi .ne. 0.) phhi = 1. / zhhi
170C
171C
172C*    4. End of routine
173C        --------------
174C 
175      RETURN       
176      END
Note: See TracBrowser for help on using the repository browser.