Changeset 3421 for trunk/LMDZ.PLUTO


Ignore:
Timestamp:
Aug 26, 2024, 6:11:23 PM (3 months ago)
Author:
afalco
Message:

Pluto PCM: Added vertical mixing in no gcm, ch4/co surf, no_n2frost.
AF

Location:
trunk/LMDZ.PLUTO/libf
Files:
2 added
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/dynphy_lonlat/phypluto/leapfrog_nogcm.F

    r3412 r3421  
    1515      USE guide_mod, ONLY : guide_main
    1616      USE write_field, ONLY: writefield
     17      USE callkeys_mod, only: tau_n2, tau_ch4, tau_co
    1718      USE control_mod, ONLY: planet_type,nday,day_step,iperiod,iphysiq,
    1819     &                       less1day,fractday,ndynstep,iconser,
     
    109110!       ED18 nogcm
    110111      REAL tau_ps
    111       REAL tau_n2
     112      REAL tau_x
     113      REAL tau_def
    112114      REAL tau_teta
    113115      REAL tetadpmean
     
    199201
    200202      REAL psmean                    ! pression moyenne
    201       REAL pqn2mean                 ! moyenne globale ps*qco
     203      REAL pqxmean                 ! moyenne globale ps*qco
    202204      REAL p0                        ! pression de reference
    203205      REAL p00d                        ! globalaverage(kpd)
    204       REAL qmean_n2,qmean_n2_vert ! mass mean mixing ratio vap n2
    205       REAL pqn2(ip1jmp1)           ! average n2 mass index : ps*q_n2
     206      REAL qmean_x,qmean_x_vert ! mass mean mixing ratio vap n2
     207      REAL pqx(ip1jmp1)           ! average n2 mass index : ps*q_n2
    206208      REAL oldps(ip1jmp1)           ! saving old pressure ps to calculate qch4
    207209
     
    243245      real :: n2mass(iip1,jjp1)
    244246      real :: n2ice_ij(iip1,jjp1)
    245       integer,save :: igcm_n2=0 ! index of CO2 tracer (if any)
     247      integer,save :: igcm_n2=0 ! index of N2 tracer (if any)
     248      integer,save :: igcm_ch4=0 ! index of CH4 tracer (if any)
     249      integer,save :: igcm_co=0 ! index of CO tracer (if any)
    246250      integer :: i,j,ig
    247251      integer, parameter :: ngrid = 2+(jjm-1)*iim
     
    339343      p00d=globaverage2d(kpd) ! mean pres at ref level
    340344      tau_ps = 1. ! constante de rappel for pressure  (s)
    341       tau_n2 = 1.E5 !E5 ! constante de rappel for mix ratio qn2 (s)
     345      tau_n2 = 1 ! constante de rappel for mix ratio qn2 (s)
     346      tau_def = 1.E7 ! default constante de rappel for mix ratio qX (s)
    342347      tau_teta = 1.E7 !constante de rappel for potentiel temperature
    343348
    344       PRINT*,'igcm_n2 = ',igcm_n2
    345349      do iq=1,nqtot
    346350        if (tname(iq)=="n2") then
    347351          igcm_n2=iq
    348           exit
     352      !     exit
     353        else if (tname(iq)=="ch4_gas") then
     354            igcm_ch4=iq
     355        else if (tname(iq)=="co_gas") then
     356            igcm_co=iq
    349357        endif
    350358      enddo
     359      PRINT*,'igcm_n2 = ',igcm_n2
     360      PRINT*,'igcm_ch4 = ',igcm_ch4
     361      PRINT*,'igcm_co = ',igcm_co
    351362
    352363c-----------------------------------------------------------------------
     
    658669!          ENDIF
    659670
    660 c          Mixing CO2 vertically
     671c          Mixing N2 vertically ! not used for pluto ?
    661672c          --------------------------
    662            if (igcm_n2.ne.0) then
    663             DO ij=1,ip1jmp1
    664                qmean_n2_vert=0.
    665                DO l=1, llm
    666                  qmean_n2_vert= qmean_n2_vert
    667      &          + q(ij,l,igcm_n2)*( p(ij,l) - p(ij,l+1))
    668                END DO
    669                qmean_n2_vert= qmean_n2_vert/ps(ij)
    670                DO l=1, llm
    671                  q(ij,l,igcm_n2)= qmean_n2_vert
    672                END DO
    673             END DO
    674            end if
     673!            if (igcm_n2.ne.0) then
     674!             DO ij=1,ip1jmp1
     675!                qmean_x_vert=0.
     676!                DO l=1, llm
     677!                  qmean_x_vert= qmean_x_vert
     678!      &          + q(ij,l,igcm_n2)*( p(ij,l) - p(ij,l+1))
     679!                END DO
     680!                qmean_x_vert= qmean_x_vert/ps(ij)
     681!                DO l=1, llm
     682!                  q(ij,l,igcm_n2)= qmean_x_vert
     683!                END DO
     684!             END DO
     685!            end if
    675686
    676687
     
    684695c        --------------------------------------------------------------------------------- 
    685696
    686          ! Simulate redistribution by dynamics for qn2
    687            if (igcm_n2.ne.0) then
     697         ! Simulate redistribution by dynamics for qX
     698         DO iq=1,nqtot
     699           if ((iq.eq.igcm_n2).or.(iq.eq.igcm_ch4).or.
     700     &         (iq.eq.igcm_co)) then
    688701
    689702              DO ij=1,ip1jmp1
    690                  pqn2(ij)= ps(ij) * q(ij,1,igcm_n2)
     703                 pqx(ij)= ps(ij) * q(ij,1,iq)
    691704              ENDDO
    692               pqn2mean=globaverage2d(pqn2)
    693 
    694          !    Rappel newtonien vers qn2_mean
    695               qmean_n2= pqn2mean / psmean
     705              pqxmean=globaverage2d(pqx)
     706
     707         !    Rappel newtonien vers qx_mean
     708              qmean_x= pqxmean / psmean
     709             
     710              tau_x = tau_def
     711              if (iq.eq.igcm_n2) then
     712                  tau_x = tau_n2
     713              else if (iq.eq.igcm_ch4) then
     714                  tau_x = tau_ch4
     715              else if (iq.eq.igcm_co) then
     716                  tau_x = tau_co
     717              end if
     718              PRINT*,' tau_x ',iq,tau_x
    696719
    697720              DO ij=1,ip1jmp1
    698                   q(ij,1,igcm_n2)=q(ij,1,igcm_n2)+
    699      &                  (qmean_n2-q(ij,1,igcm_n2))*
    700      &                  (1.-exp(-dtphys/tau_n2))
     721                  q(ij,1,iq)=q(ij,1,iq)+
     722     &                  (qmean_x-q(ij,1,iq))*
     723     &                  (1.-exp(-dtphys/tau_x))
    701724              ENDDO
    702725
    703726              DO l=2, llm
    704727                 DO ij=1,ip1jmp1
    705                      q(ij,l,igcm_n2)=q(ij,1,igcm_n2)
     728                     q(ij,l,iq)=q(ij,1,iq)
    706729                 END DO
    707730              END DO
     
    709732!             TEMPORAIRE (ED)
    710733!             PRINT*,'psmean = ',psmean
    711 !             PRINT*,'qmean_n2 = ',qmean_n2
    712 !             PRINT*,'pqn2mean = ',pqn2mean
    713 !             PRINT*,'q(50,1,igcm_n2) = ',q(50,1,igcm_n2)
    714 !             PRINT*,'q(50,2,igcm_n2) = ',q(50,2,igcm_n2)
    715 !             PRINT*,'q(50,3,igcm_n2) = ',q(50,3,igcm_n2)
     734!             PRINT*,'qmean_x = ',qmean_x
     735!             PRINT*,'pqxmean = ',pqxmean
     736            ! PRINT*,' q(50,1) = ',iq,q(50,1,iq)
     737            ! PRINT*,' q(50,2) = ',iq,q(50,2,iq)
     738            ! PRINT*,' q(50,3) = ',iq,q(50,3,iq)
    716739
    717740           endif ! igcm_n2.ne.0
    718 
    719 
    720 !       ********************************************************
     741      enddo
     742
     743
     744!       *****************************************s***************
    721745
    722746c        Horizontal mixing of pressure
  • trunk/LMDZ.PLUTO/libf/phypluto/condense_n2.F90

    r3390 r3421  
    116116  real zdtlatent (klon,klev)
    117117  real zdt (klon,klev)
    118   REAL albediceF(klon)
     118!  REAL albediceF(klon)
    119119!   SAVE albediceF
    120120  INTEGER nsubtimestep,itsub    !number of subtimestep when calling vl1d
     
    130130  REAL globzplevnew
    131131
    132   REAL vmrn2(klon)
    133 !   SAVE vmrn2
     132  real,dimension(:),save,allocatable :: vmrn2
     133!$OMP THREADPRIVATE(vmrn2)
    134134  REAL stephan
    135135  DATA stephan/5.67e-08/  ! Stephan Boltzman constant
     
    179179     ENDIF
    180180
     181     ALLOCATE(vmrn2(klon))
    181182     vmrn2(:) = 1.
    182183     !IF (ch4lag) then
     
    187188     !   ENDDO
    188189     !ENDIF
    189      !IF (no_n2frost) then
    190      !   DO ig=1,klon
    191      !      if (picen2(ig).eq.0.) then
    192      !         vmrn2(ig) = 1.e-15
    193      !      endif
    194      !   ENDDO
    195      !ENDIF
     190     IF (no_n2frost) then
     191        DO ig=1,klon
     192           if (picen2(ig).eq.0.) then
     193              vmrn2(ig) = 1.e-15
     194           endif
     195        ENDDO
     196     ENDIF
    196197     firstcall=.false.
    197198  ENDIF
     
    344345   DO ig=1,klon
    345346     ! forecast of frost temperature ztcondsol
    346      ztcondsol(ig) = tcond_n2(zplev(ig),zqn2(ig,1))
    347      !ztcondsol(ig) = tcond_n2(zplev(ig),vmrn2(ig))
     347     !ztcondsol(ig) = tcond_n2(zplev(ig),zqn2(ig,1))
     348     ztcondsol(ig) = tcond_n2(zplev(ig),vmrn2(ig))
    348349
    349350!     Loop over where we have condensation / sublimation
     
    898899   return
    899900   end  subroutine vl1d
    900 
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3412 r3421  
    3333      USE tracer_h, only: noms, mmol, radius, rho_q, qext, &
    3434                          igcm_n2,igcm_ch4_gas,igcm_ch4_ice,igcm_haze,&
    35                           igcm_co_gas,igcm_co_ice,igcm_prec_haze,lw_n2,&
     35                          igcm_co_gas,igcm_co_ice,igcm_prec_haze,lw_n2,lw_ch4,lw_co,&
    3636                          alpha_lift, alpha_devil, qextrhor, &
    3737                          nesp, is_chim, is_condensable,constants_epsi_generic
     
    5555                              n2cond,nearn2cond,noseason_day,conservn2, &
    5656                              convergeps,kbo,triton,paleo,paleoyears,glaflow, &
    57                               carbox, methane,&
     57                              carbox, methane,condmetsurf,condcosurf,&
    5858                              oldplutovdifc,oldplutocorrk,oldplutosedim, &
    5959                              aerohaze,haze_proffix,source_haze, tsurfmax, &
     
    12481248
    12491249         ! if(.not.newtonian)then
    1250             zdtsurf(1:ngrid) = zdtsurf(1:ngrid) + (fluxrad(1:ngrid) + fluxgrd(1:ngrid))/capcal(1:ngrid)
     1250         zdtsurf(1:ngrid) = zdtsurf(1:ngrid) + (fluxrad(1:ngrid) + fluxgrd(1:ngrid))/capcal(1:ngrid)
     1251
     1252!        ------------------------------------------------------------------
     1253!        Methane surface sublimation and condensation in fast model (nogcm)
     1254!        ------------------------------------------------------------------
     1255         if ((methane).and.(fast).and.condmetsurf) THEN
     1256
     1257            call ch4surf(ngrid,nlayer,nq,ptimestep, &
     1258               tsurf,zdtsurf,pplev,pdpsrf,pq,pdq,qsurf,dqsurf, &
     1259               zdqch4fast,zdqsch4fast)
     1260
     1261            dqsurf(1:ngrid,igcm_ch4_ice)= dqsurf(1:ngrid,igcm_ch4_ice) + &
     1262                                         zdqsch4fast(1:ngrid)
     1263            pdq(1:ngrid,1,igcm_ch4_gas)= pdq(1:ngrid,1,igcm_ch4_gas) + &
     1264                                         zdqch4fast(1:ngrid)
     1265            zdtsurf(1:ngrid)=zdtsurf(1:ngrid)+lw_ch4*zdqsch4fast(1:ngrid)/capcal(1:ngrid)
     1266            end if
     1267!        ------------------------------------------------------------------
     1268!        CO surface sublimation and condensation in fast model (nogcm)
     1269!        ------------------------------------------------------------------
     1270         if ((carbox).and.(fast).and.condcosurf) THEN
     1271
     1272            call cosurf(ngrid,nlayer,nq,ptimestep, &
     1273               tsurf,pplev,pdpsrf,pq,pdq,qsurf,dqsurf, &
     1274               zdqcofast,zdqscofast)
     1275
     1276            dqsurf(1:ngrid,igcm_co_ice)= dqsurf(1:ngrid,igcm_co_ice) + &
     1277                                         zdqscofast(1:ngrid)
     1278            pdq(1:ngrid,1,igcm_co_gas)= pdq(1:ngrid,1,igcm_co_gas) + &
     1279                                        zdqcofast(1:ngrid)
     1280            zdtsurf(1:ngrid)=zdtsurf(1:ngrid)+lw_co*zdqscofast(1:ngrid)/capcal(1:ngrid)
     1281         end if
     1282
    12511283
    12521284      endif ! end of 'calldifv'
Note: See TracChangeset for help on using the changeset viewer.