Ignore:
Timestamp:
Apr 24, 2019, 12:11:24 PM (6 years ago)
Author:
emillour
Message:

Mars GCM:
Updated co2condens to correctly conserve tracer mass
EM+FF

File:
1 edited

Legend:

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

    r2009 r2124  
    1616       use tracer_mod, only: noms
    1717       use surfdat_h, only: emissiv, phisfi
    18        use geometry_mod, only: latitude ! grid point latitudes (rad)
     18       use geometry_mod, only: latitude, ! grid point latitudes (rad)
     19     &                         longitude_deg, latitude_deg
    1920       use planete_h, only: obliquit
    2021       use comcstfi_h, only: cpp, g, r, pi
    2122#ifndef MESOSCALE
    22        USE vertical_layers_mod, ONLY: bp
     23       USE vertical_layers_mod, ONLY: ap, bp
    2324#endif
    2425       IMPLICIT NONE
     
    113114      REAL masse(nlayer),w(nlayer+1)
    114115      REAL Sm(nlayer),Smq(nlayer,nq),mixmas,qmix
     116      REAL availco2
    115117      LOGICAL condsub(ngrid)
    116118
     
    130132c   local saved variables
    131133      integer,save :: ico2 ! index of CO2 tracer
    132       real,save :: qco2min,qco2,mmean
     134      real,save :: qco2,mmean
    133135      real,parameter :: latcond=5.9e5 ! (J/kg) Latent heat of solid CO2 ice
    134136      real,parameter :: tcond1mb=136.27 ! condensation temperature (K) at 1 mbar
     
    139141      LOGICAL,SAVE :: firstcall = .true. !,firstcall2=.true.
    140142
    141 c D.BARDET: to debug
     143c D.BARDET: for debug
    142144      real ztc3D(ngrid,nlayer)
    143145      REAL ztm3D(ngrid,nlayer)
     
    156158
    157159         firstcall=.false.
    158          write(*,*) 'Newcondens: improved_ztcond=',improved_ztcond
    159          PRINT*,'In newcondens:Tcond(P=1mb)=',tcond1mb,' Lcond=',latcond
     160         write(*,*) 'CO2condens: improved_ztcond=',improved_ztcond
     161         PRINT*,'In co2condens:Tcond(P=1mb)=',tcond1mb,' Lcond=',latcond
    160162         PRINT*,'acond,bcond,ccond',acond,bcond,ccond
    161163
     
    177179             endif
    178180           enddo
    179 c          minimum CO2 mix. ratio below which mixing occur with layer above:
    180            qco2min =0.75 
    181181         end if
    182182      ENDIF ! of IF (firstcall)
     
    378378     &      /(latcond*ptimestep)         - zfallheat
    379379            pdtsrfc(ig) = (ztcondsol(ig) - ztsrf(ig))/ptimestep
    380        
     380            zdiceco2(ig) = zcondices(ig) + zfallice(ig,1)
     381
     382c           If there is not enough CO2 tracer in 1st layer to condense
     383c           """"""""""""""""""""""""""""""""""""""""""""""""""""""
     384            IF(ico2.ne.0) then
     385c              Available CO2 tracer in layer 1 at end of timestep (kg/m2)
     386                availco2= pq(ig,1,ico2)*((ap(1)-ap(2))+
     387     &          (bp(1)-bp(2))*(pplev(ig,1)/g-zdiceco2(ig)*ptimestep))
     388
     389               IF ((zcondices(ig) + zcondicea(ig,1))*ptimestep
     390     &           .gt.availco2) then
     391                   zcondices(ig) = availco2/ptimestep -zcondicea(ig,1)
     392                   zdiceco2(ig) = zcondices(ig) + zfallice(ig,1)
     393                   pdtsrfc(ig)=(latcond/pcapcal(ig))*
     394     &                          (zcondices(ig)+zfallheat)
     395               ENDIF
     396            ENDIF
     397
     398
    381399c           If the entire CO_2 ice layer sublimes
    382400c           """"""""""""""""""""""""""""""""""""""""""""""""""""
     
    388406               pdtsrfc(ig)=(latcond/pcapcal(ig))*
    389407     &         (zcondices(ig)+zfallheat)
     408               zdiceco2(ig) = zcondices(ig) + zfallice(ig,1)
    390409            END IF
    391410
     
    393412c           """"""""""""""""""""""""""""""""""""
    394413
    395             zdiceco2(ig) = zcondices(ig) + zfallice(ig,1)
    396414            piceco2(ig) = piceco2(ig) + zdiceco2(ig)*ptimestep
    397415            pdpsrf(ig) = -zdiceco2(ig)*g
     
    401419               PRINT*,'condensing more than total mass'
    402420               PRINT*,'Grid point ',ig
     421               PRINT*,'Longitude(degrees): ',longitude_deg(ig)
     422               PRINT*,'Latitude(degrees): ',latitude_deg(ig)
    403423               PRINT*,'Ps = ',pplev(ig,1)
    404424               PRINT*,'d Ps = ',pdpsrf(ig)
     
    416436           if(.not.piceco2(ig).ge.0.) THEN
    417437              if(piceco2(ig).le.-5.e-8) print*,
    418      $         'WARNING newcondens piceco2(',ig,')=', piceco2(ig)
     438     $         'WARNING co2condens piceco2(',ig,')=', piceco2(ig)
    419439               piceco2(ig)=0.
    420440           endif
     
    465485            END DO
    466486
    467 c Mass of each layer
    468 c ------------------
     487c Mass of each layer at the end of timestep
     488c -----------------------------------------
    469489            DO l=1,nlayer
    470               masse(l)=(pplev(ig,l) - pplev(ig,l+1))/g
     490              masse(l)=( pplev(ig,l) - pplev(ig,l+1) + 
     491     &                 (bp(l)-bp(l+1))*pdpsrf(ig)*ptimestep)/g
    471492            END DO
    472493
     
    628649           ! NB: Updated surface pressure, at grid point 'ngrid', is
    629650           !     ps(ngrid)=pplev(ngrid,1)+pdpsrf(ngrid)*ptimestep
    630 !             write(*,*) "newcondens: South pole: latitude(ngrid)=",
     651!             write(*,*) "co2condens: South pole: latitude(ngrid)=",
    631652!     &                                           latitude(ngrid)
    632653             ztcondsol(ngrid)=
     
    754775       enddo
    755776
    756 c     boundary conditions (not used in newcondens !!)
     777c     boundary conditions (not used in co2condens !!)
    757778c         qm(nlayer+1)=0.
    758779c         if(w(1).gt.0.) then
Note: See TracChangeset for help on using the changeset viewer.