source: CPL/oasis3/trunk/src/lib/anaisg/src/qgrho.f @ 1906

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

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

File size: 6.2 KB
Line 
1      SUBROUTINE qgrho (prho, kto, kwg,
2     $                  px, py,
3     $                  px1, py1, kmsk1, kngx1, kngy1,
4     $                  psig, kvma1)
5C****
6C               *****************************
7C               * OASIS ROUTINE  -  LEVEL 3 *
8C               * -------------     ------- *
9C               *****************************
10C
11C**** *qgrho* - Calculate weights and adresses at one location 
12C
13C     Purpose:
14C     -------
15C     At one location xgr gives the kwg closest neighbours 
16C     adresses kto in grid 1 and their weight, which is function of
17C     the distance and may be other grid dependant considerations. 
18C
19C**   Interface:
20C     ---------
21C       *CALL*  *qgrho(prho, kto, kwg,
22C                      px, py,
23C                      px1, py1, kmsk1, kngx1, kngy1,
24C                      psig, kvma1)* 
25C
26C     Input:
27C     -----
28C                kwg   : maximum number of overlapped neighbors
29C                px    : longitude of the current point on target grid
30C                py    : latitude of the current point on source grid
31C                px1   : longitudes for source grid (real 2D)
32C                py1   : latitudes for source grid (real 2D)
33C                kmsk1 : the mask for source grid (integer 2D)
34C                kngx1 : number of longitudes for source grid
35C                kngy1 : number of latitudes for source grid
36C                kvma1 : the value of the mask for source grid
37C                psig  : variance of the gaussian
38C     Output:
39C     ------
40C                prho  : the neighbors weights 
41C                kto   : the neighbors adresses in the source grid 
42C
43C     Workspace:
44C     ---------
45C     None
46C
47C     External:
48C     --------
49C     qlsort, sqdis, qlins, qlgaus
50C
51C     References:
52C     ----------
53C     O. Thual, Simple ocean-atmosphere interpolation. 
54C               Part A: The method, EPICOA 0629 (1992)
55C               Part B: Software implementation, EPICOA 0630 (1992)
56C     See also OASIS manual (1995)
57C
58C     History:
59C     -------
60C       Version   Programmer     Date      Description
61C       -------   ----------     ----      ----------- 
62C       1.1       O. Thual       93/04/15  created 
63C       2.0       L. Terray      95/10/01  modified: new structure
64C
65C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
66C
67C* ---------------------------- Include files ---------------------------
68C
69      USE mod_kinds_oasis
70      USE mod_unit
71C
72C* ---------------------------- Argument declarations -------------------
73C
74      REAL (kind=ip_realwp_p) px1(kngx1,kngy1), py1(kngx1,kngy1)
75      REAL (kind=ip_realwp_p) prho(kwg)
76      INTEGER (kind=ip_intwp_p) kmsk1(kngx1,kngy1)
77      INTEGER (kind=ip_intwp_p) kto(kwg)
78C
79C* ---------------------------- Poema verses ----------------------------
80C
81C %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
82C     
83C*    1. Various initializations
84C        -----------------------
85C
86C* Value of the mask
87C
88      ivma = kvma1
89      ing = kngx1 * kngy1
90C
91C
92C*    2. Nearest neighbors search
93C        ------------------------
94C
95C* Checks
96C     
97      IF (kwg .GT. ing) THEN
98          WRITE (UNIT = nulou,FMT = *) 'WARNING kwg = ',kwg,
99     $                  '.GT. kngx1*kngy1 = ',ing
100          WRITE (UNIT = nulou,FMT = *) 
101     $        ' Number of searched neighbors greater '
102          WRITE (UNIT = nulou,FMT = *) 
103     $        ' than number of grid points '
104          iwg = ing
105          WRITE (UNIT = nulou,FMT = *)  'We set  iwg = ing = ',iwg
106        ELSE
107         iwg = kwg
108      ENDIF
109C
110C
111C* Put first iwg unmasked points of source grid in kto and prho
112C
113      iind = 0
114      DO 210 j2 = 1, kngy1
115        DO 220 j1 = 1, kngx1
116          IF (kmsk1(j1,j2) .NE. ivma) THEN
117              iind = iind + 1
118              icum = (j2-1) * kngx1 + j1
119              prho(iind) = sqdis (px, py, px1(j1,j2), py1(j1,j2))
120              kto(iind) = icum
121              i1t = j1
122              i2t = j2
123              IF (iind .EQ. iwg) GO TO 225
124          ENDIF
125 220    CONTINUE
126 210  CONTINUE
127 225  CONTINUE
128C
129C* Check
130C
131      IF (iind .NE. iwg) THEN
132          WRITE(UNIT = nulou,FMT = *) 
133     $        ' WARNING: iind.ne.iwg ===> ',iind, iwg
134          WRITE(UNIT = nulou,FMT = *) 
135     $        ' *******  ===> Program must stop '
136          CALL HALTE ('STOP in qgrho')
137      ENDIF
138C
139C* Sorting of these first iwg points
140C
141      CALL qlsort (prho, kto, iwg)
142C
143C* Loop on the remaining points of source grid
144C
145      IF (iwg .NE. ing) THEN   
146C
147C* Loop over the remaining longitudes for latitude i2t on source grid 
148C  if necessary
149C
150          IF (i1t .LT. kngx1) THEN     
151              DO 230 j1 = i1t+1, kngx1
152                IF (kmsk1(j1,i2t) .NE. ivma) THEN
153                    icum = (i2t-1) * kngx1 + j1
154C
155C* Calculate distance between the current source grid point and
156C  the given target grid point
157C
158                    zrnew = sqdis (px, py, px1(j1,i2t), py1(j1,i2t))
159C
160C* Insert in list at the correct rank
161C
162                    CALL qlins (prho, kto, iwg, zrnew, icum)
163                ENDIF
164 230          CONTINUE
165          ENDIF
166C
167C* Loop over the remaining source grid points
168C
169          DO 240 j2 = i2t+1, kngy1
170            DO 250 j1 = 1, kngx1
171              IF (kmsk1(j1,j2) .NE. ivma) THEN
172                  icum = (j2-1) * kngx1 + j1
173C
174C* Calculate distance between the current source grid point and
175C  the given target grid point
176C
177                  zrnew = sqdis (px, py, px1(j1,j2), py1(j1,j2))
178C
179C* Insert in list at the correct rank
180C
181                  CALL qlins (prho, kto, iwg, zrnew, icum)
182              ENDIF
183 250        CONTINUE
184 240      CONTINUE
185      ENDIF
186C 
187C
188C*    3. Weight function
189C        ---------------
190C
191C* Gaussian value for the weight function
192C
193      zsum = 0.
194      DO 310 jwg = 1, iwg
195          zr = qlgaus (prho(jwg), psig)
196          zsum = zsum + zr
197          prho(jwg) = zr
198 310  CONTINUE
199C
200C* Normalization
201C
202      zthres = 1.e-6
203C
204C* If under threshold
205C
206      IF (zsum .LT. zthres) THEN
207          WRITE(UNIT=nulou,FMT=*) 'Gaussian sum under threshold value'
208          DO 320 jwg = 1, iwg
209            prho(jwg) = 1. / float(iwg)
210 320      CONTINUE
211C
212        ELSE
213C
214C* If above threshold
215C
216          DO 330 jwg = 1, iwg
217            prho(jwg) = prho(jwg) / zsum
218 330      CONTINUE
219      ENDIF
220C
221C* End of routine
222C
223      RETURN
224      END
Note: See TracBrowser for help on using the repository browser.