Changeset 629 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Apr 20, 2012, 2:57:26 PM (13 years ago)
Author:
tnavarro
Message:

Mistake in radius update in case of microphysics

File:
1 edited

Legend:

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

    r626 r629  
    22     &                rdust,rice,nuice,
    33     &                reffrad,nueffrad,
    4      &                pq)
     4     &                pq,tauscaling)
    55
    66       IMPLICIT NONE
     
    6868
    6969      REAL, PARAMETER :: ccn0 = 1.3E8
    70 
    71 c      LOGICAL firstcall
    72 c      DATA firstcall/.true./
    73 c      SAVE firstcall
     70     
     71c     For microphysics only:     
     72      REAL Mo,No                       ! Mass and number of ccn
     73      REAL rhocloud(ngridmx,nlayermx)  ! Cloud density (kg.m-3)
     74      REAL tauscaling(ngridmx)         ! Convertion factor for qccn and Nccn
     75
     76      LOGICAL firstcall
     77      DATA firstcall/.true./
     78      SAVE firstcall
    7479
    7580      REAL CBRT
     
    8186c     ---------------------
    8287
    83 c==================================================================
    84 
    85 c      IF (firstcall) THEN
    86 c       At firstcall, rdust and rice are not known; therefore
    87 c         they need to be computed below.
    88 
    89 c      Correction TN 17/04: rdust and rice must be updated at all steps,
    90 c      otherwise it is a possible source of bugs
     88
     89c==================================================================
     90c 1. Update radius from fields from dynamics or initial state
     91c==================================================================
    9192
    9293c       1.1 Dust particles
     
    110111          ENDDO
    111112        ENDIF
     113       
    112114c       1.2 Water-ice particles
    113115c       -----------------------
    114         IF (water.AND.activice) THEN
    115           DO l=1,nlayer
    116             DO ig=1,ngrid
    117               rice(ig,l) = max( CBRT(
    118      &          (pq(ig,l,igcm_h2o_ice)/rho_ice +
    119      &          ccn0*(4./3.)*pi*rdust(ig,l)**3.) /
    120      &          (ccn0*4./3.*pi)),rdust(ig,l) )
    121               nuice(ig,l) = nuice_ref
    122             ENDDO
    123           ENDDO
     116        IF (water.AND.activice) THEN         
     117          IF ((firstcall).or.(microphys.eq..false.)) THEN
     118            DO l=1,nlayer
     119              DO ig=1,ngrid
     120                rice(ig,l) = max(CBRT(
     121     &            (pq(ig,l,igcm_h2o_ice)/rho_ice +
     122     &            ccn0*(4./3.)*pi*rdust(ig,l)**3.) /
     123     &            (ccn0*4./3.*pi)),rdust(ig,l) )
     124                nuice(ig,l) = nuice_ref
     125              ENDDO
     126            ENDDO
     127          firstcall = .false.
     128c    At firstcall, the true number and true mass of cloud condensation nuclei are not known.
     129c    Indeed it is scaled on the prescribed dust opacity via a 'tauscaling' coefficient
     130c    computed after radiative transfer.
     131c    Therefore, we use a typical value ccn0 at firstcall, like it is done without microphysics.
     132          ELSE
     133            DO l=1,nlayer
     134              DO ig=1,ngrid
     135                Mo = pq(ig,l,igcm_h2o_ice) +
     136     &              pq(ig,l,igcm_ccn_mass)* tauscaling(ig) + 1.e-30
     137                No = pq(ig,l,igcm_ccn_number)* tauscaling(ig)+ 1e-30
     138                rhocloud(ig,l) =  pq(ig,l,igcm_h2o_ice)*rho_ice / Mo
     139     &           + pq(ig,l,igcm_ccn_mass)*tauscaling(ig)*rho_dust/Mo
     140                rhocloud(ig,l) =
     141     &            min(max(rhocloud(ig,l),rho_ice),rho_dust)
     142                rice(ig,l) =
     143     &           CBRT( Mo/No * 0.75 / pi / rhocloud(ig,l))
     144                nuice(ig,l) = nuice_ref
     145              ENDDO
     146            ENDDO
     147          ENDIF ! of if ((firstcall).or.(microphys.eq.false))
    124148        ENDIF ! of if (water.AND.activice)
    125149       
    126 c        firstcall = .false.
    127 c      ENDIF ! of if firstcall
    128150
    129151c==================================================================
Note: See TracChangeset for help on using the changeset viewer.