/[lmdze]/trunk/libf/phylmd/readsulfate_preind.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/readsulfate_preind.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 68 - (show annotations)
Wed Nov 14 16:59:30 2012 UTC (11 years, 6 months ago) by guez
File size: 5932 byte(s)
Split "flincom.f90" into "flinclo.f90", "flinfindcood.f90",
"flininfo.f90" and "flinopen_nozoom.f90", in directory
"IOIPSL/Flincom".

Renamed "etat0_lim" to "ce0l", as in LMDZ.

Split "readsulfate.f" into "readsulfate.f90", "readsulfate_preind.f90"
and "getso4fromfile.f90".

In etat0, renamed variable q3d to q, as in "dynredem1". Replaced calls
to Flicom procedures by calls to NetCDF95.

In leapfrog, added call to writehist.

Extracted ASCII art from "grid_noro" into a file
"grid_noro.txt". Transformed explicit-shape local arrays into
automatic arrays, so that test on values of iim and jjm is no longer
needed. Test on weight:
          IF (weight(ii, jj) /= 0.) THEN
is useless. There is already a test before:
    if (any(weight == 0.)) stop "zero weight in grid_noro"

In "aeropt", replaced duplicated lines with different values of inu by
a loop on inu.

Removed arguments of "conf_phys". Corresponding variables are now
defined in "physiq", in a namelist. In "conf_phys", read a namelist
instead of using getin.

1 SUBROUTINE readsulfate_preind (r_day, first, pi_sulfate)
2
3 ! Read in /calculate pre-industrial values of sulfate
4
5 use dimens_m
6 use dimphy
7 use temps
8 use SUPHEC_M
9 use chem
10 IMPLICIT none
11
12 ! Content:
13 ! --------
14 ! This routine reads in monthly mean values of sulfate aerosols and
15 ! returns a linearly interpolated daily-mean field.
16 !
17 ! It does so for the preindustriel values of the sulfate, to a large part
18 ! analogous to the routine readsulfate.
19 !
20 ! Only Pb: Variables must be saved and don t have to be overwritten!
21 !
22 ! Author:
23 ! -------
24 ! Johannes Quaas (quaas@lmd.jussieu.fr)
25 ! 26/06/01
26 !
27 ! Input:
28 ! ------
29 double precision, intent(in):: r_day ! Day of integration
30 LOGICAL, intent(in):: first ! First timestep
31 ! (and therefore initialization necessary)
32 !
33 ! Output:
34 ! -------
35 double precision pi_sulfate (klon, klev) ! Number conc. sulfate (monthly mean data,
36 ! from file)
37 !
38 ! Local Variables:
39 ! ----------------
40 INTEGER i, ig, k, it
41 INTEGER j, iday, ny, iyr
42 parameter (ny=jjm+1)
43
44 INTEGER im, day1, day2, im2, ismaller
45 double precision pi_so4_1(iim, jjm+1, klev, 12)
46
47 double precision pi_so4(klon, klev, 12) ! SO4 in right dimension
48 SAVE pi_so4
49 double precision pi_so4_out(klon, klev)
50 SAVE pi_so4_out
51
52 CHARACTER*4 cyear
53 LOGICAL lnewday
54
55
56
57 iday = INT(r_day)
58
59 ! Get the year of the run
60 iyr = iday/360
61
62 ! Get the day of the actual year:
63 iday = iday-iyr*360
64
65 ! 0.02 is about 0.5/24, namly less than half an hour
66 lnewday = (r_day-FLOAT(iday).LT.0.02)
67
68 ! ---------------------------------------------
69 ! All has to be done only, if a new day begins!
70 ! ---------------------------------------------
71
72 IF (lnewday.OR.first) THEN
73 im = iday/30 +1 ! the actual month
74
75 ! annee_ref is the initial year (defined in temps.h)
76 iyr = iyr + annee_ref
77
78
79 IF (first) THEN
80 cyear='.nat'
81 CALL getso4fromfile(cyear,pi_so4_1)
82
83 ! Transform the horizontal 2D-field into the physics-field
84 ! (Also the levels and the latitudes have to be inversed)
85
86 ! Initialize field
87 DO it=1,12
88 DO k=1,klev
89 DO i=1,klon
90 pi_so4(i,k,it)=0.
91 ENDDO
92 ENDDO
93 ENDDO
94
95 write (*,*) 'preind: finished reading', FLOAT(iim)
96 DO it=1,12
97 DO k=1, klev
98 ! a) at the poles, use the zonal mean:
99 DO i=1,iim
100 ! North pole
101 pi_so4(1,k,it)=pi_so4(1,k,it)+pi_so4_1(i,jjm+1,klev+1-k,it)
102 ! South pole
103 pi_so4(klon,k,it)=pi_so4(klon,k,it)+pi_so4_1(i,1,klev+1-k,it)
104 ENDDO
105 pi_so4(1,k,it)=pi_so4(1,k,it)/FLOAT(iim)
106 pi_so4(klon,k,it)=pi_so4(klon,k,it)/FLOAT(iim)
107
108 ! b) the values between the poles:
109 ig=1
110 DO j=2,jjm
111 DO i=1,iim
112 ig=ig+1
113 if (ig.gt.klon) write (*,*) 'shit'
114 pi_so4(ig,k,it) = pi_so4_1(i,jjm+1-j,klev+1-k,it)
115 ENDDO
116 ENDDO
117 IF (ig.NE.klon-1) STOP 'Error in readsulfate (var conversion)'
118 ENDDO ! Loop over k (vertical)
119 ENDDO ! Loop over it (months)
120
121 ENDIF ! Had to read new data?
122
123
124 ! Interpolate to actual day:
125 IF (iday.LT.im*30-15) THEN
126 ! in the first half of the month use month before and actual month
127 im2=im-1
128 day1 = im2*30+15
129 day2 = im2*30-15
130 IF (im2.LE.0) THEN
131 ! the month is january, thus the month before december
132 im2=12
133 ENDIF
134 DO k=1,klev
135 DO i=1,klon
136 pi_sulfate(i,k) = pi_so4(i,k,im2) &
137 - FLOAT(iday-day2)/FLOAT(day1-day2) &
138 * (pi_so4(i,k,im2) - pi_so4(i,k,im))
139 IF (pi_sulfate(i,k).LT.0.) THEN
140 IF (iday-day2.LT.0.) write(*,*) 'iday-day2',iday-day2
141 IF (pi_so4(i,k,im2) - pi_so4(i,k,im).LT.0.) &
142 write(*,*) 'pi_so4(i,k,im2) - pi_so4(i,k,im)', &
143 pi_so4(i,k,im2) - pi_so4(i,k,im)
144 IF (day1-day2.LT.0.) write(*,*) 'day1-day2',day1-day2
145 stop 'pi_sulfate'
146 endif
147 ENDDO
148 ENDDO
149 ELSE
150 ! the second half of the month
151 im2=im+1
152 day1 = im*30+15
153 IF (im2.GT.12) THEN
154 ! the month is december, the following thus january
155 im2=1
156 ENDIF
157 day2 = im*30-15
158
159 DO k=1,klev
160 DO i=1,klon
161 pi_sulfate(i,k) = pi_so4(i,k,im2) &
162 - FLOAT(iday-day2)/FLOAT(day1-day2) &
163 * (pi_so4(i,k,im2) - pi_so4(i,k,im))
164 IF (pi_sulfate(i,k).LT.0.) THEN
165 IF (iday-day2.LT.0.) write(*,*) 'iday-day2',iday-day2
166 IF (pi_so4(i,k,im2) - pi_so4(i,k,im).LT.0.) &
167 write(*,*) 'pi_so4(i,k,im2) - pi_so4(i,k,im)', &
168 pi_so4(i,k,im2) - pi_so4(i,k,im)
169 IF (day1-day2.LT.0.) write(*,*) 'day1-day2',day1-day2
170 stop 'pi_sulfate'
171 endif
172 ENDDO
173 ENDDO
174 ENDIF
175
176
177 !JLD ! The sulfate concentration [molec cm-3] is read in.
178 !JLD ! Convert it into mass [ug SO4/m3]
179 !JLD ! masse_so4 in [g/mol], n_avogadro in [molec/mol]
180 DO k=1,klev
181 DO i=1,klon
182 !JLD pi_sulfate(i,k) = pi_sulfate(i,k)*masse_so4
183 !JLD . /n_avogadro*1.e+12
184 pi_so4_out(i,k) = pi_sulfate(i,k)
185 ENDDO
186 ENDDO
187
188 ELSE ! If no new day, use old data:
189 DO k=1,klev
190 DO i=1,klon
191 pi_sulfate(i,k) = pi_so4_out(i,k)
192 ENDDO
193 ENDDO
194 ENDIF ! Was this the beginning of a new day?
195
196 END SUBROUTINE readsulfate_preind

  ViewVC Help
Powered by ViewVC 1.1.21