/[lmdze]/trunk/dyn3d/conf_dat3d.f90
ViewVC logotype

Annotation of /trunk/dyn3d/conf_dat3d.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (hide annotations)
Thu Jun 13 14:40:06 2019 UTC (5 years ago) by guez
File size: 2691 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 guez 3 module conf_dat3d_m
2    
3     IMPLICIT NONE
4    
5     contains
6    
7     SUBROUTINE conf_dat3d(xd, yd, zd, xf, yf, zf, champd)
8    
9 guez 266 ! From dyn3d/conf_dat3d.F, version 1.1.1.1, 2004/05/19 12:53:05
10 guez 3
11 guez 266 ! Author: P. Le Van
12 guez 3
13 guez 266 ! Ce sous-programme configure le champ de donn\'ees 3D 'champd' pour
14     ! que la longitude varie de - pi \`a pi, la latitude de pi/2 \`a
15     ! - pi/2 et pour que la coordonn\'ee pression soit d\'ecroissante.
16 guez 3
17 guez 39 use nr_util, only: assert_eq, pi
18 guez 3
19 guez 24 REAL, intent(in):: xd(:), yd(:) ! longitudes et latitudes initiales, en rad
20 guez 3 REAL, intent(in):: zd(:) ! pressure levels, in Pa or hPa
21    
22     REAL, intent(out):: xf(:) ! longitude, in rad, - pi to pi
23     REAL, intent(out):: yf(:) ! latitude, in rad, pi/2 to -pi/2
24     REAL, intent(out):: zf(:) ! pressure levels, in decreasing order, in Pa
25     REAL, intent(inout):: champd(:, :, :)
26    
27     ! Variables locales :
28    
29     INTEGER lons, lats, levs
30 guez 24 LOGICAL invlon
31 guez 3 REAL rlatmin, rlatmax, oldxd1
32     INTEGER i
33    
34     !--------------------------------------
35    
36     lons = assert_eq(size(xd), size(xf), size(champd, 1), "conf_dat3d lons")
37     lats = assert_eq(size(yd), size(yf), size(champd, 2), "conf_dat3d lats")
38     levs = assert_eq(size(zd), size(zf), size(champd, 3), "conf_dat3d levs")
39    
40     IF (xd(1) >= - pi - 0.5 .AND. xd(lons) <= pi + 0.5) THEN
41     invlon = .FALSE.
42     ELSE IF (xd(1) >= -0.5 .AND. xd(lons) <= 2 * pi+0.5) THEN
43     invlon = .TRUE.
44     ELSE
45 guez 266 print *, "Probl\`eme sur les longitudes des donn\'ees"
46 guez 3 stop 1
47     ENDIF
48    
49     rlatmin = MIN(yd(1), yd(lats))
50     rlatmax = MAX(yd(1), yd(lats))
51    
52 guez 24 IF (rlatmin < -pi / 2 - 0.5 .or. rlatmax > pi / 2 + 0.5) THEN
53 guez 266 print *, "Probl\`eme sur les latitudes des donn\'ees"
54 guez 3 stop 1
55     ENDIF
56    
57 guez 24 xf(:) = xd(:)
58     yf(:) = yd(:)
59 guez 3
60     IF (invlon) THEN
61 guez 266 ! On tourne les longitudes pour avoir - pi \`a pi
62 guez 3 DO i=1, lons
63     IF (xf(i) > pi) exit
64     ENDDO
65    
66     where (xf > pi) xf = xf - 2 * pi
67     xf = cshift(xf, i - 1)
68     ! On tourne les longitudes pour "champd":
69     champd = cshift(champd, i - 1)
70     ENDIF
71    
72     IF (yd(1) < yd(lats)) THEN
73     yf = yf(lats:1:-1)
74     champd = champd(:, lats:1:-1, :)
75     ENDIF
76    
77     oldxd1 = xf(1)
78     forall (i = 1: lons-1) xf(i) = 0.5 * (xf(i) + xf(i+1))
79     xf(lons) = 0.5 * (xf(lons) + oldxd1 + 2 * pi)
80     forall (i = 1: lats-1) yf(i) = 0.5 * (yf(i) + yf(i+1))
81    
82     IF (MAX(zd(1), zd(levs)) < 1200.) THEN
83     zf(:) = zd(:) * 100. ! convert from hPa to Pa
84     else
85     zf(:) = zd(:)
86     ENDIF
87    
88     IF (zd(1) < zd(levs)) THEN
89     zf(:) = zf(levs:1:-1)
90     champd(:, :, :) = champd(:, :, levs:1:-1)
91     ENDIF
92    
93     END SUBROUTINE conf_dat3d
94    
95     end module conf_dat3d_m

  ViewVC Help
Powered by ViewVC 1.1.21