/[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 24 - (show annotations)
Wed Mar 3 13:23:49 2010 UTC (14 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/inter_barxy.f90
File size: 12862 byte(s)
Created directory "phylmd/Radlwsw". Split "radlwsw.f" in files
containing a single procedure.

Removed variable "itaufinp1" in "leapfrog".

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

  ViewVC Help
Powered by ViewVC 1.1.21