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

Contents of /trunk/dyn3d/conf_dat3d.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 266 - (show annotations)
Thu Apr 19 17:54:55 2018 UTC (6 years ago) by guez
File size: 2691 byte(s)
Define macros of the preprocessor CPP_IIM, CPP_JJM, CPP_LLM so we can
control the resolution from the compilation command, and automate
compilation for several resolutions.

In module yoethf_m, transform variables into named constants. So we do
not need procedure yoethf any longer.

Bug fix in program test_inter_barxy, missing calls to fyhyp and fxhyp,
and definition of rlatu.

Remove variable iecri of module conf_gcm_m. The files dyn_hist*.nc are
written every time step. We are simplifying the output system, pending
replacement by a whole new system.

Modify possible value of vert_sampling from "param" to
"strato_custom", following LMDZ. Default values of corresponding
namelist variables are now the values used for LMDZ CMIP6.

1 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 ! From dyn3d/conf_dat3d.F, version 1.1.1.1, 2004/05/19 12:53:05
10
11 ! Author: P. Le Van
12
13 ! 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
17 use nr_util, only: assert_eq, pi
18
19 REAL, intent(in):: xd(:), yd(:) ! longitudes et latitudes initiales, en rad
20 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 LOGICAL invlon
31 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 print *, "Probl\`eme sur les longitudes des donn\'ees"
46 stop 1
47 ENDIF
48
49 rlatmin = MIN(yd(1), yd(lats))
50 rlatmax = MAX(yd(1), yd(lats))
51
52 IF (rlatmin < -pi / 2 - 0.5 .or. rlatmax > pi / 2 + 0.5) THEN
53 print *, "Probl\`eme sur les latitudes des donn\'ees"
54 stop 1
55 ENDIF
56
57 xf(:) = xd(:)
58 yf(:) = yd(:)
59
60 IF (invlon) THEN
61 ! On tourne les longitudes pour avoir - pi \`a pi
62 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