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

Annotation of /trunk/Sources/phylmd/readsulfate.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 191 - (hide annotations)
Mon May 9 19:56:28 2016 UTC (8 years, 1 month ago) by guez
File size: 7753 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 guez 69 module readsulfate_m
2 guez 3
3 guez 68 IMPLICIT none
4 guez 3
5 guez 69 contains
6 guez 3
7 guez 130 SUBROUTINE readsulfate(dayvrai, time, first, sulfate)
8 guez 3
9 guez 69 ! From LMDZ4/libf/phylmd/readsulfate.F, version 1.2 2005/05/19
10     ! 08:27:15 fairhead
11 guez 3
12 guez 191 ! This routine reads monthly mean values of sulfate aerosols and
13 guez 69 ! returns a linearly interpolated daily-mean field.
14 guez 3
15 guez 69 ! Author: Johannes Quaas (quaas@lmd.jussieu.fr)
16 guez 191 ! April 26th, 2001
17 guez 3
18 guez 69 ! ATTENTION!! runs are supposed to start with Jan, 1. 1930
19 guez 191 ! (rday = 1)
20 guez 3
21 guez 191 ! The model always has 360 days per year.
22     ! SO4 concentration rather than mixing ratio
23     ! 10yr-mean-values to interpolate
24     ! Introduce flag to read in just one decade
25 guez 3
26 guez 191 use dimens_m, only: iim, jjm
27     use dimphy, only: klon, klev
28     use dynetat0_m, only: annee_ref
29 guez 69 use getso4fromfile_m, only: getso4fromfile
30 guez 3
31 guez 130 integer, intent(in):: dayvrai
32     ! current day number, based at value 1 on January 1st of annee_ref
33    
34     REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
35    
36 guez 191 LOGICAL, intent(in):: first ! First timestep
37 guez 69 ! (and therefore initialization necessary)
38 guez 3
39 guez 191 real, intent(out):: sulfate(klon, klev)
40     ! mass of sulfate (monthly mean data, from file) (micro g SO4 / m3)
41 guez 3
42 guez 191 ! Local:
43 guez 69 INTEGER i, ig, k, it
44 guez 188 INTEGER j, iday, iyr, iyr1, iyr2
45 guez 191 CHARACTER(len = 4) cyear
46 guez 69 INTEGER im, day1, day2, im2
47 guez 191 real so4_1(iim, jjm + 1, klev, 12)
48     real so4_2(iim, jjm + 1, klev, 12) ! sulfate distributions
49     double precision, save:: so4(klon, klev, 12) ! SO4 in right dimension
50     double precision, save:: so4_out(klon, klev)
51 guez 69 LOGICAL lnewday
52 guez 3
53 guez 191 !----------------------------------------------------------------
54 guez 3
55 guez 130 iday = dayvrai
56 guez 3
57 guez 69 ! Get the year of the run
58 guez 191 iyr = iday/360
59 guez 3
60 guez 69 ! Get the day of the actual year:
61 guez 191 iday = iday - iyr*360
62 guez 3
63 guez 69 ! 0.02 is about 0.5/24, namly less than half an hour
64 guez 130 lnewday = time < 0.02
65 guez 3
66 guez 191 ! All has to be done only, if a new day begins
67 guez 3
68 guez 191 test_newday: IF (lnewday .OR. first) THEN
69     im = iday/30 + 1 ! the actual month
70    
71 guez 69 ! annee_ref is the initial year (defined in temps.h)
72     iyr = iyr + annee_ref
73 guez 3
74 guez 69 ! Do I have to read new data? (Is this the first day of a year?)
75 guez 191 IF (first .OR. iday == 1.) THEN
76     ! Initialize field
77     DO it = 1, 12
78     DO k = 1, klev
79     DO i = 1, klon
80     so4(i, k, it) = 0.
81 guez 69 ENDDO
82     ENDDO
83     ENDDO
84 guez 3
85 guez 191 IF (iyr < 1850) THEN
86     cyear = '.nat'
87     print *, 'getso4 iyr = ', iyr, ' ', cyear
88 guez 69 CALL getso4fromfile(cyear, so4_1)
89 guez 191 ELSE IF (iyr >= 2100) THEN
90     cyear = '2100'
91     print *, 'getso4 iyr = ', iyr, ' ', cyear
92 guez 69 CALL getso4fromfile(cyear, so4_1)
93     ELSE
94     ! Read in data:
95     ! a) from actual 10-yr-period
96 guez 3
97 guez 191 IF (iyr < 1900) THEN
98 guez 69 iyr1 = 1850
99     iyr2 = 1900
100 guez 191 ELSE IF (iyr >= 1900.and.iyr < 1920) THEN
101 guez 69 iyr1 = 1900
102     iyr2 = 1920
103     ELSE
104     iyr1 = INT(iyr/10)*10
105 guez 191 iyr2 = INT(1 + iyr/10)*10
106 guez 69 ENDIF
107 guez 191 WRITE(cyear, '(I4)') iyr1
108     print *, 'getso4 iyr = ', iyr, ' ', cyear
109 guez 69 CALL getso4fromfile(cyear, so4_1)
110 guez 3
111 guez 191 ! Read two decades:
112     ! b) from the next following one
113     WRITE(cyear, '(I4)') iyr2
114     print *, 'getso4 iyr = ', iyr, ' ', cyear
115     CALL getso4fromfile(cyear, so4_2)
116 guez 3
117 guez 69 ! Interpolate linarily to the actual year:
118 guez 191 DO it = 1, 12
119     DO k = 1, klev
120     DO j = 1, jjm
121     DO i = 1, iim
122     so4_1(i, j, k, it) = so4_1(i, j, k, it) &
123     - REAL(iyr - iyr1)/REAL(iyr2 - iyr1) &
124     * (so4_1(i, j, k, it) - so4_2(i, j, k, it))
125 guez 69 ENDDO
126     ENDDO
127     ENDDO
128     ENDDO
129 guez 191 ENDIF
130 guez 69
131     ! Transform the horizontal 2D-field into the physics-field
132     ! (Also the levels and the latitudes have to be inversed)
133    
134 guez 191 DO it = 1, 12
135     DO k = 1, klev
136 guez 69 ! a) at the poles, use the zonal mean:
137 guez 191 DO i = 1, iim
138 guez 69 ! North pole
139 guez 191 so4(1, k, it) = so4(1, k, it) &
140     + so4_1(i, jjm + 1, klev + 1 - k, it)
141 guez 69 ! South pole
142 guez 191 so4(klon, k, it) = so4(klon, k, it) &
143     + so4_1(i, 1, klev + 1 - k, it)
144 guez 69 ENDDO
145 guez 191 so4(1, k, it) = so4(1, k, it)/REAL(iim)
146     so4(klon, k, it) = so4(klon, k, it)/REAL(iim)
147 guez 69
148     ! b) the values between the poles:
149 guez 191 ig = 1
150     DO j = 2, jjm
151     DO i = 1, iim
152     ig = ig + 1
153     if (ig > klon) stop 1
154     so4(ig, k, it) = so4_1(i, jjm + 1 - j, klev + 1 - k, it)
155 guez 69 ENDDO
156     ENDDO
157 guez 191 IF (ig /= klon - 1) then
158     print *, 'Error in readsulfate (var conversion)'
159     STOP 1
160     end IF
161 guez 69 ENDDO ! Loop over k (vertical)
162     ENDDO ! Loop over it (months)
163     ENDIF ! Had to read new data?
164    
165     ! Interpolate to actual day:
166 guez 191 IF (iday < im*30 - 15) THEN
167 guez 69 ! in the first half of the month use month before and actual month
168 guez 191 im2 = im - 1
169     day1 = im2*30 + 15
170     day2 = im2*30 - 15
171     IF (im2 <= 0) THEN
172 guez 69 ! the month is january, thus the month before december
173 guez 191 im2 = 12
174 guez 69 ENDIF
175 guez 191 DO k = 1, klev
176     DO i = 1, klon
177     sulfate(i, k) = so4(i, k, im2) &
178     - REAL(iday - day2)/REAL(day1 - day2) &
179     * (so4(i, k, im2) - so4(i, k, im))
180     IF (sulfate(i, k) < 0.) THEN
181     IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
182     IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
183     write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
184     so4(i, k, im2) - so4(i, k, im)
185     IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
186     stop 1
187 guez 69 endif
188     ENDDO
189     ENDDO
190     ELSE
191     ! the second half of the month
192 guez 191 im2 = im + 1
193     IF (im2 > 12) THEN
194 guez 69 ! the month is december, the following thus january
195 guez 191 im2 = 1
196 guez 69 ENDIF
197 guez 191 day2 = im*30 - 15
198     day1 = im*30 + 15
199     DO k = 1, klev
200     DO i = 1, klon
201     sulfate(i, k) = so4(i, k, im2) &
202     - REAL(iday - day2)/REAL(day1 - day2) &
203     * (so4(i, k, im2) - so4(i, k, im))
204     IF (sulfate(i, k) < 0.) THEN
205     IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
206     IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
207     write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
208     so4(i, k, im2) - so4(i, k, im)
209     IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
210     stop 1
211 guez 69 endif
212     ENDDO
213     ENDDO
214     ENDIF
215    
216 guez 191 DO k = 1, klev
217     DO i = 1, klon
218     so4_out(i, k) = sulfate(i, k)
219 guez 69 ENDDO
220     ENDDO
221 guez 191 ELSE
222     ! If no new day, use old data:
223     DO k = 1, klev
224     DO i = 1, klon
225     sulfate(i, k) = so4_out(i, k)
226 guez 69 ENDDO
227     ENDDO
228 guez 191 ENDIF test_newday
229 guez 69
230     END SUBROUTINE readsulfate
231    
232     end module readsulfate_m

  ViewVC Help
Powered by ViewVC 1.1.21