Ignore:
Timestamp:
May 22, 2024, 3:16:36 PM (6 weeks ago)
Author:
lebasn
Message:

StratAer?: New model version (microphysic, composition routine, code cleaning, new params...)

File:
1 edited

Legend:

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

    r4767 r4950  
    5151 
    5252  !============= NUCLEATION VARS =============
     53  ! MOLECULAR ACCOMODATION OF H2SO4 (Raes and Van Dingen)
     54  REAL,SAVE    :: ALPH2SO4               ! H2SO4 accommodation  coefficient [condensation/evaporation]
     55  !$OMP THREADPRIVATE(ALPH2SO4)
     56 
    5357  ! flag to constraint nucleation rate in a lat/pres box
    5458  LOGICAL,SAVE :: flag_nuc_rate_box      ! Nucleation rate limit or not to a lat/pres
     
    6468  INTEGER,SAVE :: flh2o  ! ds stratemit : flh2o =0 (tr_seri), flh2o=1 (dq)
    6569  !$OMP THREADPRIVATE(flh2o)
    66 !  REAL,ALLOCATABLE,SAVE    :: d_q_emiss(:,:)
    67 !  !$OMP THREADPRIVATE(d_q_emiss)
    6870 
    6971  REAL,ALLOCATABLE,SAVE    :: budg_emi(:,:)            !DIMENSION(klon,n)
     
    144146  !$OMP THREADPRIVATE(day_emit_roc)
    145147 
     148  REAL,ALLOCATABLE,SAVE    :: RRSI(:) ! radius [cm] for each aerosol size
     149  REAL,ALLOCATABLE,SAVE    :: Vbin(:) ! volume [m3] for each aerosol size 
     150  !$OMP THREADPRIVATE(RRSI, Vbin)
    146151  REAL,SAVE    :: dlat, dlon             ! delta latitude and d longitude of grid in degree
    147152  !$OMP THREADPRIVATE(dlat, dlon)
     
    153158    USE print_control_mod, ONLY : lunout
    154159    USE mod_phys_lmdz_para, ONLY : is_master
    155     USE infotrac_phy, ONLY: id_OCS_strat,id_SO2_strat,id_H2SO4_strat,nbtr_sulgas
     160    USE infotrac_phy, ONLY: id_OCS_strat,id_SO2_strat,id_H2SO4_strat,nbtr_sulgas,nbtr_bin
     161    USE phys_local_var_mod, ONLY : mdw
     162    USE aerophys, ONLY: mdwmin, V_rat
     163    USE YOMCST  , ONLY : RPI
     164   
     165    INTEGER :: it
    156166   
    157167    WRITE(lunout,*) 'IN STRATAER_LOCAL_VAR INIT WELCOME!'
     
    185195   
    186196    ! nuc init
     197    ALPH2SO4 = 0.1
    187198    flag_nuc_rate_box = .FALSE.
    188199    nuclat_min=0  ; nuclat_max=0
     
    238249    ENDIF ! if master
    239250   
     251    !--initialising dry diameters to geometrically spaced mass/volume (see Jacobson 1994)
     252    mdw(1)=mdwmin
     253    IF (V_rat.LT.1.62) THEN ! compensate for dip in second bin for lower volume ratio
     254       mdw(2)=mdw(1)*2.**(1./3.)
     255       DO it=3, nbtr_bin
     256          mdw(it)=mdw(it-1)*V_rat**(1./3.)
     257       ENDDO
     258    ELSE
     259       DO it=2, nbtr_bin
     260          mdw(it)=mdw(it-1)*V_rat**(1./3.)
     261       ENDDO
     262    ENDIF
     263    IF (is_master) WRITE(lunout,*) 'init mdw=', mdw
     264   
     265    !   compute particle radius RRSI [cm] and volume Vbin [m3] from diameter mdw [m]
     266    ALLOCATE(RRSI(nbtr_bin), Vbin(nbtr_bin))
     267   
     268    DO it=1,nbtr_bin
     269       !     [cm]
     270       RRSI(it)=mdw(it)/2.*100.
     271       !     [m3]
     272       Vbin(it)=4.0*RPI*((mdw(it)/2.)**3)/3.0
     273    ENDDO
     274   
     275    IF (is_master) THEN
     276       WRITE(lunout,*) 'init RRSI=', RRSI
     277       WRITE(lunout,*) 'init Vbin=', Vbin
     278    ENDIF
     279   
    240280    WRITE(lunout,*) 'IN STRATAER INIT END'
    241281   
Note: See TracChangeset for help on using the changeset viewer.