Ignore:
Timestamp:
Jun 17, 2015, 8:06:14 PM (9 years ago)
Author:
jescribano
Message:

Bugs corrections, control vector is now fine mode+coarse mode and seasalt coarse+fine, change in emission scheme parameters, more outputs at 10h30 and 13h30 LT. (Pending correct optical and sedimentation parameters)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/LMDZ5_SPLA/libf/phylmd/dustemission_mod.F90

    r2217 r2303  
    3838!  real   , parameter :: cd=1.*roa/gravity
    3939! new values
    40 !  logical, parameter :: ok_splatunning=.true.
     40!  logical, parameter :: ok_splatuning=.true.
    4141! Div=3 from S. Alfaro (Sow et al ACPD 2011)
    4242!JE 20150206
    43   integer, parameter :: div1=3.
    44   integer, parameter :: div2=3.
    45   integer, parameter :: div3=3.
     43!  integer, parameter :: div1=3.
     44!  integer, parameter :: div2=3.
     45!  integer, parameter :: div3=3.
     46  integer, parameter :: div1=6.
     47  integer, parameter :: div2=6.
     48  integer, parameter :: div3=6.
    4649  real   , parameter :: e1=3.61/div1
    4750  real   , parameter :: e2=3.52/div2
     
    161164  USE mod_grid_phy_lmdz
    162165  USE mod_phys_lmdz_para
     166  USE indice_sol_mod
    163167
    164168  IMPLICIT NONE
     
    169173  REAL,DIMENSION(klon),     INTENT(IN)     :: xlat
    170174  REAL,DIMENSION(klon),     INTENT(IN)     :: xlon
    171   REAL,DIMENSION(klon),    INTENT(IN)     :: pctsrf
     175  REAL,DIMENSION(klon,nbsrf), INTENT(IN)     :: pctsrf
    172176  REAL,DIMENSION(klon),INTENT(IN)          :: zu10m   ! 10m zonal wind
    173177  REAL,DIMENSION(klon),INTENT(IN)          :: zv10m   ! meridional 10m wind
     
    218222  ENDIF
    219223
    220   CALL adaptdustemission(debutphy,emisbinloc,emdustacc,emdustcoa,emdustsco)
     224  !CALL adaptdustemission(debutphy,emisbinloc,emdustacc,emdustcoa,emdustsco)
     225  CALL adaptdustemission(debutphy,emisbinloc,emdustacc,emdustcoa,emdustsco,maskdust,pctsrf)
    221226  ! output in kg/m2/s
    222227
     
    258263
    259264 SUBROUTINE adaptdustemission(debutphy,emisbinlocal, &
    260                                emdustacc,emdustcoa,emdustsco)
     265                emdustacc,emdustcoa,emdustsco,maskdust,pctsrf)
     266!                               emdustacc,emdustcoa,emdustsco)
    261267
    262268  USE dimphy
     
    265271  USE mod_grid_phy_lmdz
    266272  USE mod_phys_lmdz_para
     273  USE indice_sol_mod
    267274
    268275  IMPLICIT NONE
     
    276283  INTEGER,SAVE ::iminacclow,iminacchigh,imincoalow
    277284  INTEGER,SAVE ::imincoahigh,iminscohigh,iminscolow
     285  INTEGER,DIMENSION(klon) :: maskdust ! where the emissions were calculated
     286  REAL,DIMENSION(klon,nbsrf),     INTENT(IN)     :: pctsrf
    278287!  real,parameter :: sizeacclow=0.03
    279288!  real,parameter :: sizeacchigh=0.5
     
    286295  real,parameter :: sizescolow=6.
    287296  real,parameter :: sizescohigh=30.  ! in micrometers
    288 
    289   real,parameter :: tunningfactor=4.5  ! factor for fine bins!!! important!!
     297!--------------------------------
     298  real,parameter :: tuningfactorfine=1.0  ! factor for fine bins!!! important!!
     299!  real,parameter :: tuningfactorfine=4.5  ! factor for fine bins!!! important!!
     300  real,parameter :: tuningfactorcoa=4.0  ! factor for coarse bins!!! important!!
     301!  real,parameter :: tuningfactorcoa=4.5  ! factor for coarse bins!!! important!!
     302  real,parameter :: tuningfactorsco=4.0  ! factor for supercoarse bins!!! important!!
     303!  real,parameter :: tuningfactorsco=4.5  ! factor for supercoarse bins!!! important!!
     304  real,parameter :: basesumemission= 0.0  !1.e-6  ! emissions to SUM to each land pixel FOR ASSIMILATION ONLY important!!  in mg/m2/s, per bin
     305 !basesumemission = 1.e-6 increase the AOD in about 12%  (0.03 of AOD) ,
     306 !while 1e-8 increase in about 0.12%  (0.003 of AOD)
     307
     308  real,dimension(klon) :: basesumacc,basesumcoa,basesumsco
     309!--------------------------------
    290310!JE20140915  real,parameter :: sizeacclow=0.06
    291311!JE20140915  real,parameter :: sizeacchigh=1.0
     
    317337   call abort_gcm('adaptdustemission', 'Dust range problem',1)
    318338  endif
    319   print *,'ALL DUST BIN: tunning EMISSION factor= ',tunningfactor
     339  print *,'FINE DUST BIN: tuning EMISSION factor= ',tuningfactorfine
     340  print *,'COA DUST BIN: tuning EMISSION factor= ',tuningfactorcoa
     341  print *,'SCO DUST BIN: tuning EMISSION factor= ',tuningfactorsco
     342  print *,'ALL DUST BIN: SUM to the emissions (mg/m2/s) = ',basesumemission
    320343  auxr1=9999.
    321344  auxr2=9999.
     
    386409
    387410! estimate and integrate bins into only accumulation and coarse
     411do k=1,klon
     412  basesumacc(k)=basesumemission*(pctsrf(k,is_ter))*1.e-6 ! from mg/m2/s
     413  basesumcoa(k)=basesumemission*(pctsrf(k,is_ter))*1.e-6
     414  basesumsco(k)=basesumemission*(pctsrf(k,is_ter))*1.e-6
     415enddo
    388416
    389417
     
    395423   auxr1=auxr1+emisbinlocal(k,i)
    396424  enddo
    397   emdustacc(k)= auxr1*tunningfactor
     425  emdustacc(k)=(auxr1 + basesumacc(k))*tuningfactorfine
    398426  do i=imincoalow,imincoahigh-1
    399427    auxr2=auxr2+emisbinlocal(k,i)
    400428  enddo
    401   emdustcoa(k)=auxr2*tunningfactor
     429  emdustcoa(k)=(auxr2 + basesumcoa(k))*tuningfactorcoa
    402430  do i=iminscolow,iminscohigh-1
    403431    auxr3=auxr3+emisbinlocal(k,i)
    404432  enddo
    405   emdustsco(k)=auxr3*tunningfactor
     433  emdustsco(k)=(auxr3 + basesumsco(k))*tuningfactorsco
    406434enddo
     435
     436
     437!do k=1,klon
     438!auxr1=0.0
     439!auxr2=0.0
     440!auxr3=0.0
     441!  do i=iminacclow,iminacchigh-1
     442!   auxr1=auxr1+emisbinlocal(k,i)
     443!  enddo
     444!  emdustacc(k)= auxr1*tuningfactor
     445!  do i=imincoalow,imincoahigh-1
     446!    auxr2=auxr2+emisbinlocal(k,i)
     447!  enddo
     448!  emdustcoa(k)=auxr2*tuningfactor
     449!  do i=iminscolow,iminscohigh-1
     450!    auxr3=auxr3+emisbinlocal(k,i)
     451!  enddo
     452!  emdustsco(k)=auxr3*tuningfactor
     453!enddo
     454!
     455
     456
     457
    407458
    408459!JEdbg<<
     
    462513  USE mod_grid_phy_lmdz
    463514  USE mod_phys_lmdz_para
     515  USE indice_sol_mod
    464516
    465517  IMPLICIT NONE
     
    467519  REAL,DIMENSION(klon),     INTENT(IN)     :: xlat
    468520  REAL,DIMENSION(klon),     INTENT(IN)     :: xlon
    469   REAL,DIMENSION(klon),     INTENT(IN)     :: pctsrf
     521  ! JE20150605<< better to read
     522  ! REAL,DIMENSION(klon),     INTENT(IN)     :: pctsrf
     523  REAL,DIMENSION(klon,nbsrf),     INTENT(IN)     :: pctsrf
     524  ! JE20150605>>
    470525
    471526  !Local
     
    613668      !&      xlat(i).ge.latmin.and.xlat(i).le.latmax    &
    614669      !&      .and.pctsrf(i)>0.5.and.Pini(i,nts)>0.)THEN
    615       IF(pctsrf(i)>0.5.and.Pini(i,nts)>0.)THEN
    616          
     670  ! JE20150605<< easier to read
     671  !    IF(pctsrf(i)>0.5.and.Pini(i,nts)>0.)THEN
     672      IF(pctsrf(i,is_ter)>0.5.and.Pini(i,nts)>0.)THEN
     673  ! JE20150605>>
    617674           sol(i,nts) = solini(i,nts)
    618675             P(i,nts) = Pini(i,nts)
Note: See TracChangeset for help on using the changeset viewer.