/[lmdze]/trunk/Sources/phylmd/readsulfate_preind.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/readsulfate_preind.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 191 - (show annotations)
Mon May 9 19:56:28 2016 UTC (8 years, 1 month ago) by guez
File size: 5860 byte(s)
Extracted the call to read_comdissnew out of conf_gcm.

Made ok_instan a variable of module clesphys, itau_phy a variable of
module phyetat0_m, nid_ins a variable of module ini_histins_m, itap a
variable of new module time_phylmdz, so that histwrite_phy can be
called from any procedure without the need to cascade those variables
into that procedure. Made itau_w a variable of module time_phylmdz so
that it is computed only once per time step of physics.

Extracted variables of module clesphys which were in namelist
conf_phys_nml into their own namelist, clesphys_nml, and created
procedure read_clesphys reading clesphys_nml, to avoid side effect.

No need for double precision in procedure getso4fromfile. Assume there
is a single variable for the whole year in the NetCDF file instead of
one variable per month.

Created generic procedure histwrite_phy and removed procedure
write_histins, following LMDZ. histwrite_phy has only two arguments,
can be called from anywhere, and should manage the logic of writing or
not writing into various history files with various operations. So the
test on ok_instan goes inside histwrite_phy.

Test for raz_date in phyetat0 instead of physiq to avoid side effect.

Created procedure increment_itap to avoid side effect.

Removed unnecessary differences between procedures readsulfate and
readsulfate_pi.

1 module readsulfate_preind_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE readsulfate_preind(dayvrai, time, first, sulfate)
8
9 ! Read and calculate pre-industrial values of sulfate. This
10 ! routine reads monthly mean values of sulfate aerosols and
11 ! returns a linearly interpolated daily-mean field. It does so for
12 ! the preindustriel values of the sulfate, to a large part
13 ! analogous to the routine readsulfate.
14
15 ! Author:
16 ! Johannes Quaas (quaas@lmd.jussieu.fr)
17 ! June 26th, 2001
18
19 use dimens_m, only: iim, jjm
20 use dimphy, only: klon, klev
21 use dynetat0_m, only: annee_ref
22 use getso4fromfile_m, only: getso4fromfile
23
24 integer, intent(in):: dayvrai
25 ! current day number, based at value 1 on January 1st of annee_ref
26
27 REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
28
29 LOGICAL, intent(in):: first ! First timestep
30 ! (and therefore initialization necessary)
31
32 real, intent(out):: sulfate (klon, klev)
33 ! number concentration sulfate (monthly mean data, from file)
34
35 ! Local:
36 INTEGER i, ig, k, it
37 INTEGER j, iday, iyr
38 INTEGER im, day1, day2, im2
39 real so4_1(iim, jjm + 1, klev, 12)
40 double precision, save:: so4(klon, klev, 12) ! SO4 in right dimension
41 double precision, save:: so4_out(klon, klev)
42 LOGICAL lnewday
43
44 !----------------------------------------------------------------
45
46 iday = dayvrai
47
48 ! Get the year of the run
49 iyr = iday/360
50
51 ! Get the day of the actual year:
52 iday = iday - iyr*360
53
54 ! 0.02 is about 0.5/24, namly less than half an hour
55 lnewday = time < 0.02
56
57 ! All has to be done only, if a new day begins
58
59 test_newday: IF (lnewday .OR. first) THEN
60 im = iday/30 + 1 ! the actual month
61
62 ! annee_ref is the initial year (defined in temps.h)
63 iyr = iyr + annee_ref
64
65 IF (first) THEN
66 ! Initialize field
67 DO it = 1, 12
68 DO k = 1, klev
69 DO i = 1, klon
70 so4(i, k, it) = 0.
71 ENDDO
72 ENDDO
73 ENDDO
74
75 CALL getso4fromfile('.nat', so4_1)
76
77 ! Transform the horizontal 2D-field into the physics-field
78 ! (Also the levels and the latitudes have to be inversed)
79
80 DO it = 1, 12
81 DO k = 1, klev
82 ! a) at the poles, use the zonal mean:
83 DO i = 1, iim
84 ! North pole
85 so4(1, k, it) = so4(1, k, it) &
86 + so4_1(i, jjm + 1, klev + 1 - k, it)
87 ! South pole
88 so4(klon, k, it) = so4(klon, k, it) &
89 + so4_1(i, 1, klev + 1 - k, it)
90 ENDDO
91 so4(1, k, it) = so4(1, k, it)/REAL(iim)
92 so4(klon, k, it) = so4(klon, k, it)/REAL(iim)
93
94 ! b) the values between the poles:
95 ig = 1
96 DO j = 2, jjm
97 DO i = 1, iim
98 ig = ig + 1
99 if (ig > klon) stop 1
100 so4(ig, k, it) = so4_1(i, jjm + 1 - j, klev + 1 - k, it)
101 ENDDO
102 ENDDO
103 IF (ig /= klon - 1) then
104 print *, 'Error in readsulfate (var conversion)'
105 STOP 1
106 end IF
107 ENDDO ! Loop over k (vertical)
108 ENDDO ! Loop over it (months)
109 ENDIF ! Had to read new data?
110
111 ! Interpolate to actual day:
112 IF (iday < im*30 - 15) THEN
113 ! in the first half of the month use month before and actual month
114 im2 = im - 1
115 day1 = im2*30 + 15
116 day2 = im2*30 - 15
117 IF (im2 <= 0) THEN
118 ! the month is january, thus the month before december
119 im2 = 12
120 ENDIF
121 DO k = 1, klev
122 DO i = 1, klon
123 sulfate(i, k) = so4(i, k, im2) &
124 - REAL(iday - day2)/REAL(day1 - day2) &
125 * (so4(i, k, im2) - so4(i, k, im))
126 IF (sulfate(i, k) < 0.) THEN
127 IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
128 IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
129 write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
130 so4(i, k, im2) - so4(i, k, im)
131 IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
132 stop 1
133 endif
134 ENDDO
135 ENDDO
136 ELSE
137 ! the second half of the month
138 im2 = im + 1
139 IF (im2 > 12) THEN
140 ! the month is december, the following thus january
141 im2 = 1
142 ENDIF
143 day2 = im*30 - 15
144 day1 = im*30 + 15
145 DO k = 1, klev
146 DO i = 1, klon
147 sulfate(i, k) = so4(i, k, im2) &
148 - REAL(iday - day2)/REAL(day1 - day2) &
149 * (so4(i, k, im2) - so4(i, k, im))
150 IF (sulfate(i, k) < 0.) THEN
151 IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
152 IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
153 write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
154 so4(i, k, im2) - so4(i, k, im)
155 IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
156 stop 1
157 endif
158 ENDDO
159 ENDDO
160 ENDIF
161
162 DO k = 1, klev
163 DO i = 1, klon
164 so4_out(i, k) = sulfate(i, k)
165 ENDDO
166 ENDDO
167 ELSE
168 ! If no new day, use old data:
169 DO k = 1, klev
170 DO i = 1, klon
171 sulfate(i, k) = so4_out(i, k)
172 ENDDO
173 ENDDO
174 ENDIF test_newday
175
176 END SUBROUTINE readsulfate_preind
177
178 end module readsulfate_preind_m

  ViewVC Help
Powered by ViewVC 1.1.21