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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 129 - (hide annotations)
Fri Feb 13 18:22:38 2015 UTC (9 years, 3 months ago) by guez
Original Path: trunk/phylmd/readsulfate_preind.f
File size: 6375 byte(s)
Removed arguments day0, anne0 of procedures initdynav and
inithist. Use directly day_ref, annee_ref instead.

Moved variables annee_ref, day_ref of module temps to module
dynetat0_m. Deleted variables dayref and anneeref of module conf_gcm_m
and removed them from namelist conf_gcm_nml. These variables were
troubling intermediary on the way to annee_ref and day_ref. Gave as
default values to annee_ref and day_ref the default values of dayref
and anneeref. Moved the test on raz_date from main unit gcm to
procedure dynetat0. Created namelist dynetat0_nml. Read annee_ref and
day_ref from standard input in dynetat0 and redefine them from
"start.nc" if not raz_date. Rationale: 1 - Choose the best programming
from the point of view of program gcm only, forgetting program ce0l. 2
- The normal case is to define annee_ref and day_ref from "start.nc"
so put them in module dynetat0_m rather than in conf_gcm_m. 3 - Try to
always read the same namelists in the same order regardless of choices
in previous namelists. Downsides: 1 -We now need the file "dynetat0.f"
for the program ce0l, because dynetat0_m is used by dynredem0. 2 - We
need to define annee_ref and day_ref from procedure etat0.

Removed useless variable day_end of module temps.

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

  ViewVC Help
Powered by ViewVC 1.1.21