source: LMDZ5/branches/LMDZ5_SPLA/libf/phylmd/read_newemissions.F @ 2916

Last change on this file since 2916 was 2175, checked in by jescribano, 10 years ago

SPLA code included for first time

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