Ignore:
Timestamp:
Jun 26, 2023, 5:44:59 PM (17 months ago)
Author:
jnaar
Message:

Adaptative timestep working and computed directly in improvedclouds. Simpleclouds working again. JN

File:
1 edited

Legend:

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

    r2966 r2984  
    4747c  2004 - 2012
    4848c
    49 c     2023: J. Naar, adding different subtimestep on each grid cell
    50 c          plus not doing microphysics if no water present
    51 c          plus simpleclouds no longer in the loop for microphysics
     49c     2023: J. Naar, now with adaptative timestep for improvedclouds
     50c          (done in improvedclouds_mod).
    5251c=======================================================================
    5352
     
    146145! Scheme for adaptative timestep J. Naar 2023
    147146c      LOGICAL :: computed_micro(ngrid,nlay) ! Check if microphy was done in this cell
    148       REAL :: computed_micro(ngrid,nlay) ! Check if microphy was done inthis cell (logical)
     147      REAL :: count_micro(ngrid,nlay) ! Initially computed microtimestep
    149148      REAL :: zt_micro(ngrid,nlay) ! Temperature during microphysics (K)
    150149      REAL :: zq_micro(ngrid,nlay,nq) ! Tracers during microphysics (kg/kg)
     
    155154      REAL :: zpotcond(ngrid,nlay) ! maximal condensable water, used to
    156155compute adaptative subdivision of ptimestep
     156      REAL :: spenttime ! timespent
     157      REAL :: zdq ! used to compute adaptative timestep
    157158
    158159
     
    298299      END IF ! end if (CLFvarying)
    299300c------------------------------------------------------------------
    300 c Time subsampling for microphysics
     301c Cloud physics (nucleation, condensation / sublimation)
    301302c------------------------------------------------------------------
    302303      rhocloud(1:ngrid,1:nlay) = rho_dust
    303304
    304 
    305 c     Initialisation of all the stuff JN2023
    306 c      computed_micro(1:ngrid,1:nlay)=.false.
    307       computed_micro(1:ngrid,1:nlay)=0.
     305c     Initialisation of all the stuff (JN,2023)
    308306      zt_micro(:,:)=pt(:,:)
    309307      zq_micro(:,:,:)=pq(:,:,:)
    310       zq_micro(:,:,:)=pq(:,:,:)
    311       call watersat(ngrid*nlay,zt_micro,pplay,zqsat_micro)
    312       zpotcond_inst=zq_micro(:,:,igcm_h2o_vap) - zqsat_micro
    313       call watersat(ngrid*nlay,zt_micro+pdt*ptimestep,pplay,zqsat_micro)
    314       zpotcond_full=(zq_micro(:,:,igcm_h2o_vap)+
    315      &             pdq(:,:,igcm_h2o_vap)*ptimestep) - zqsat_micro
    316       zimicro(1:ngrid,1:nlay)=imicro
    317       if (cloud_adapt_ts) then
    318               call adapt_imicro(ptimestep,zpotcond(ig,l),
    319      $                   zimicro(ig,l))
    320       endif! (cloud_adapt_ts) then
    321       DO l=1,nlay
    322         DO ig=1,ngrid
    323 c         Start by computing the condensable water vapor amount
    324           if (zpotcond_full(ig,l).gt.0.) then
    325             zpotcond(ig,l)=max(zpotcond_inst(ig,l),zpotcond_full(ig,l))
    326           else if (zpotcond_full(ig,l).le.0.) then
    327             zpotcond(ig,l)=min(zpotcond_inst(ig,l),zpotcond_full(ig,l))
    328           endif! (zpotcond_full.gt.0.) then
    329           microtimestep=ptimestep/real(zimicro(ig,l))
    330 c         Check if microphysics is even needed, that is if enough action
    331 c         is happening water-wise
    332           if ((pq(ig,l,igcm_h2o_ice)+pdq(ig,l,igcm_h2o_ice)*ptimestep
    333      &      .gt.1e-22) .or. (abs(zpotcond(ig,l)).gt.1e-22)) then
    334 c         Eventuellement sortir simpleclouds de la boucle egalement
    335           computed_micro(ig,l)=1.
    336           DO microstep=1,zimicro(ig,l)
    337      
    338 
    339 c JN : incrementing after main microphysics scheme
    340 c Previously we were incrementing tendencies, we now
    341 c increment tracers and temperature directly
    342 c We are thus starting at the end of the first iteration
    343 c
     308
    344309c-------------------------------------------------------------------
    345310c   1.  Main call to the different cloud schemes:
    346311c------------------------------------------------
    347         IF (microphys) THEN
    348            CALL improvedclouds(microtimestep,
    349      &          pplay(ig,l),zt_micro(ig,l),
    350      &          zq_micro(ig,l,:),subpdqcloud(ig,l,:),
    351      &          subpdtcloud(ig,l),nq,tauscaling(ig),mmean(ig,l))
    352 
    353         ELSE
    354 c Simpleclouds should maybe be taken out and put in a specific loop ?
    355            CALL simpleclouds(ngrid,nlay,microtimestep,
     312c ds.
     313      IF (microphys) THEN
     314           CALL improvedclouds(ngrid,nlay,ptimestep,
     315     &          pplay,pt,pdt,pq,pdq,nq,tauscaling,imicro,
     316     &          zt_micro,zq_micro)
     317
     318      ELSE
     319
     320c Specific loop for simpleclouds.
     321       DO l=1,nlay
     322         DO ig=1,ngrid
     323           CALL simpleclouds(ngrid,nlay,ptimestep,
    356324     &             pplay,pzlay,pteff,sum_subpdt,
    357325     &             pqeff,sum_subpdq,subpdqcloud,subpdtcloud,
    358326     &             nq,tau,rice)
    359         ENDIF
    360 
    361327c-------------------------------------------------------------------
    362328c   2.  Updating tracers and temperature after cloud scheme:
     329c   For improved clouds (with microphysics) this is done directly
     330c   in the microphysics, during the subtimestep
     331c   I put it like that to be retrocompatible (JN)
    363332c-----------------------------------------------
    364333
    365         IF (microphys) THEN
    366               zq_micro(ig,l,igcm_dust_mass) =
    367      &         zq_micro(ig,l,igcm_dust_mass)+(pdq(ig,l,igcm_dust_mass)
    368      &         +subpdqcloud(ig,l,igcm_dust_mass))*microtimestep
    369               zq_micro(ig,l,igcm_dust_number) =
    370      &         zq_micro(ig,l,igcm_dust_number)
    371      &         +(pdq(ig,l,igcm_dust_number)
    372      &         + subpdqcloud(ig,l,igcm_dust_number))*microtimestep
    373               zq_micro(ig,l,igcm_ccn_mass) =
    374      &         zq_micro(ig,l,igcm_ccn_mass) +
    375      &         (pdq(ig,l,igcm_ccn_mass)
    376      &         +subpdqcloud(ig,l,igcm_ccn_mass))*microtimestep
    377               zq_micro(ig,l,igcm_ccn_number) =
    378      &          zq_micro(ig,l,igcm_ccn_number) +
    379      &         (pdq(ig,l,igcm_ccn_number)
    380      &          + subpdqcloud(ig,l,igcm_ccn_number))*microtimestep
    381         ENDIF
    382334            zq_micro(ig,l,igcm_h2o_ice) =
    383335     &       zq_micro(ig,l,igcm_h2o_ice)+
    384336     &         (pdq(ig,l,igcm_h2o_ice)
    385      &        + subpdqcloud(ig,l,igcm_h2o_ice))*microtimestep
     337     &        + subpdqcloud(ig,l,igcm_h2o_ice))*ptimestep
    386338            zq_micro(ig,l,igcm_h2o_vap) =
    387339     &       zq_micro(ig,l,igcm_h2o_vap)+
    388340     &         (pdq(ig,l,igcm_h2o_vap)
    389      &        + subpdqcloud(ig,l,igcm_h2o_vap))*microtimestep
     341     &        + subpdqcloud(ig,l,igcm_h2o_vap))*ptimestep
    390342
    391343            IF (hdo) THEN
     
    393345     &       zq_micro(ig,l,igcm_hdo_ice)+
    394346     &         (pdq(ig,l,igcm_hdo_ice)
    395      &        + subpdqcloud(ig,l,igcm_hdo_ice))*microtimestep
     347     &        + subpdqcloud(ig,l,igcm_hdo_ice))*ptimestep
    396348            zq_micro(ig,l,igcm_hdo_vap) =
    397349     &       zq_micro(ig,l,igcm_hdo_vap)+
    398350     &         (pdq(ig,l,igcm_hdo_vap)
    399      &        + subpdqcloud(ig,l,igcm_hdo_vap))*microtimestep
     351     &        + subpdqcloud(ig,l,igcm_hdo_vap))*ptimestep
    400352            ENDIF ! hdo
    401353
    402354c  Could also set subpdtcloud to 0 if not activice to make it simpler
    403             zt_micro(ig,l) = zt_micro(ig,l)+
    404      &           pdt(ig,l)*microtimestep
    405         IF (activice) THEN
    406               zt_micro(ig,l) = zt_micro(ig,l)+
    407      &           subpdtcloud(ig,l)*microtimestep
    408         ENDIF
    409 !      !! Example of how to use writediagmicrofi useful to
    410 !      !! get outputs at each microphysical sub-timestep (better to be used in 1D)
    411 !            CALL WRITEDIAGMICROFI(ngrid,imicro,microstep,
    412 !     &       microtimestep,'subpdtcloud',
    413 !     &      'subpdtcloud','K/s',1,subpdtcloud(:,:))     
    414  
    415           ENDDO ! of DO microstep=1,imicro
    416           endif! (zq(ig,l,igcm_h2o_ice)+pdq(ig,l,igcm_h2o_ice)*ptimestep
    417 !     &      .gt.1e-22).or.(abs(zpotcond).gt.1e-22) then
    418         ENDDO ! ig=1,ngrid
    419       ENDDO ! l=1,nlay
    420 
    421      
    422 c------ Useful outputs to check how it went
    423       call write_output("computed_micro","computed_micro "//
    424      &   "after microphysics","logical",computed_micro(:,:))
    425       call write_output("zimicro","Used number of subtimestep "//
    426      &   "in cloud microphysics","integer",real(zimicro(:,:)))
     355c  or change name of the flag
     356            IF (activice) THEN
     357                zt_micro(ig,l) = zt_micro(ig,l)+
     358     &             subpdtcloud(ig,l)*ptimestep
     359            ENDIF
     360
     361         ENDDO !ig=1,ngrid
     362       ENDDO !l=1,nlay
     363      ENDIF
     364
     365
     366     
    427367c-------------------------------------------------------------------
    428368c   3.  Compute final tendencies after time loop:
     
    786726
    787727
    788        SUBROUTINE adapt_imicro(ptimestep,potcond,
    789      $                     zimicro)
    790 
    791 c Pas de temps adaptatif pour les nuages
    792 
    793       real,intent(in) :: ptimestep ! total duration of physics (sec)
    794       real,intent(in) :: potcond ! total duration of physics (sec)
    795       real :: alpha, beta ! total duration of physics (sec)
    796       integer,intent(out) :: zimicro ! number of ptimestep division
    797 
    798 c       zimicro = ptimestep*alpha*potcond**beta
    799        zimicro = 30
    800 
    801        END SUBROUTINE adapt_imicro
    802 
    803 
    804728      END MODULE watercloud_mod
Note: See TracChangeset for help on using the changeset viewer.