Ignore:
Timestamp:
Jul 18, 2018, 4:48:34 PM (6 years ago)
Author:
mvals
Message:

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/updatereffrad_mod.F

    r1969 r1974  
    66     
    77      SUBROUTINE updatereffrad(ngrid,nlayer,
    8      &                rdust,rice,nuice,
     8     &                rdust,rstormdust,rice,nuice,
    99     &                reffrad,nueffrad,
    1010     &                pq,tauscaling,tau,pplay)
     
    1414     &                       igcm_h2o_ice, igcm_ccn_mass, radius,
    1515     &                       igcm_ccn_number, nuice_ref, varian,
    16      &                       ref_r0, igcm_dust_submicron
     16     &                       ref_r0, igcm_dust_submicron,
     17     &                       igcm_stormdust_mass,igcm_stormdust_number
    1718       USE dimradmars_mod, only: nueffdust,naerkind,
    1819     &            name_iaer,
    1920     &            iaer_dust_conrath,iaer_dust_doubleq,
    20      &            iaer_dust_submicron,iaer_h2o_ice
     21     &            iaer_dust_submicron,iaer_h2o_ice,
     22     &            iaer_stormdust_doubleq
    2123
    2224       IMPLICIT NONE
     
    4547
    4648c-----------------------------------------------------------------------
    47 c     Inputs:
     49c     Inputs/outputs:
    4850c     ------
    4951
    50       INTEGER ngrid,nlayer
     52      INTEGER, INTENT(in) :: ngrid,nlayer
    5153c     Ice geometric mean radius (m)
    52       REAL :: rice(ngrid,nlayer)
     54      REAL, INTENT(out) :: rice(ngrid,nlayer)
    5355c     Estimated effective variance of the size distribution (n.u.)
    54       REAL :: nuice(ngrid,nlayer)
     56      REAL, INTENT(out) :: nuice(ngrid,nlayer)
    5557c     Tracer mass mixing ratio (kg/kg)
    56       REAL pq(ngrid,nlayer,nqmx)
    57       REAL rdust(ngrid,nlayer) ! Dust geometric mean radius (m)
    58      
    59       REAL pplay(ngrid,nlayer) ! altitude at the middle of the layers
    60       REAL tau(ngrid,naerkind)
    61 
    62 
    63 c     Outputs:
    64 c     -------
    65 
     58      REAL, INTENT(in) :: pq(ngrid,nlayer,nqmx)
     59      REAL, INTENT(out) :: rdust(ngrid,nlayer) ! Dust geometric mean radius (m)
     60      REAL, INTENT(out) :: rstormdust(ngrid,nlayer) ! Dust geometric mean radius (m)
     61      REAL, INTENT(in) :: pplay(ngrid,nlayer) ! altitude at the middle of the layers
     62      REAL, INTENT(in) :: tau(ngrid,naerkind)
    6663c     Aerosol effective radius used for radiative transfer (meter)
    67       REAL :: reffrad(ngrid,nlayer,naerkind)
     64      REAL, INTENT(out) :: reffrad(ngrid,nlayer,naerkind)
    6865c     Aerosol effective variance used for radiative transfer (n.u.)
    69       REAL :: nueffrad(ngrid,nlayer,naerkind)
    70 
     66      REAL, INTENT(out) :: nueffrad(ngrid,nlayer,naerkind)
     67      REAL, INTENT(in) :: tauscaling(ngrid)         ! Convertion factor for qccn and Nccn
     68     
    7169c     Local variables:
    7270c     ---------------
     
    8583      REAL Mo,No                       ! Mass and number of ccn
    8684      REAL rhocloud(ngrid,nlayer)  ! Cloud density (kg.m-3)
    87       REAL tauscaling(ngrid)         ! Convertion factor for qccn and Nccn
    8885
    8986      LOGICAL,SAVE :: firstcall=.true.
     
    114111          ENDDO
    115112        ENDIF
     113
     114        ! updating radius of stormdust particles
     115        IF (rdstorm.AND.active) THEN
     116          DO l=1,nlayer
     117            DO ig=1, ngrid
     118              call updaterdust(pq(ig,l,igcm_stormdust_mass),
     119     &                 pq(ig,l,igcm_stormdust_number),rstormdust(ig,l))
     120              nueffdust(ig,l) = exp(varian**2.)-1.
     121             ENDDO
     122           ENDDO
     123        ENDIF
    116124       
    117125c       1.2 Water-ice particles
     
    126134
    127135          IF (firstcall) THEN
    128             IF (minval(tauscaling).lt.0) tauscaling(:) = 1.e-3 ! default value when non-read in startfi is -1
    129             IF (freedust)                tauscaling(:) = 1.    ! if freedust, enforce no rescaling at all
     136            !IF (minval(tauscaling).lt.0) tauscaling(:) = 1.e-3 ! default value when non-read in startfi is -1
     137            !IF (freedust)                tauscaling(:) = 1.    ! if freedust, enforce no rescaling at all
    130138            firstcall = .false.
    131139          ENDIF
     
    206214          ENDDO
    207215c==================================================================
     216        CASE("stormdust_doubleq") aerkind! Two-moment scheme for
     217c       stormdust; same distribution than normal dust
     218c==================================================================
     219          DO l=1,nlayer
     220            DO ig=1,ngrid
     221              reffrad(ig,l,iaer) = rstormdust(ig,l) * ref_r0
     222              nueffrad(ig,l,iaer) = nueffdust(ig,l)
     223            ENDDO
     224          ENDDO
     225c==================================================================
    208226        END SELECT aerkind
    209227      ENDDO ! iaer (loop on aerosol kind)
Note: See TracChangeset for help on using the changeset viewer.