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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 25 - (show annotations)
Fri Mar 5 16:43:45 2010 UTC (14 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/inter_barxy.f90
File size: 12772 byte(s)
Simplified "etat0_lim.sh" and "gcm.sh" because the full versions
depended on personal arrangements for directories and machines.

Translated included files into modules. Encapsulated procedures into modules.

Moved variables from module "comgeom" to local variables of
"inigeom". Deleted some unused variables in "comgeom".

Moved variable "day_ini" from module "temps" to module "dynetat0_m".

Removed useless test on variable "time" and useless "close" statement
in procedure "leapfrog".

Removed useless call to "inigeom" in procedure "limit".

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

  ViewVC Help
Powered by ViewVC 1.1.21