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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 188 - (show annotations)
Tue Mar 22 16:31:39 2016 UTC (8 years, 2 months ago) by guez
File size: 8409 byte(s)
Removed argument ncum of cv30_unsat, arguments nloc, ncum, nd, na of cv30_yield.

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

  ViewVC Help
Powered by ViewVC 1.1.21