Changeset 3527


Ignore:
Timestamp:
May 30, 2019, 3:43:48 PM (5 years ago)
Author:
oboucher
Message:

Cleaning up StratAer? for trunk version

Location:
LMDZ6/trunk/libf/phylmd/StratAer
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/StratAer/micphy_tstep.F90

    r3526 r3527  
    9898      !NL - add nucleation box (if flag on)
    9999      IF (flag_nuc_rate_box) THEN
    100          IF (latitude_deg(ilon).LE.(nuclat_min) .OR. latitude_deg(ilon).GE.(nuclat_max) &
    101               .OR. pplay(ilon,ilev).GE.nucpres_max .AND. pplay(ilon,ilev) .LE. nucpres_min ) THEN
     100         IF (latitude_deg(ilon).LE.nuclat_min .OR. latitude_deg(ilon).GE.nuclat_max &
     101              .OR. pplay(ilon,ilev).GE.nucpres_max .AND. pplay(ilon,ilev).LE.nucpres_min) THEN
    102102            nucl_rate=0.0
    103103         ENDIF
  • LMDZ6/trunk/libf/phylmd/StratAer/nucleation_tstep_mod.F90

    r3526 r3527  
    112112
    113113SUBROUTINE binapara(pt,prh,rhoa_in,jnuc,x,ntot,rc)
    114 
    115114
    116115  !    Fortran 90 subroutine binapara
  • LMDZ6/trunk/libf/phylmd/StratAer/strataer_mod.F90

    r3526 r3527  
    109109    ALLOCATE(xlat_max_vol(nErupt),xlon_max_vol(nErupt))
    110110   
    111     year_emit_vol=0 ; mth_emit_vol=0 ; day_emit_vol=0
    112     m_aer_emiss_vol=0. ; altemiss_vol=0. ; sigma_alt_vol=0.
    113     xlon_min_vol=0. ; xlon_max_vol=0.
    114     xlat_min_vol=0. ; xlat_max_vol=0.
     111    IF (nErupt.GT.0) THEN
     112      year_emit_vol=0 ; mth_emit_vol=0 ; day_emit_vol=0
     113      m_aer_emiss_vol=0. ; altemiss_vol=0. ; sigma_alt_vol=0.
     114      xlon_min_vol=0. ; xlon_max_vol=0.
     115      xlat_min_vol=0. ; xlat_max_vol=0.
     116    ENDIF
    115117   
    116118    CALL getin_p('year_emit_vol',year_emit_vol)
     
    140142    CALL getin_p('nucpres_max',nucpres_max)
    141143
    142     WRITE(lunout,*) 'IN STRATAER INIT2 year_emit_vol = ',year_emit_vol
    143     WRITE(lunout,*) 'IN STRATAER INIT2 mth_emit_vol = ',mth_emit_vol
    144     WRITE(lunout,*) 'IN STRATAER INIT2 day_emit_vol = ',day_emit_vol
    145    
    146144    !IF (is_master) THEN
    147        WRITE(lunout,*) 'IN STRATAER INIT2 year_emit_vol = ',year_emit_vol
    148        WRITE(lunout,*) 'IN STRATAER INIT2 mth_emit_vol=',mth_emit_vol
    149        WRITE(lunout,*) 'IN STRATAER INIT2 day_emit_vol=',day_emit_vol
    150        WRITE(lunout,*) 'IN STRATAER INIT2 =m_aer_emiss_vol',m_aer_emiss_vol
    151        WRITE(lunout,*) 'IN STRATAER INIT2 =altemiss_vol',altemiss_vol
    152        WRITE(lunout,*) 'IN STRATAER INIT2 =sigma_alt_vol',sigma_alt_vol
    153        WRITE(lunout,*) 'IN STRATAER INIT2 xlon_min_vol=',xlon_min_vol
    154        WRITE(lunout,*) 'IN STRATAER INIT2 xlon_max_vol=',xlon_max_vol
    155        WRITE(lunout,*) 'IN STRATAER INIT2 xlat_min_vol=',xlat_min_vol
    156        WRITE(lunout,*) 'IN STRATAER INIT2 xlat_max_vol=',xlat_max_vol
    157        WRITE(lunout,*) 'flag_nuc_rate_box = ',flag_nuc_rate_box
    158        WRITE(lunout,*) 'nuclat_min = ',nuclat_min
    159        WRITE(lunout,*) 'nuclat_max = ',nuclat_max
    160        WRITE(lunout,*) 'nucpres_min = ',nucpres_min
    161        WRITE(lunout,*) 'nucpres_max = ',nucpres_max
    162        WRITE(lunout,*) 'flag_sulf_emit = ',flag_sulf_emit
    163        WRITE(lunout,*) 'injdur = ',injdur
     145    WRITE(lunout,*) 'flag_sulf_emit = ',flag_sulf_emit
     146    IF (flag_sulf_emit == 1) THEN
     147       WRITE(lunout,*) 'IN STRATAER nErupt: ',nErupt
     148       WRITE(lunout,*) 'IN STRATAER injdur: ',injdur
     149       WRITE(lunout,*) 'IN STRATAER : year_emit_vol',year_emit_vol
     150       WRITE(lunout,*) 'IN STRATAER : mth_emit_vol',mth_emit_vol
     151       WRITE(lunout,*) 'IN STRATAER : day_emit_vol',day_emit_vol
     152       WRITE(lunout,*) 'IN STRATAER : m_aer_emiss_vol',m_aer_emiss_vol
     153       WRITE(lunout,*) 'IN STRATAER : altemiss_vol',altemiss_vol
     154       WRITE(lunout,*) 'IN STRATAER : sigma_alt_vol',sigma_alt_vol
     155       WRITE(lunout,*) 'IN STRATAER : ponde_lonlat_vol',ponde_lonlat_vol
     156       WRITE(lunout,*) 'IN STRATAER : xlat_min_vol',xlat_min_vol
     157       WRITE(lunout,*) 'IN STRATAER : xlat_max_vol',xlat_max_vol
     158       WRITE(lunout,*) 'IN STRATAER : xlon_min_vol',xlon_min_vol
     159       WRITE(lunout,*) 'IN STRATAER : xlon_max_vol',xlon_max_vol
     160    ELSEIF (flag_sulf_emit == 2) THEN
     161       WRITE(lunout,*) 'IN STRATAER : m_aer_emiss_sai',m_aer_emiss_sai
     162       WRITE(lunout,*) 'IN STRATAER : altemiss_sai',altemiss_sai
     163       WRITE(lunout,*) 'IN STRATAER : sigma_alt_sai',sigma_alt_sai
     164       WRITE(lunout,*) 'IN STRATAER : xlat_sai',xlat_sai
     165       WRITE(lunout,*) 'IN STRATAER : xlon_sai',xlon_sai
    164166       WRITE(lunout,*) 'flag_sulf_emit_distrib = ',flag_sulf_emit_distrib
    165        WRITE(lunout,*) 'nErupt = ',nErupt
    166        WRITE(lunout,*) 'year_emit_vol = ',year_emit_vol
    167        WRITE(lunout,*) 'mth_emit_vol = ',mth_emit_vol
    168        WRITE(lunout,*) 'day_emit_vol = ',day_emit_vol
    169        WRITE(lunout,*) 'm_aer_emiss_vol = ',m_aer_emiss_vol
    170        WRITE(lunout,*) 'altemiss_vol = ',altemiss_vol
    171        WRITE(lunout,*) 'sigma_alt_vol = ',sigma_alt_vol
    172        WRITE(lunout,*) 'xlat_min_vol = ',xlat_min_vol
    173        WRITE(lunout,*) 'xlat_max_vol = ',xlat_max_vol
    174        WRITE(lunout,*) 'xlon_min_vol = ',xlon_min_vol
    175        WRITE(lunout,*) 'xlon_max_vol = ',xlon_max_vol
    176        WRITE(lunout,*) 'm_aer_emiss_sai = ',m_aer_emiss_sai
    177        WRITE(lunout,*) 'altemiss_sai = ',altemiss_sai
    178        WRITE(lunout,*) 'sigma_alt_sai = ',sigma_alt_sai
    179        WRITE(lunout,*) 'xlat_sai = ',xlat_sai
    180        WRITE(lunout,*) 'xlon_sai = ',xlon_sai
    181        WRITE(lunout,*) 'xlat_min_sai = ',xlat_min_sai
    182        WRITE(lunout,*) 'xlat_max_sai = ',xlat_max_sai
     167    ELSEIF (flag_sulf_emit == 3) THEN
     168       WRITE(lunout,*) 'IN STRATAER : m_aer_emiss_sai',m_aer_emiss_sai
     169       WRITE(lunout,*) 'IN STRATAER : altemiss_sai',altemiss_sai
     170       WRITE(lunout,*) 'IN STRATAER : sigma_alt_sai',sigma_alt_sai
     171       WRITE(lunout,*) 'IN STRATAER : xlat_min_sai',xlat_min_sai
     172       WRITE(lunout,*) 'IN STRATAER : xlat_max_sai',xlat_max_sai
     173       WRITE(lunout,*) 'IN STRATAER : xlon_sai',xlon_sai
     174       WRITE(lunout,*) 'flag_sulf_emit_distrib = ',flag_sulf_emit_distrib
     175    ENDIF
     176    WRITE(lunout,*) 'IN STRATAER : flag_nuc_rate_box = ',flag_nuc_rate_box
     177    IF (flag_nuc_rate_box) THEN
     178       WRITE(lunout,*) 'IN STRATAER : nuclat_min = ',nuclat_min,', nuclat_max = ',nuclat_max
     179       WRITE(lunout,*) 'IN STRATAER : nucpres_min = ',nucpres_min,', nucpres_max = ',nucpres_max
     180    ENDIF
    183181    !ENDIF
    184182
  • LMDZ6/trunk/libf/phylmd/StratAer/traccoag_mod.F90

    r3526 r3527  
    5959!----------------
    6060    REAL                                   :: m_aer_emiss_vol_daily ! daily injection mass emission
    61     REAL                                   :: sum_emi_so2         ! Test sum of all LON for budg_emi_so2
    6261    INTEGER                                :: it, k, i, ilon, ilev, itime, i_int, ieru
    6362    LOGICAL,DIMENSION(klon,klev)           :: is_strato           ! true = above tropopause, false = below
     
    8483       WRITE(lunout,*) 'in traccoag: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
    8584       WRITE(lunout,*) 'IN traccoag flag_sulf_emit: ',flag_sulf_emit
    86        IF (flag_sulf_emit == 1) THEN
    87           WRITE(lunout,*) 'IN traccoag nErupt: ',nErupt
    88           WRITE(lunout,*) 'IN traccoag injdur: ',injdur
    89           WRITE(lunout,*) 'IN traccoag : year_emit_vol',year_emit_vol
    90           WRITE(lunout,*) 'IN traccoag : mth_emit_vol',mth_emit_vol
    91           WRITE(lunout,*) 'IN traccoag : day_emit_vol',day_emit_vol
    92           WRITE(lunout,*) 'IN traccoag : m_aer_emiss_vol',m_aer_emiss_vol
    93           WRITE(lunout,*) 'IN traccoag : altemiss_vol',altemiss_vol
    94           WRITE(lunout,*) 'IN traccoag : sigma_alt_vol',sigma_alt_vol
    95           WRITE(lunout,*) 'IN traccoag : ponde_lonlat_vol',ponde_lonlat_vol
    96           WRITE(lunout,*) 'IN traccoag : xlat_min_vol',xlat_min_vol
    97           WRITE(lunout,*) 'IN traccoag : xlat_max_vol',xlat_max_vol
    98           WRITE(lunout,*) 'IN traccoag : xlon_min_vol',xlon_min_vol
    99           WRITE(lunout,*) 'IN traccoag : xlon_max_vol',xlon_max_vol
    100        ELSEIF (flag_sulf_emit == 2) THEN
    101           WRITE(lunout,*) 'IN traccoag : m_aer_emiss_sai',m_aer_emiss_sai
    102           WRITE(lunout,*) 'IN traccoag : altemiss_sai',altemiss_sai
    103           WRITE(lunout,*) 'IN traccoag : sigma_alt_sai',sigma_alt_sai
    104           WRITE(lunout,*) 'IN traccoag : xlat_sai',xlat_sai
    105           WRITE(lunout,*) 'IN traccoag : xlon_sai',xlon_sai
    106        ELSEIF (flag_sulf_emit == 3) THEN
    107           WRITE(lunout,*) 'IN traccoag : m_aer_emiss_sai',m_aer_emiss_sai
    108           WRITE(lunout,*) 'IN traccoag : altemiss_sai',altemiss_sai
    109           WRITE(lunout,*) 'IN traccoag : sigma_alt_sai',sigma_alt_sai
    110           WRITE(lunout,*) 'IN traccoag : xlat_min_sai',xlat_min_sai
    111           WRITE(lunout,*) 'IN traccoag : xlat_max_sai',xlat_max_sai
    112           WRITE(lunout,*) 'IN traccoag : xlon_sai',xlon_sai
    113        ENDIF
    114        WRITE(lunout,*) 'IN traccoag : flag_nuc_rate_box = ',flag_nuc_rate_box
    115        IF (flag_nuc_rate_box) THEN
    116           WRITE(lunout,*) 'IN traccoag : nuclat_min = ',nuclat_min,', nuclat_max = ',nuclat_max
    117           WRITE(lunout,*) 'IN traccoag : nucpres_min = ',nucpres_min,', nucpres_max = ',nucpres_max
    118        ENDIF
    11985    ENDIF
    12086   
     
    190156      ! stretch emission over one day of Pinatubo eruption
    191157       DO ieru=1, nErupt
    192           IF (is_mpi_root) THEN
    193              sum_emi_so2 = 0.0 ! Init sum
    194           ENDIF
    195158          IF (year_cur==year_emit_vol(ieru).AND.mth_cur==mth_emit_vol(ieru).AND.&
    196159               day_cur>=day_emit_vol(ieru).AND.day_cur<(day_emit_vol(ieru)+injdur)) THEN
     
    259222                      budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
    260223                   ENDDO
    261                    sum_emi_so2 = sum_emi_so2 + budg_emi_so2(i) ! Sum all LON
    262224                ENDIF ! emission grid cell
    263225             ENDDO ! klon loop
    264              WRITE(lunout,*) "IN traccoag (ieru=",ieru,") global sum_emi_so2=",sum_emi_so2
    265226             WRITE(lunout,*) "IN traccoag (ieru=",ieru,") m_aer_emiss_vol_daily=",m_aer_emiss_vol_daily
    266227          ENDIF ! emission period
     
    323284          DO k=1, klev
    324285            ! stretch emission over whole year (360d)
    325             emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/year_len/86400. 
     286            emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/FLOAT(year_len)/86400. 
    326287            tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
    327288            budg_emi_so2(i)=budg_emi_so2(i)+emission*zdm(k)*mSatom/mSO2mol
     
    332293!          DO k=1, klev
    333294!            ! stretch emission over whole year (360d)
    334 !            emission=m_aer_emiss*(mH2SO4mol/mSatom)/m_part_dry(21)/m_air_gridbox(i,k)*f_lay_emiss(k)/year_len/86400
     295!            emission=m_aer_emiss*(mH2SO4mol/mSatom)/m_part_dry(21)/m_air_gridbox(i,k)*f_lay_emiss(k)/FLOAT(year_len)/86400.
    335296!            tr_seri(i,k,id_BIN01_strat+20)=tr_seri(i,k,id_BIN01_strat+20)+emission*pdtphys
    336297!            budg_emi_part(i)=budg_emi_part(i)+emission*zdm(k)*mSatom/mH2SO4mol
     
    346307!       SAI scenario with continuous emission
    347308        dlat_loc=180./RPI/2.*(boundslat(i,1)-boundslat(i,3)) ! dlat = half difference of boundary latitudes
    348         WRITE(lunout,*) 'IN traccoag, dlat = ',dlat_loc
    349309        theta_min = max(xlat(i)-dlat_loc,xlat_min_sai)
    350310        theta_max = min(xlat(i)+dlat_loc,xlat_max_sai)
     
    397357            ! stretch emission over whole year (360d)
    398358            emission=m_aer_emiss_sai*(mSO2mol/mSatom)/m_air_gridbox(i,k)*f_lay_emiss(k)/ &
    399                       & year_len/86400.*(sin(theta_max/180.*RPI)-sin(theta_min/180.*RPI))/ &
     359                      & FLOAT(year_len)/86400.*(sin(theta_max/180.*RPI)-sin(theta_min/180.*RPI))/ &
    400360                      & (sin(xlat_max_sai/180.*RPI)-sin(xlat_min_sai/180.*RPI))
    401361            tr_seri(i,k,id_SO2_strat)=tr_seri(i,k,id_SO2_strat)+emission*pdtphys
Note: See TracChangeset for help on using the changeset viewer.