/[lmdze]/trunk/dyn3d/Inter_barxy/inter_barxy.f
ViewVC logotype

Annotation of /trunk/dyn3d/Inter_barxy/inter_barxy.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 13 - (hide annotations)
Fri Jul 25 19:59:34 2008 UTC (15 years, 10 months ago) by guez
Original Path: trunk/libf/dyn3d/inter_barxy.f90
File size: 12861 byte(s)
-- Minor change of behaviour:

"etat0" does not compute "rugsrel" nor "radpas". Deleted arguments
"radpas" and "rugsrel" of "phyredem". Deleted argument "rugsrel" of
"phyetat0". "startphy.nc" does not contain the variable "RUGSREL". In
"physiq", "rugoro" is set to 0 if not "ok_orodr". The whole program
"etat0_lim" does not use "clesphys2".

-- Minor modification of input/output:

Created subroutine "read_clesphys2". Variables of "clesphys2" are read
in "read_clesphys2" instead of "conf_gcm". "printflag" does not print
variables of "clesphys2".

-- Should not change any result at run time:

References to module "numer_rec" instead of individual modules of
"Numer_rec_Lionel".

Deleted argument "clesphy0" of "calfis", "physiq", "conf_gcm",
"leapfrog", "phyetat0". Deleted variable "clesphy0" in
"gcm". "phyetat0" does not modify variables of "clesphys2".

The program unit "gcm" does not modify "itau_phy".

Added some "intent" attributes.

"regr11_lint" does not call "polint".

1 guez 3 module inter_barxy_m
2    
3     ! From inter_barxy.F, version 1.1.1.1 2004/05/19 12:53:07
4    
5     ! This file is clean: there is neither C preprocessor directive, nor
6     ! include line.
7    
8     implicit none
9    
10     private
11     public inter_barxy
12    
13     contains
14    
15     SUBROUTINE inter_barxy(dlonid, dlatid, champ, rlonimod, rlatimod, champint)
16    
17     ! Author: P. Le Van
18    
19 guez 13 use numer_rec, only: assert_eq, assert
20 guez 3
21     use dimens_m, only: iim, jjm
22     use comgeom, only: aire_2d, apoln, apols
23    
24     REAL, intent(in):: dlonid(:)
25     ! (longitude from input file, in rad, from -pi to pi)
26    
27     REAL, intent(in):: dlatid(:), champ(:, :), rlonimod(:)
28    
29     REAL, intent(in):: rlatimod(:)
30     ! (latitude angle, in degrees or rad, in strictly decreasing order)
31    
32     real, intent(out):: champint(:, :)
33     ! Si taille de la seconde dim = jjm + 1, on veut interpoler sur les
34     ! jjm+1 latitudes rlatu du modele (latitudes des scalaires et de U)
35     ! Si taille de la seconde dim = jjm, on veut interpoler sur les
36     ! jjm latitudes rlatv du modèle (latitudes de V)
37    
38     ! Variables local to the procedure:
39    
40     REAL champy(iim, size(champ, 2))
41     integer j, i, jnterfd, jmods
42    
43     REAL yjmod(size(champint, 2))
44     ! (angle, in degrees, in strictly increasing order)
45    
46     REAL yjdat(size(dlatid) + 1) ! angle, in degrees, in increasing order
47     LOGICAL decrois ! "dlatid" is in decreasing order
48    
49     !-----------------------------------
50    
51     jnterfd = assert_eq(size(champ, 2) - 1, size(dlatid), &
52     "inter_barxy jnterfd")
53     jmods = size(champint, 2)
54     call assert(size(champ, 1) == size(dlonid), "inter_barxy size(champ, 1)")
55     call assert((/size(rlonimod), size(champint, 1)/) == iim, &
56     "inter_barxy iim")
57     call assert(any(jmods == (/jjm, jjm + 1/)), 'inter_barxy jmods')
58     call assert(size(rlatimod) == jjm, "inter_barxy size(rlatimod)")
59    
60     ! Check decreasing order for "rlatimod":
61     DO i = 2, jjm
62     IF (rlatimod(i) >= rlatimod(i-1)) stop &
63     '"inter_barxy": "rlatimod" should be strictly decreasing'
64     ENDDO
65    
66     yjmod(:jjm) = ord_coordm(rlatimod)
67     IF (jmods == jjm + 1) THEN
68     IF (90. - yjmod(jjm) < 0.01) stop &
69     '"inter_barxy": with jmods = jjm + 1, yjmod(jjm) should be < 90.'
70     ELSE
71     ! jmods = jjm
72     IF (ABS(yjmod(jjm) - 90.) > 0.01) stop &
73     '"inter_barxy": with jmods = jjm, yjmod(jjm) should be 90.'
74     ENDIF
75    
76     if (jmods == jjm + 1) yjmod(jjm + 1) = 90.
77    
78     DO j = 1, jnterfd + 1
79     champy(:, j) = inter_barx(dlonid, champ(:, j), rlonimod)
80     ENDDO
81    
82     CALL ord_coord(dlatid, yjdat, decrois)
83     IF (decrois) champy(:, :) = champy(:, jnterfd + 1:1:-1)
84     DO i = 1, iim
85     champint(i, :) = inter_bary(yjdat, champy(i, :), yjmod)
86     ENDDO
87     champint(:, :) = champint(:, jmods:1:-1)
88    
89     IF (jmods == jjm + 1) THEN
90     ! Valeurs uniques aux poles
91     champint(:, 1) = SUM(aire_2d(:iim, 1) * champint(:, 1)) / apoln
92     champint(:, jjm + 1) = SUM(aire_2d(:iim, jjm + 1) &
93     * champint(:, jjm + 1)) / apols
94     ENDIF
95    
96     END SUBROUTINE inter_barxy
97    
98     !******************************
99    
100     function inter_barx(dlonid, fdat, rlonimod)
101    
102     ! From dyn3d/inter_barx.F, v 1.1.1.1 2004/05/19 12:53:06
103    
104     ! Auteurs : Robert Sadourny, P. Le Van
105    
106     ! INTERPOLATION BARYCENTRIQUE BASEE SUR LES AIRES
107     ! VERSION UNIDIMENSIONNELLE , EN LONGITUDE .
108    
109     ! idat : indice du champ de donnees, de 1 a idatmax
110     ! imod : indice du champ du modele, de 1 a imodmax
111     ! fdat(idat) : champ de donnees (entrees)
112     ! inter_barx(imod) : champ du modele (sorties)
113     ! dlonid(idat): abscisses des interfaces des mailles donnees
114     ! rlonimod(imod): abscisses des interfaces des mailles modele
115     ! ( L'indice 1 correspond a l'interface mailLE 1 / maille 2)
116     ! ( Les abscisses sont exprimées en degres)
117    
118 guez 13 use numer_rec, only: assert_eq
119 guez 3
120     IMPLICIT NONE
121    
122     REAL, intent(in):: dlonid(:)
123     real, intent(in):: fdat(:)
124     real, intent(in):: rlonimod(:)
125    
126     real inter_barx(size(rlonimod))
127    
128     ! ... Variables locales ...
129    
130     INTEGER idatmax, imodmax
131     REAL xxid(size(dlonid)+1), xxd(size(dlonid)+1), fdd(size(dlonid)+1)
132     REAL fxd(size(dlonid)+1), xchan(size(dlonid)+1), fdchan(size(dlonid)+1)
133     REAL xxim(size(rlonimod))
134    
135     REAL x0, xim0, dx, dxm
136     REAL chmin, chmax, pi
137    
138     INTEGER imod, idat, i, ichang, id0, id1, nid, idatmax1
139    
140     !-----------------------------------------------------
141    
142     idatmax = assert_eq(size(dlonid), size(fdat), "inter_barx idatmax")
143     imodmax = size(rlonimod)
144    
145     pi = 2. * ASIN(1.)
146    
147     ! REDEFINITION DE L'ORIGINE DES ABSCISSES
148     ! A L'INTERFACE OUEST DE LA PREMIERE MAILLE DU MODELE
149     DO imod = 1, imodmax
150     xxim(imod) = rlonimod(imod)
151     ENDDO
152    
153     CALL minmax( imodmax, xxim, chmin, chmax)
154     IF( chmax.LT.6.50 ) THEN
155     DO imod = 1, imodmax
156     xxim(imod) = xxim(imod) * 180./pi
157     ENDDO
158     ENDIF
159    
160     xim0 = xxim(imodmax) - 360.
161    
162     DO imod = 1, imodmax
163     xxim(imod) = xxim(imod) - xim0
164     ENDDO
165    
166     idatmax1 = idatmax +1
167    
168     DO idat = 1, idatmax
169     xxd(idat) = dlonid(idat)
170     ENDDO
171    
172     CALL minmax( idatmax, xxd, chmin, chmax)
173     IF( chmax.LT.6.50 ) THEN
174     DO idat = 1, idatmax
175     xxd(idat) = xxd(idat) * 180./pi
176     ENDDO
177     ENDIF
178    
179     DO idat = 1, idatmax
180     xxd(idat) = AMOD( xxd(idat) - xim0, 360. )
181     fdd(idat) = fdat (idat)
182     ENDDO
183    
184     i = 2
185     DO while (xxd(i) >= xxd(i-1) .and. i < idatmax)
186     i = i + 1
187     ENDDO
188     IF (xxd(i) < xxd(i-1)) THEN
189     ichang = i
190     ! *** reorganisation des longitudes entre 0. et 360. degres ****
191     nid = idatmax - ichang +1
192     DO i = 1, nid
193     xchan (i) = xxd(i+ichang -1 )
194     fdchan(i) = fdd(i+ichang -1 )
195     ENDDO
196     DO i=1, ichang -1
197     xchan (i+ nid) = xxd(i)
198     fdchan(i+nid) = fdd(i)
199     ENDDO
200     DO i =1, idatmax
201     xxd(i) = xchan(i)
202     fdd(i) = fdchan(i)
203     ENDDO
204     end IF
205    
206     ! translation des champs de donnees par rapport
207     ! a la nouvelle origine, avec redondance de la
208     ! maille a cheval sur les bords
209    
210     id0 = 0
211     id1 = 0
212    
213     DO idat = 1, idatmax
214     IF ( xxd( idatmax1- idat ).LT.360.) exit
215     id1 = id1 + 1
216     ENDDO
217    
218     DO idat = 1, idatmax
219     IF (xxd(idat).GT.0.) exit
220     id0 = id0 + 1
221     END DO
222    
223     IF( id1 /= 0 ) then
224     DO idat = 1, id1
225     xxid(idat) = xxd(idatmax - id1 + idat) - 360.
226     fxd (idat) = fdd(idatmax - id1 + idat)
227     END DO
228     DO idat = 1, idatmax - id1
229     xxid(idat + id1) = xxd(idat)
230     fxd (idat + id1) = fdd(idat)
231     END DO
232     end IF
233    
234     IF(id0 /= 0) then
235     DO idat = 1, idatmax - id0
236     xxid(idat) = xxd(idat + id0)
237     fxd (idat) = fdd(idat + id0)
238     END DO
239    
240     DO idat = 1, id0
241     xxid (idatmax - id0 + idat) = xxd(idat) + 360.
242     fxd (idatmax - id0 + idat) = fdd(idat)
243     END DO
244     else
245     DO idat = 1, idatmax
246     xxid(idat) = xxd(idat)
247     fxd (idat) = fdd(idat)
248     ENDDO
249     end IF
250     xxid(idatmax1) = xxid(1) + 360.
251     fxd (idatmax1) = fxd(1)
252    
253     ! initialisation du champ du modele
254    
255     inter_barx(:) = 0.
256    
257     ! iteration
258    
259     x0 = xim0
260     dxm = 0.
261     imod = 1
262     idat = 1
263    
264     do while (imod <= imodmax)
265     do while (xxim(imod).GT.xxid(idat))
266     dx = xxid(idat) - x0
267     dxm = dxm + dx
268     inter_barx(imod) = inter_barx(imod) + dx * fxd(idat)
269     x0 = xxid(idat)
270     idat = idat + 1
271     end do
272     IF (xxim(imod).LT.xxid(idat)) THEN
273     dx = xxim(imod) - x0
274     dxm = dxm + dx
275     inter_barx(imod) = (inter_barx(imod) + dx * fxd(idat)) / dxm
276     x0 = xxim(imod)
277     dxm = 0.
278     imod = imod + 1
279     ELSE
280     dx = xxim(imod) - x0
281     dxm = dxm + dx
282     inter_barx(imod) = (inter_barx(imod) + dx * fxd(idat)) / dxm
283     x0 = xxim(imod)
284     dxm = 0.
285     imod = imod + 1
286     idat = idat + 1
287     END IF
288     end do
289    
290     END function inter_barx
291    
292     !******************************
293    
294     function inter_bary(yjdat, fdat, yjmod)
295    
296     ! From dyn3d/inter_bary.F, version 1.1.1.1 2004/05/19 12:53:06
297     ! Authors: R. Sadourny, P. Le Van
298    
299     ! Interpolation barycentrique basée sur les aires.
300     ! Version unidimensionnelle, en latitude.
301     ! L'indice 1 correspond à l'interface maille 1 -- maille 2.
302    
303 guez 13 use numer_rec, only: assert
304 guez 3
305     IMPLICIT NONE
306    
307     REAL, intent(in):: yjdat(:)
308     ! (angles, ordonnées des interfaces des mailles des données, in
309     ! degrees, in increasing order)
310    
311     REAL, intent(in):: fdat(:) ! champ de données
312    
313     REAL, intent(in):: yjmod(:)
314     ! (ordonnées des interfaces des mailles du modèle)
315     ! (in degrees, in strictly increasing order)
316    
317     REAL inter_bary(size(yjmod)) ! champ du modèle
318    
319     ! Variables local to the procedure:
320    
321     REAL y0, dy, dym
322     INTEGER jdat ! indice du champ de données
323     integer jmod ! indice du champ du modèle
324    
325     !------------------------------------
326    
327     call assert(size(yjdat) == size(fdat), "inter_bary")
328    
329     ! Initialisation des variables
330     inter_bary(:) = 0.
331     y0 = -90.
332     dym = 0.
333     jmod = 1
334     jdat = 1
335    
336     do while (jmod <= size(yjmod))
337     do while (yjmod(jmod) > yjdat(jdat))
338     dy = yjdat(jdat) - y0
339     dym = dym + dy
340     inter_bary(jmod) = inter_bary(jmod) + dy * fdat(jdat)
341     y0 = yjdat(jdat)
342     jdat = jdat + 1
343     end do
344     IF (yjmod(jmod) < yjdat(jdat)) THEN
345     dy = yjmod(jmod) - y0
346     dym = dym + dy
347     inter_bary(jmod) = (inter_bary(jmod) + dy * fdat(jdat)) / dym
348     y0 = yjmod(jmod)
349     dym = 0.
350     jmod = jmod + 1
351     ELSE
352     ! yjmod(jmod) == yjdat(jdat)
353     dy = yjmod(jmod) - y0
354     dym = dym + dy
355     inter_bary(jmod) = (inter_bary(jmod) + dy * fdat(jdat)) / dym
356     y0 = yjmod(jmod)
357     dym = 0.
358     jmod = jmod + 1
359     jdat = jdat + 1
360     END IF
361     end do
362     ! Le test de fin suppose que l'interface 0 est commune aux deux
363     ! grilles "yjdat" et "yjmod".
364    
365     END function inter_bary
366    
367     !******************************
368    
369     SUBROUTINE ord_coord(xi, xo, decrois)
370    
371     ! From dyn3d/ord_coord.F, version 1.1.1.1 2004/05/19 12:53:06
372     ! Author : P. Le Van
373    
374     ! This procedure receives an array of latitudes.
375     ! It converts them to degrees if they are in radians.
376     ! If the input latitudes are in decreasing order, the procedure
377     ! reverses their order.
378     ! Finally, the procedure adds 90° as the last value of the array.
379    
380 guez 13 use numer_rec, only: assert_eq
381 guez 3 use comconst, only: pi
382    
383     IMPLICIT NONE
384    
385     REAL, intent(in):: xi(:)
386     ! (latitude, in degrees or radians, in increasing or decreasing order)
387     ! ("xi" should contain latitudes from pole to pole.
388     ! "xi" should contain the latitudes of the boundaries of grid
389     ! cells, not the centers of grid cells.
390     ! So the extreme values should not be 90° and -90°.)
391    
392     REAL, intent(out):: xo(:) ! angles in degrees
393     LOGICAL, intent(out):: decrois
394    
395     ! Variables local to the procedure:
396     INTEGER nmax, i
397    
398     !--------------------
399    
400     nmax = assert_eq(size(xi), size(xo) - 1, "ord_coord")
401    
402     ! Check monotonicity:
403     decrois = xi(2) < xi(1)
404     DO i = 3, nmax
405     IF (decrois .neqv. xi(i) < xi(i-1)) stop &
406     '"ord_coord": latitudes are not monotonic'
407     ENDDO
408    
409     IF (abs(xi(1)) < pi) then
410     ! "xi" contains latitudes in radians
411     xo(:nmax) = xi(:) * 180. / pi
412     else
413     ! "xi" contains latitudes in degrees
414     xo(:nmax) = xi(:)
415     end IF
416    
417     IF (ABS(abs(xo(1)) - 90) < 0.001 .or. ABS(abs(xo(nmax)) - 90) < 0.001) THEN
418     print *, "ord_coord"
419     PRINT *, '"xi" should contain the latitudes of the boundaries of ' &
420     // 'grid cells, not the centers of grid cells.'
421     STOP
422     ENDIF
423    
424     IF (decrois) xo(:nmax) = xo(nmax:1:- 1)
425     xo(nmax + 1) = 90.
426    
427     END SUBROUTINE ord_coord
428    
429     !***********************************
430    
431     function ord_coordm(xi)
432    
433     ! From dyn3d/ord_coordm.F, version 1.1.1.1 2004/05/19 12:53:06
434     ! Author : P. Le Van
435    
436     ! This procedure converts to degrees, if necessary, and inverts the
437     ! order.
438    
439     use comconst, only: pi
440    
441     IMPLICIT NONE
442    
443     REAL, intent(in):: xi(:) ! angle, in rad or degrees
444     REAL ord_coordm(size(xi)) ! angle, in degrees
445    
446     !-----------------------------
447    
448     IF (xi(1) < 6.5) THEN
449     ! "xi" is in rad
450     ord_coordm(:) = xi(size(xi):1:-1) * 180. / pi
451     else
452     ! "xi" is in degrees
453     ord_coordm(:) = xi(size(xi):1:-1)
454     ENDIF
455    
456     END function ord_coordm
457    
458     end module inter_barxy_m

  ViewVC Help
Powered by ViewVC 1.1.21