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/callradite_mod.F

    r1969 r1974  
    77      SUBROUTINE callradite(icount,ngrid,nlayer,nq,zday,ls,pq,albedo,
    88     $     emis,mu0,pplev,pplay,pt,tsurf,fract,dist_sol,igout,
    9      $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,fluxtop_sw,
    10      &     tauref,tau,aerosol,dsodust,tauscaling,taucloudtes,rdust,rice,
    11      &     nuice,co2ice,clearsky,totcloudfrac)
     9     $     dtlw,dtsw,fluxsurf_lw,fluxsurf_sw,fluxtop_lw,
     10     $     fluxtop_sw,tauref,tau,aerosol,dsodust,tauscaling,
     11     $     taucloudtes,rdust,rice,nuice,co2ice,rstormdust,
     12     $     totstormfract,clearatm,dsords,
     13     $     clearsky,totcloudfrac)
    1214
    1315      use aeropacity_mod, only: aeropacity
     
    1618      use dimradmars_mod, only: naerkind, name_iaer,
    1719     &            iaer_dust_conrath,iaer_dust_doubleq,
    18      &            iaer_dust_submicron,iaer_h2o_ice
     20     &            iaer_dust_submicron,iaer_h2o_ice,
     21     &            iaer_stormdust_doubleq
    1922      use yomlw_h, only: gcp, nlaylte
    2023      use comcstfi_h, only: g,cpp
     
    154157c                         the "naerkind" kind of aerosol optical
    155158c                         properties.
    156 
    157159c=======================================================================
    158160c
     
    160162c    -------------
    161163c
    162 #include "callkeys.h"
     164      include "callkeys.h"
    163165
    164166c-----------------------------------------------------------------------
     
    170172
    171173      REAL,INTENT(IN) :: pq(ngrid,nlayer,nq)
    172       REAL,INTENT(IN) :: tauscaling(ngrid) ! Conversion factor for
     174      REAL,INTENT(INOUT) :: tauscaling(ngrid) ! Conversion factor for
    173175                               ! qdust and Ndust
    174176      REAL,INTENT(IN) :: albedo(ngrid,2),emis(ngrid)
     
    194196      REAL,INTENT(OUT) :: nuice(ngrid,nlayer)  ! Estimated effective variance
    195197      REAL,INTENT(IN) :: co2ice(ngrid)           ! co2 ice surface layer (kg.m-2)
     198
     199c     rocket dust storm
     200      LOGICAL,INTENT(IN) :: clearatm ! true for background dust
     201      REAL,INTENT(IN) :: totstormfract(ngrid) ! dust storm mesh fraction
     202      REAL,INTENT(OUT) :: rstormdust(ngrid,nlayer)  ! Storm dust geometric mean radius (m)
     203      REAL dsords(ngrid,nlayer) ! density scaled opacity for rocket dust storm dust
     204
    196205c     sub-grid scale water ice clouds
    197       real,intent(out) :: totcloudfrac(ngrid)
    198       logical,intent(in) :: clearsky
     206      LOGICAL,INTENT(IN) :: clearsky
     207      REAL,INTENT(IN) :: totcloudfrac(ngrid)
    199208
    200209c
     
    292301         iaer_dust_submicron=0
    293302         iaer_h2o_ice=0
     303         iaer_stormdust_doubleq=0
    294304
    295305         aer_count=0
     
    326336           enddo
    327337         endif
     338         if (rdstorm.AND.active) then
     339           do iaer=1,naerkind
     340             if (name_iaer(iaer).eq."stormdust_doubleq") then
     341               iaer_stormdust_doubleq = iaer
     342               aer_count = aer_count + 1
     343             endif
     344           enddo
     345         end if
    328346
    329347c        Check that we identified all tracers:
     
    372390c     Updating aerosol size distributions:
    373391      CALL updatereffrad(ngrid,nlayer,
    374      &                rdust,rice,nuice,
     392     &                rdust,rstormdust,rice,nuice,
    375393     &                reffrad,nueffrad,
    376394     &                pq,tauscaling,tau,pplay)
     
    385403c     Computing aerosol optical depth in each layer:
    386404      CALL aeropacity(ngrid,nlayer,nq,zday,pplay,pplev,ls,
    387      &     pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
    388      &     nueffrad,QREFvis3d,QREFir3d,omegaREFvis3d,omegaREFir3d,
    389      &     clearsky,totcloudfrac)
     405     &    pq,tauscaling,tauref,tau,taucloudtes,aerosol,dsodust,reffrad,
     406     &    QREFvis3d,QREFir3d,omegaREFir3d,
     407     &    totstormfract,clearatm,dsords,
     408     &    clearsky,totcloudfrac)
    390409
    391410c     Starting loop on sub-domain
Note: See TracChangeset for help on using the changeset viewer.