source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/read_newemissions.f90 @ 5110

Last change on this file since 5110 was 5110, checked in by abarral, 2 months ago

Rename modules properly (mod_* -> lmdz_*) in phy_common

File size: 13.5 KB
Line 
1! Routine to read the emissions of the different species
2!
3SUBROUTINE read_newemissions(julien, jH_emi, edgar, flag_dms, &
4        debutphy, &
5        pdtphys, lafinphy, nbjour, pctsrf, &
6        t_seri, xlat, xlon, &
7        pmflxr, pmflxs, prfl, psfl, &
8        u10m_ec, v10m_ec, dust_ec, &
9        lmt_sea_salt, lmt_so2ff_l, &
10        lmt_so2ff_h, lmt_so2nff, lmt_so2ba, &
11        lmt_so2bb_l, lmt_so2bb_h, &
12        lmt_so2volc_cont, lmt_altvolc_cont, &
13        lmt_so2volc_expl, lmt_altvolc_expl, &
14        lmt_dmsbio, lmt_h2sbio, lmt_dmsconc, &
15        lmt_bcff, lmt_bcnff, lmt_bcbb_l, &
16        lmt_bcbb_h, lmt_bcba, lmt_omff, &
17        lmt_omnff, lmt_ombb_l, lmt_ombb_h, &
18        lmt_omnat, lmt_omba)
19
20  USE dimphy
21  USE indice_sol_mod
22  USE lmdz_grid_phy
23  USE lmdz_phys_para
24
25  IMPLICIT NONE
26
27  INCLUDE "dimensions.h"
28  INCLUDE 'paramet.h'
29  INCLUDE 'chem.h'
30  INCLUDE 'chem_spla.h'
31
32  logical :: debutphy, lafinphy, edgar
33  INTEGER :: test_vent, test_day, step_vent, flag_dms, nbjour
34  INTEGER :: julien, i, iday
35  SAVE step_vent, test_vent, test_day, iday
36  !$OMP THREADPRIVATE(step_vent, test_vent, test_day, iday)
37  REAL :: pct_ocean(klon), pctsrf(klon, nbsrf)
38  REAL :: pdtphys  ! pas d'integration pour la physique (seconde)
39  REAL :: t_seri(klon, klev)  ! temperature
40
41  REAL :: xlat(klon)       ! latitudes pour chaque point
42  REAL :: xlon(klon)       ! longitudes pour chaque point
43
44  !
45  !   Emissions:
46  !   ---------
47  !
48  !---------------------------- SEA SALT & DUST emissions ------------------------
49  REAL :: lmt_sea_salt(klon, ss_bins) !Sea salt 0.03-8.0 um !NOT SAVED OK
50  REAL :: clyfac, avgdryrate, drying
51  ! je      REAL u10m_ec1(klon), v10m_ec1(klon), dust_ec1(klon)
52  ! je      REAL u10m_ec2(klon), v10m_ec2(klon), dust_ec2(klon)
53
54  REAL, SAVE, ALLOCATABLE :: u10m_ec1(:), v10m_ec1(:), dust_ec1(:)
55  REAL, SAVE, ALLOCATABLE :: u10m_ec2(:), v10m_ec2(:), dust_ec2(:)
56  !$OMP THREADPRIVATE(u10m_ec1, v10m_ec1, dust_ec1)
57  !$OMP THREADPRIVATE(u10m_ec2, v10m_ec2, dust_ec2)
58  ! as      REAL u10m_nc(iip1,jjp1), v10m_nc(iip1,jjp1)
59  REAL :: u10m_ec(klon), v10m_ec(klon), dust_ec(klon)
60  !      REAL cly(klon), wth(klon), zprecipinsoil(klon)
61  REAL, SAVE, ALLOCATABLE :: cly(:), wth(:), zprecipinsoil(:)
62  REAL :: cly_glo(klon_glo), wth_glo(klon_glo)
63  REAL :: zprecipinsoil_glo(klon_glo)
64  !$OMP THREADPRIVATE(cly,wth,zprecipinsoil)
65
66
67  ! je     SAVE u10m_ec2, v10m_ec2, dust_ec2
68  ! je      SAVE u10m_ec1, v10m_ec1, dust_ec1   ! Added on titane
69  ! je      SAVE cly, wth, zprecipinsoil        ! Added on titane
70  ! SAVE cly, wth, zprecipinsoil, u10m_ec2, v10m_ec2, dust_ec2
71  !------------------------- BLACK CARBON emissions ----------------------
72  REAL :: lmt_bcff(klon)       ! emissions de BC fossil fuels
73  REAL :: lmt_bcnff(klon)      ! emissions de BC non-fossil fuels
74  REAL :: lmt_bcbb_l(klon)     ! emissions de BC biomass basses
75  REAL :: lmt_bcbb_h(klon)     ! emissions de BC biomass hautes
76  REAL :: lmt_bcba(klon)       ! emissions de BC bateau
77  !------------------------ ORGANIC MATTER emissions ---------------------
78  REAL :: lmt_omff(klon)     ! emissions de OM fossil fuels
79  REAL :: lmt_omnff(klon)    ! emissions de OM non-fossil fuels
80  REAL :: lmt_ombb_l(klon)   ! emissions de OM biomass basses
81  REAL :: lmt_ombb_h(klon)   ! emissions de OM biomass hautes
82  REAL :: lmt_omnat(klon)    ! emissions de OM Natural
83  REAL :: lmt_omba(klon)     ! emissions de OM bateau
84  !------------------------- SULFUR emissions ----------------------------
85  REAL :: lmt_so2ff_l(klon)       ! emissions so2 fossil fuels (low)
86  REAL :: lmt_so2ff_h(klon)       ! emissions so2 fossil fuels (high)
87  REAL :: lmt_so2nff(klon)        ! emissions so2 non-fossil fuels
88  REAL :: lmt_so2bb_l(klon)       ! emissions de so2 biomass burning basse
89  REAL :: lmt_so2bb_h(klon)       ! emissions de so2 biomass burning hautes
90  REAL :: lmt_so2ba(klon)         ! emissions de so2 bateau
91  REAL :: lmt_so2volc_cont(klon)  ! emissions so2 volcan continuous
92  REAL :: lmt_altvolc_cont(klon)  ! altitude  so2 volcan continuous
93  REAL :: lmt_so2volc_expl(klon)  ! emissions so2 volcan explosive
94  REAL :: lmt_altvolc_expl(klon)  ! altitude  so2 volcan explosive
95  REAL :: lmt_dmsconc(klon)       ! concentration de dms oceanique
96  REAL :: lmt_dmsbio(klon)        ! emissions de dms bio
97  REAL :: lmt_h2sbio(klon)        ! emissions de h2s bio
98
99  REAL, SAVE, ALLOCATABLE :: lmt_dms(:)           ! emissions de dms
100  !$OMP THREADPRIVATE(lmt_dms)
101  !
102  !  Lessivage
103  !  ---------
104  !
105  REAL :: pmflxr(klon, klev + 1), pmflxs(klon, klev + 1) !--convection
106  REAL :: prfl(klon, klev + 1), psfl(klon, klev + 1)   !--large-scale
107  ! REAL pmflxr(klon,klev), pmflxs(klon,klev) !--convection
108  ! REAL prfl(klon,klev),   psfl(klon,klev)   !--large-scale
109  !
110  !  Variable interne
111  !  ----------------
112  !
113  INTEGER :: icount
114  REAL :: tau_1, tau_2
115  REAL :: max_flux, min_flux
116  INTRINSIC MIN, MAX
117  !
118  ! JE: Changes due to new pdtphys in new physics.
119  !  REAL windintime ! time in hours of the wind input files resolution
120  !  REAL dayemintime ! time in hours of the other emissions input files resolution
121  REAL :: jH_init ! shift in the hour (count as days) respecto to
122  ! ! realhour = (pdtphys*i)/3600/24 -days_elapsed
123  REAL :: jH_emi, jH_vent, jH_day
124  SAVE jH_init, jH_vent, jH_day
125  !$OMP THREADPRIVATE(jH_init,jH_vent,jH_day)
126  REAL, PARAMETER :: vent_resol = 6. ! resolution of winds in hours
127  REAL, PARAMETER :: day_resol = 24. ! resolution of daily emmis. in hours
128  ! INTEGER   test_day1
129  ! SAVE test_day1
130  ! REAL tau_1j,tau_2j
131  ! je
132  ! allocate if necessary
133  !
134
135  IF (.NOT. ALLOCATED(u10m_ec1)) ALLOCATE(u10m_ec1(klon))
136  IF (.NOT. ALLOCATED(v10m_ec1)) ALLOCATE(v10m_ec1(klon))
137  IF (.NOT. ALLOCATED(dust_ec1)) ALLOCATE(dust_ec1(klon))
138  IF (.NOT. ALLOCATED(u10m_ec2)) ALLOCATE(u10m_ec2(klon))
139  IF (.NOT. ALLOCATED(v10m_ec2)) ALLOCATE(v10m_ec2(klon))
140  IF (.NOT. ALLOCATED(dust_ec2)) ALLOCATE(dust_ec2(klon))
141  IF (.NOT. ALLOCATED(cly)) ALLOCATE(cly(klon))
142  IF (.NOT. ALLOCATED(wth)) ALLOCATE(wth(klon))
143  IF (.NOT. ALLOCATED(zprecipinsoil)) ALLOCATE(zprecipinsoil(klon))
144  IF (.NOT. ALLOCATED(lmt_dms)) ALLOCATE(lmt_dms(klon))
145  ! end je nov2013
146  !
147  !***********************************************************************
148  ! DUST EMISSIONS
149  !***********************************************************************
150  !
151  IF (debutphy) THEN
152    !---Fields are read only at the beginning of the period
153    !--reading wind and dust
154    iday = julien
155    step_vent = 1
156    test_vent = 0
157    test_day = 0
158    CALL read_vent(.TRUE., step_vent, nbjour, u10m_ec2, v10m_ec2)
159    print *, 'Read (debut) dust emissions: step_vent,julien,nbjour', &
160            step_vent, julien, nbjour
161    CALL read_dust(.TRUE., step_vent, nbjour, dust_ec2)
162    ! Threshold velocity map
163    !$OMP MASTER
164    IF (is_mpi_root .AND. is_omp_root) THEN
165      zprecipinsoil_glo(:) = 0.0
166      OPEN(51, file = 'wth.dat', status = 'unknown', form = 'formatted')
167      READ(51, '(G18.10)') (wth_glo(i), i = 1, klon_glo)
168      CLOSE(51)
169      ! Clay content
170      OPEN(52, file = 'cly.dat', status = 'unknown', form = 'formatted')
171      READ(52, '(G18.10)') (cly_glo(i), i = 1, klon_glo)
172      CLOSE(52)
173      OPEN(53, file = 'precipinsoil.dat', &
174              status = 'old', form = 'formatted', err = 999)
175      READ(53, '(G18.10)') (zprecipinsoil_glo(i), i = 1, klon_glo)
176      PRINT *, 'lecture precipinsoil.dat'
177      999   CONTINUE
178      CLOSE(53)
179    ENDIF
180    !$OMP END MASTER
181    !$OMP BARRIER
182    CALL scatter(wth_glo, wth)
183    CALL scatter(cly_glo, cly)
184    CALL scatter(zprecipinsoil_glo, zprecipinsoil)
185
186    !JE20140908<<        GOTO 1000
187    ! DO i=1, klon
188    !   zprecipinsoil(i)=0.0
189    ! ENDDO
190    ! 1000   CLOSE(53)
191    !JE20140908>>
192    jH_init = jH_emi
193    jH_vent = jH_emi
194    jH_day = jH_emi
195    ! test_day1=0
196    !JE end
197    !
198
199  ENDIF !--- debutphy
200
201  print *, 'READ_EMISSION: test_vent & test_day = ', test_vent, &
202          test_day
203  IF (test_vent==0) THEN    !--on lit toutes les 6 h
204    CALL SCOPY(klon, u10m_ec2, 1, u10m_ec1, 1)
205    CALL SCOPY(klon, v10m_ec2, 1, v10m_ec1, 1)
206    CALL SCOPY(klon, dust_ec2, 1, dust_ec1, 1)
207    step_vent = step_vent + 1
208    ! !PRINT *,'step_vent=', step_vent
209    CALL read_vent(.FALSE., step_vent, nbjour, u10m_ec2, v10m_ec2)
210    print *, 'Reading dust emissions: step_vent, julien, nbjour ', &
211            step_vent, julien, nbjour
212    ! !print *,'test_vent, julien = ',test_vent, julien
213    CALL read_dust(.FALSE., step_vent, nbjour, dust_ec2)
214
215  ENDIF !--test_vent
216
217  ! ubicacion original
218  !  test_vent=test_vent+1
219  !  IF (test_vent.EQ.(6*2)) test_vent=0 !on remet a zero ttes les 6 h
220
221  !JE      tau_2=FLOAT(test_vent)/12.
222  !JE      tau_1=1.-tau_2
223  tau_2 = (jH_vent - jH_init) * 24. / (vent_resol)
224  tau_1 = 1. - tau_2
225  ! PRINT*,'JEdec jHv,JHi,ventres',jH_vent,jH_init,vent_resol
226  ! PRINT*,'JEdec tau2,tau1',tau_2,tau_1
227  ! PRINT*,'JEdec step_vent',step_vent
228  DO i = 1, klon
229    ! PRINT*,'JE tau_2,tau_2j',tau_2,tau_2j
230    u10m_ec(i) = tau_1 * u10m_ec1(i) + tau_2 * u10m_ec2(i)
231    v10m_ec(i) = tau_1 * v10m_ec1(i) + tau_2 * v10m_ec2(i)
232    dust_ec(i) = tau_1 * dust_ec1(i) + tau_2 * dust_ec2(i)
233  ENDDO
234  !
235  !JE      IF (test_vent.EQ.(6*2)) THEN
236  !JE        PRINT *,'6 hrs interval reached'
237  !JE        print *,'day in read_emission, test_vent = ',julien, test_vent
238  !JE      ENDIF
239  !JE
240  !JE      test_vent=test_vent+1
241  !JE      IF (test_vent.EQ.(6*2)) test_vent=0 !on remet a zero ttes les 6 h
242  ! JE
243  jH_vent = jH_vent + pdtphys / (24. * 3600.)
244  test_vent = test_vent + 1
245  IF (jH_vent>(vent_resol) / 24.) THEN
246    test_vent = 0
247    jH_vent = jH_init
248  ENDIF
249  ! PRINT*,'JE test_vent,test_vent1,jH_vent ', test_vent,test_vent1
250  ! .     ,jH_vent
251  ! endJEi
252  !
253  avgdryrate = 300. / 365. * pdtphys / 86400.
254  !
255  DO i = 1, klon
256    !
257    IF (cly(i)<9990..AND.wth(i)<9990.) THEN
258      zprecipinsoil(i) = zprecipinsoil(i) + &
259              (pmflxr(i, 1) + pmflxs(i, 1) + prfl(i, 1) + psfl(i, 1)) * pdtphys
260      !
261      clyfac = MIN(16., cly(i) * 0.4 + 8.) ![mm] max amount of water hold in top soil
262      drying = avgdryrate * exp(0.03905491 * &
263              exp(0.17446 * (t_seri(i, 1) - 273.15))) ! [mm]
264      zprecipinsoil(i) = min(max(0., zprecipinsoil(i) - drying), clyfac) ! [mm]
265    ENDIF
266    ! zprecipinsoil(i)=0.0 ! Temporarely introduced to reproduce obelix result
267  ENDDO
268
269  ! print *,'cly = ',sum(cly),maxval(cly),minval(cly)
270  ! print *,'wth = ',sum(wth),maxval(wth),minval(wth)
271  ! print *,'t_seri = ',sum(t_seri),maxval(t_seri),minval(t_seri)
272  ! print *,'precipinsoil = ',sum(zprecipinsoil),maxval(zprecipinsoil)
273  ! .                      ,minval(zprecipinsoil)
274  icount = 0
275  DO i = 1, klon
276    IF (cly(i)>=9990..OR.wth(i)>=9990..OR. &
277            t_seri(i, 1)<=273.15.OR.zprecipinsoil(i)>1.e-8) THEN
278      dust_ec(i) = 0.0 ! commented out for test dustemtest
279      ! print *,'Dust emissions surpressed at grid = ',i
280      ! icount=icount+1
281    ENDIF
282  ENDDO
283  !
284  print *, 'Total N of grids with surpressed emission = ', icount
285  print *, 'dust_ec = ', SUM(dust_ec), MINVAL(dust_ec), &
286          MAXVAL(dust_ec)
287  !nhl Transitory scaling of desert dust emissions
288
289  !nhl      DO i=1, klon
290  !nhl         dust_ec(i)=dust_ec(i)/2.
291  !nhl      ENDDO
292
293  !-saving precipitation field to be read in next simulation
294
295  IF (lafinphy) THEN
296    !
297    CALL gather(zprecipinsoil, zprecipinsoil_glo)
298    !$OMP MASTER
299    IF (is_mpi_root .AND. is_omp_root) THEN
300
301      OPEN(53, file = 'newprecipinsoil.dat', &
302              status = 'unknown', form = 'formatted')
303      WRITE(53, '(G18.10)') (zprecipinsoil_glo(i), i = 1, klon_glo)
304      CLOSE(53)
305    ENDIF
306    !$OMP END MASTER
307    !$OMP BARRIER
308    !
309  ENDIF
310  !
311  !***********************************************************************
312  ! SEA SALT EMISSIONS
313  !***********************************************************************
314  !
315  DO i = 1, klon
316    pct_ocean(i) = pctsrf(i, is_oce)
317  ENDDO
318
319  print *, 'IS_OCE = ', is_oce
320  CALL seasalt(v10m_ec, u10m_ec, pct_ocean, lmt_sea_salt) !mgSeaSalt/cm2/s
321  ! print *,'SUM, MAX & MIN Sea Salt = ',SUM(lmt_sea_salt),
322  ! .               MAXVAL(lmt_sea_salt),MINVAL(lmt_sea_salt)
323  !
324  !***********************************************************************
325  ! SULFUR & CARBON EMISSIONS
326  !***********************************************************************
327  !
328
329  IF (test_day==0) THEN
330    print *, 'Computing SULFATE emissions for day : ', iday, julien, &
331            step_vent
332    CALL condsurfs_new(iday, edgar, flag_dms, &
333            lmt_so2ff_l, lmt_so2ff_h, lmt_so2nff, &
334            lmt_so2bb_l, lmt_so2bb_h, lmt_so2ba, &
335            lmt_so2volc_cont, lmt_altvolc_cont, &
336            lmt_so2volc_expl, lmt_altvolc_expl, &
337            lmt_dmsbio, lmt_h2sbio, lmt_dms, lmt_dmsconc)
338    print *, 'Computing CARBON emissions for day : ', iday, julien, &
339            step_vent
340    CALL condsurfc_new(iday, &
341            lmt_bcff, lmt_bcnff, lmt_bcbb_l, lmt_bcbb_h, &
342            lmt_bcba, lmt_omff, lmt_omnff, lmt_ombb_l, &
343            lmt_ombb_h, lmt_omnat, lmt_omba)
344    print *, 'IDAY = ', iday
345    iday = iday + 1
346    print *, 'BCBB_L emissions :', SUM(lmt_bcbb_l), MAXVAL(lmt_bcbb_l) &
347            , MINVAL(lmt_bcbb_l)
348    print *, 'BCBB_H emissions :', SUM(lmt_bcbb_h), MAXVAL(lmt_bcbb_h) &
349            , MINVAL(lmt_bcbb_h)
350  ENDIF
351
352  !JE      test_day=test_day+1
353  !JE      IF (test_day.EQ.(24*2.)) THEN
354  !JE        test_day=0 !on remet a zero ttes les 24 h
355  !JE        print *,'LAST TIME STEP OF DAY ',julien
356  !JE      ENDIF
357
358  jH_day = jH_day + pdtphys / (24. * 3600.)
359  test_day = test_day + 1
360  IF (jH_day>(day_resol) / 24.) THEN
361    print *, 'LAST TIME STEP OF DAY ', julien
362    test_day = 0
363    jH_day = jH_init
364  ENDIF
365  ! PRINT*,'test_day,test_day1',test_day,test_day1
366
367END SUBROUTINE read_newemissions
Note: See TracBrowser for help on using the repository browser.