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

    r1962 r1974  
    44
    55      CONTAINS
    6      
    7       SUBROUTINE callsedim(ngrid,nlay, ptimestep,
    8      &                pplev,zlev, zlay, pt, pdt, rdust, rice,
     6
     7      SUBROUTINE callsedim(ngrid,nlay,ptimestep,
     8     &                pplev,zlev,zlay,pt,pdt,rdust,rstormdust,rice,
    99     &                rsedcloud,rhocloud,
    10      &                pq, pdqfi, pdqsed,pdqs_sed,nq,
     10     &                pq,pdqfi,pdqsed,pdqs_sed,nq,
    1111     &                tau,tauscaling)
    12 ! to use  'getin'
     12
    1313      USE ioipsl_getincom, only: getin
    1414      USE updaterad, only: updaterdust,updaterice_micro,updaterice_typ
     
    1717     &                      igcm_ccn_mass, igcm_ccn_number,
    1818     &                      igcm_h2o_ice, nuice_sed, nuice_ref,
    19      &                      igcm_ccnco2_mass, igcm_ccnco2_number,
    20      &                      igcm_co2_ice
     19     &                      igcm_ccnco2_mass,igcm_ccnco2_number,
     20     &                      igcm_co2_ice, igcm_stormdust_mass,
     21     &                      igcm_stormdust_number
    2122      USE newsedim_mod, ONLY: newsedim
    2223      USE comcstfi_h, ONLY: g
     
    6162c    Aerosol radius provided by the water ice microphysical scheme:
    6263      real,intent(out) :: rdust(ngrid,nlay) ! Dust geometric mean radius (m)
     64      real,intent(out) :: rstormdust(ngrid,nlay) ! Stormdust geometric mean radius (m)
    6365      real,intent(out) :: rice(ngrid,nlay)  ! H2O Ice geometric mean radius (m)
    6466c     Sedimentation radius of water ice
     
    8991      real r0dust(ngrid,nlay) ! geometric mean radius used for
    9092                                    !   dust (m)
    91 !      real r0ccn(ngrid,nlay)  ! geometric mean radius used for
     93      real r0stormdust(ngrid,nlay) ! Geometric mean radius used for stormdust (m)
    9294!                                    !   CCNs (m)
    9395      real,save :: beta ! correction for the shape of the ice particles (cf. newsedim)
    94 
    9596c     for ice radius computation
    9697      REAL Mo,No
     
    133134      INTEGER,SAVE :: iccn_number ! index of tracer containing CCN number
    134135                                  !   mix. ratio
     136      INTEGER,SAVE :: istormdust_mass  !  index of tracer containing
     137                                       !stormdust mass mix. ratio
     138      INTEGER,SAVE :: istormdust_number !  index of tracer containing
     139                                        !stormdust number mix. ratio                     
    135140      INTEGER,SAVE :: iccnco2_number ! index of tracer containing CCN number
    136141      INTEGER,SAVE :: iccnco2_mass ! index of tracer containing CCN number
     
    140145      LOGICAL,SAVE :: firstcall=.true.
    141146
     147
     148
    142149c    ** un petit test de coherence
    143150c       --------------------------
    144 
    145151      ! AS: firstcall OK absolute
    146152      IF (firstcall) THEN
     
    240246       ENDIF                    !of if (co2clouds)
    241247
    242 
    243         IF (water) THEN
     248       IF (water) THEN
    244249         write(*,*) "correction for the shape of the ice particles ?"
    245250         beta=0.75 ! default value
     
    251256            write(*,*) "water_param nueff Radiative:", nuice_ref
    252257          ENDIF
    253         ENDIF
     258       ENDIF
     259
     260       IF (rdstorm) THEN ! identifying stormdust tracers for sedimentation
     261           istormdust_mass=0      ! dummy initialization
     262           istormdust_number=0    ! dummy initialization
     263
     264           do iq=1,nq
     265             if (noms(iq).eq."stormdust_mass") then
     266               istormdust_mass=iq
     267               write(*,*)"callsedim: istormdust_mass=",istormdust_mass
     268             endif
     269             if (noms(iq).eq."stormdust_number") then
     270               istormdust_number=iq
     271               write(*,*)"callsedim: istormdust_number=",
     272     &                                           istormdust_number
     273             endif
     274           enddo
     275
     276           ! check that we did find the tracers
     277           if ((istormdust_mass.eq.0).or.(istormdust_number.eq.0)) then
     278             write(*,*) 'callsedim: error! could not identify'
     279             write(*,*) ' tracers for stormdust mass and number mixing'
     280             write(*,*) ' ratio and rdstorm is activated!'
     281             stop
     282           endif
     283       ENDIF !of if (rdstorm)
    254284     
    255285        firstcall=.false.
     
    268298      zt(1:ngrid,1:nlay)=pt(1:ngrid,1:nlay)
    269299     &                         +pdt(1:ngrid,1:nlay)*ptimestep
    270 
    271300
    272301c    Computing the different layer properties
     
    295324        end do
    296325      endif
    297 
    298 
     326      ! rocket dust storm
     327      if (rdstorm) then
     328        do l=1,nlay
     329          do ig=1, ngrid
     330     
     331         call updaterdust(zqi(ig,l,igcm_stormdust_mass),
     332     &               zqi(ig,l,igcm_stormdust_number),r0stormdust(ig,l),
     333     &               tauscaling(ig))
     334         
     335          end do
     336        end do
     337      endif
    299338c =================================================================
    300339      do iq=1,nq
     
    307346c -----------------------------------------------------------------
    308347          if ((doubleq.and.
    309      &        ((iq.eq.idust_mass).or.
    310      &         (iq.eq.idust_number)))) then
     348     &     ((iq.eq.idust_mass).or.(iq.eq.idust_number).or.
     349     &     (iq.eq.istormdust_mass).or.(iq.eq.istormdust_number)))) then
    311350     
    312351c           Computing size distribution:
    313352c           ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    314353
    315 c            if ((iq.eq.idust_mass).or.(iq.eq.idust_number)) then
     354            if ((iq.eq.idust_mass).or.(iq.eq.idust_number)) then
    316355              do  l=1,nlay
    317356                do ig=1, ngrid
     
    319358                end do
    320359              end do
    321               sigma0 = varian
     360            else if ((iq.eq.istormdust_mass).or.
     361     &                                (iq.eq.istormdust_number)) then
     362              do  l=1,nlay
     363                do ig=1, ngrid
     364                  r0(ig,l)=r0stormdust(ig,l)
     365                end do
     366              end do
     367            endif
     368            sigma0 = varian
    322369
    323370c        Computing mass mixing ratio for each particle size
    324371c        ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    325           IF ((iq.EQ.idust_mass).or.(iq.EQ.iccn_mass)) then
     372          IF ((iq.EQ.idust_mass).or.(iq.EQ.istormdust_mass)) then
    326373            radpower = 2
    327374          ELSE  ! number
     
    376423
    377424          do ir=1,nr
    378          
    379425               call newsedim(ngrid,nlay,1,1,ptimestep,
    380426     &         pplev,masse,epaisseur,zt,rd(ir),(/rho_dust/),qr(1,1,ir),
     
    391437                 zqi(ig,l,iq)=zqi(ig,l,iq)+qr(ig,l,ir)
    392438               ENDDO
    393              ENDDO
     439             ENDDO           
    394440          enddo ! of do ir=1,nr
    395441c -----------------------------------------------------------------
     
    457503       ENDDO
    458504      endif ! of if (doubleq)
    459      
     505
     506      if (rdstorm) then
     507       DO l = 1, nlay
     508        DO ig=1,ngrid
     509         call updaterdust(zqi(ig,l,igcm_stormdust_mass),
     510     &                zqi(ig,l,igcm_stormdust_number),rstormdust(ig,l),
     511     &                tauscaling(ig))   
     512        ENDDO
     513       ENDDO
     514      endif ! of if (rdstorm)
     515 
    460516c     Update the ice particle size "rice"
    461517c     -------------------------------------
     
    490546     
    491547      END MODULE callsedim_mod
     548
Note: See TracChangeset for help on using the changeset viewer.