source: LMDZ6/trunk/libf/phylmd/Dust/read_newemissions.f90 @ 5301

Last change on this file since 5301 was 5292, checked in by abarral, 4 days ago

Move academic.h chem.h chem_spla.h to module

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