Changeset 3411 for trunk/LMDZ.PLUTO


Ignore:
Timestamp:
Aug 20, 2024, 12:12:41 PM (3 months ago)
Author:
afalco
Message:

Pluto PCM: Fixed some issue with no gcm.
AF

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

Legend:

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

    r3410 r3411  
    1313#endif
    1414      USE infotrac, ONLY: nqtot,ok_iso_verif,tname
     15      USE guide_mod, ONLY : guide_main
    1516      USE write_field, ONLY: writefield
    1617      USE control_mod, ONLY: planet_type,nday,day_step,iperiod,iphysiq,
     
    2223      use exner_milieu_m, only: exner_milieu
    2324      use cpdet_mod, only: cpdet,tpot2t,t2tpot
     25      use sponge_mod, only: callsponge,mode_sponge,sponge
    2426       use comuforc_h
    2527      USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs,
     
    107109!       ED18 nogcm
    108110      REAL tau_ps
    109       REAL tau_co2
     111      REAL tau_n2
    110112      REAL tau_teta
    111113      REAL tetadpmean
     
    197199
    198200      REAL psmean                    ! pression moyenne
    199       REAL pqco2mean                 ! moyenne globale ps*qco
     201      REAL pqn2mean                 ! moyenne globale ps*qco
    200202      REAL p0                        ! pression de reference
    201203      REAL p00d                        ! globalaverage(kpd)
    202       REAL qmean_co2,qmean_co2_vert ! mass mean mixing ratio vap co2
    203       REAL pqco2(ip1jmp1)           ! average co2 mass index : ps*q_co2
     204      REAL qmean_n2,qmean_n2_vert ! mass mean mixing ratio vap n2
     205      REAL pqn2(ip1jmp1)           ! average n2 mass index : ps*q_n2
    204206      REAL oldps(ip1jmp1)           ! saving old pressure ps to calculate qch4
    205207
     
    239241
    240242      ! TEMP : diagnostic mass
    241       real :: co2mass(iip1,jjp1)
    242       real :: co2ice_ij(iip1,jjp1)
    243       integer,save :: igcm_co2=0 ! index of CO2 tracer (if any)
     243      real :: n2mass(iip1,jjp1)
     244      real :: n2ice_ij(iip1,jjp1)
     245      integer,save :: igcm_n2=0 ! index of CO2 tracer (if any)
    244246      integer :: i,j,ig
    245247      integer, parameter :: ngrid = 2+(jjm-1)*iim
     
    337339      p00d=globaverage2d(kpd) ! mean pres at ref level
    338340      tau_ps = 1. ! constante de rappel for pressure  (s)
    339       tau_co2 = 1.E5 !E5 ! constante de rappel for mix ratio qco2 (s)
     341      tau_n2 = 1.E5 !E5 ! constante de rappel for mix ratio qn2 (s)
    340342      tau_teta = 1.E7 !constante de rappel for potentiel temperature
    341343
    342 ! ED18 TEST
    343 !      PRINT*,'igcm_co2 = ',igcm_co2
    344 ! Locate tracer "co2" and set igcm_co2:
     344      PRINT*,'igcm_n2 = ',igcm_n2
    345345      do iq=1,nqtot
    346         if (tname(iq)=="co2") then
    347           igcm_co2=iq
     346        if (tname(iq)=="n2") then
     347          igcm_n2=iq
    348348          exit
    349349        endif
     
    475475     &          (itau+1)/day_step
    476476
    477            IF ((planet_type .eq."generic").or.
    478      &         (planet_type .eq."mars")) THEN
    479               ! AS: we make jD_cur to be pday
    480               jD_cur = int(day_ini + itau/day_step)
    481            ENDIF
     477           ! AS: we make jD_cur to be pday
     478           jD_cur = int(day_ini + itau/day_step)
    482479
    483480!           print*,'itau =',itau
     
    488485           jH_cur = jH_ref + start_time +                               &
    489486     &          mod(itau+1,day_step)/float(day_step)
    490            IF ((planet_type .eq."generic").or.
    491      &         (planet_type .eq."mars")) THEN
    492              jH_cur = jH_ref + start_time +                               &
     487           jH_cur = jH_ref + start_time +                               &
    493488     &          mod(itau,day_step)/float(day_step)
    494            ENDIF
    495489           jD_cur = jD_cur + int(jH_cur)
    496490           jH_cur = jH_cur - int(jH_cur)
     
    590584         DO l=1, llm
    591585           DO ij=1,ip1jmp1
    592               mq(ij,l) = masse(ij,l)*q(ij,l,igcm_co2)
     586              mq(ij,l) = masse(ij,l)*q(ij,l,igcm_n2)
    593587           ENDDO
    594588         ENDDO
     
    645639         DO l=1, llm
    646640           DO ij=1,ip1jmp1
    647               q(ij,l,igcm_co2) = mq(ij,l)/ masse(ij,l)
     641              q(ij,l,igcm_n2) = mq(ij,l)/ masse(ij,l)
    648642           ENDDO
    649643         ENDDO
     
    655649         ! Rappel newtonien vers psmean
    656650           psmean= globaverage2d(ps)  ! mean pressure
    657 !        ! increment q_co2  with physical tendancy
    658 !          IF (igcm_co2.ne.0) then
     651!        ! increment q_n2  with physical tendancy
     652!          IF (igcm_n2.ne.0) then
    659653!            DO l=1, llm
    660654!               DO ij=1,ip1jmp1
    661 !                q(ij,l,igcm_co2)=q(ij,l,igcm_co2)+
    662 !    &                    dqfi(ij,l,igcm_co2)*dtphys
     655!                q(ij,l,igcm_n2)=q(ij,l,igcm_n2)+
     656!    &                    dqfi(ij,l,igcm_n2)*dtphys
    663657!               ENDDO
    664658!            ENDDO
     
    667661c          Mixing CO2 vertically
    668662c          --------------------------
    669            if (igcm_co2.ne.0) then
     663           if (igcm_n2.ne.0) then
    670664            DO ij=1,ip1jmp1
    671                qmean_co2_vert=0.
     665               qmean_n2_vert=0.
    672666               DO l=1, llm
    673                  qmean_co2_vert= qmean_co2_vert
    674      &          + q(ij,l,igcm_co2)*( p(ij,l) - p(ij,l+1))
     667                 qmean_n2_vert= qmean_n2_vert
     668     &          + q(ij,l,igcm_n2)*( p(ij,l) - p(ij,l+1))
    675669               END DO
    676                qmean_co2_vert= qmean_co2_vert/ps(ij)
     670               qmean_n2_vert= qmean_n2_vert/ps(ij)
    677671               DO l=1, llm
    678                  q(ij,l,igcm_co2)= qmean_co2_vert
     672                 q(ij,l,igcm_n2)= qmean_n2_vert
    679673               END DO
    680674            END DO
     
    691685c        --------------------------------------------------------------------------------- 
    692686
    693          ! Simulate redistribution by dynamics for qco2
    694            if (igcm_co2.ne.0) then
     687         ! Simulate redistribution by dynamics for qn2
     688           if (igcm_n2.ne.0) then
    695689
    696690              DO ij=1,ip1jmp1
    697                  pqco2(ij)= ps(ij) * q(ij,1,igcm_co2)
     691                 pqn2(ij)= ps(ij) * q(ij,1,igcm_n2)
    698692              ENDDO
    699               pqco2mean=globaverage2d(pqco2)
    700 
    701          !    Rappel newtonien vers qco2_mean
    702               qmean_co2= pqco2mean / psmean
     693              pqn2mean=globaverage2d(pqn2)
     694
     695         !    Rappel newtonien vers qn2_mean
     696              qmean_n2= pqn2mean / psmean
    703697
    704698              DO ij=1,ip1jmp1
    705                   q(ij,1,igcm_co2)=q(ij,1,igcm_co2)+
    706      &                  (qmean_co2-q(ij,1,igcm_co2))*
    707      &                  (1.-exp(-dtphys/tau_co2))
     699                  q(ij,1,igcm_n2)=q(ij,1,igcm_n2)+
     700     &                  (qmean_n2-q(ij,1,igcm_n2))*
     701     &                  (1.-exp(-dtphys/tau_n2))
    708702              ENDDO
    709703
    710704              DO l=2, llm
    711705                 DO ij=1,ip1jmp1
    712                      q(ij,l,igcm_co2)=q(ij,1,igcm_co2)
     706                     q(ij,l,igcm_n2)=q(ij,1,igcm_n2)
    713707                 END DO
    714708              END DO
     
    716710!             TEMPORAIRE (ED)
    717711!             PRINT*,'psmean = ',psmean
    718 !             PRINT*,'qmean_co2 = ',qmean_co2
    719 !             PRINT*,'pqco2mean = ',pqco2mean
    720 !             PRINT*,'q(50,1,igcm_co2) = ',q(50,1,igcm_co2)
    721 !             PRINT*,'q(50,2,igcm_co2) = ',q(50,2,igcm_co2)
    722 !             PRINT*,'q(50,3,igcm_co2) = ',q(50,3,igcm_co2)
    723 
    724            endif ! igcm_co2.ne.0
     712!             PRINT*,'qmean_n2 = ',qmean_n2
     713!             PRINT*,'pqn2mean = ',pqn2mean
     714!             PRINT*,'q(50,1,igcm_n2) = ',q(50,1,igcm_n2)
     715!             PRINT*,'q(50,2,igcm_n2) = ',q(50,2,igcm_n2)
     716!             PRINT*,'q(50,3,igcm_n2) = ',q(50,3,igcm_n2)
     717
     718           endif ! igcm_n2.ne.0
    725719
    726720
     
    736730c          -------------------------------
    737731!          initialize variables that will be averaged
    738     !        DO l=1,llm
    739     !          DO ij=1,ip1jmp1
    740     !            dp(ij,l) = p(ij,l) - p(ij,l+1)
    741     !            tetadp(ij,l) = teta(ij,l)*dp(ij,l)
    742     !          ENDDO
    743     !        ENDDO
    744 
    745     !        DO l=1,llm
    746     !          tetadpmean = globaverage2d(tetadp(:,l))
    747     !          dpmean = globaverage2d(dp(:,l))
    748     !          tetamean = tetadpmean / dpmean
    749     !          DO ij=1,ip1jmp1
    750     !            teta(ij,l) = teta(ij,l) + (tetamean - teta(ij,l)) *
    751     ! &                      (1 - exp(-dtphys/tau_teta))
    752     !          ENDDO
    753     !        ENDDO
     732           DO l=1,llm
     733             DO ij=1,ip1jmp1
     734               dp(ij,l) = p(ij,l) - p(ij,l+1)
     735               tetadp(ij,l) = teta(ij,l)*dp(ij,l)
     736             ENDDO
     737           ENDDO
     738
     739           DO l=1,llm
     740             tetadpmean = globaverage2d(tetadp(:,l))
     741             dpmean = globaverage2d(dp(:,l))
     742             tetamean = tetadpmean / dpmean
     743             DO ij=1,ip1jmp1
     744               teta(ij,l) = teta(ij,l) + (tetamean - teta(ij,l)) *
     745    &                      (1 - exp(-dtphys/tau_teta))
     746             ENDDO
     747           ENDDO
    754748           
    755749
     
    867861            IF(itau.EQ.itaufin) THEN
    868862
    869               if (planet_type=="mars") then
    870                 CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
     863              CALL dynredem1("restart.nc",start_time,
    871864     &                         vcov,ucov,teta,q,masse,ps)
    872               else
    873                 CALL dynredem1("restart.nc",start_time,
    874      &                         vcov,ucov,teta,q,masse,ps)
    875               endif
    876865              CLOSE(99)
    877866              !!! Ehouarn: Why not stop here and now?
     
    997986
    998987              IF(itau.EQ.itaufin) THEN
    999                 if (planet_type=="mars") then
    1000                   CALL dynredem1("restart.nc",REAL(itau)/REAL(day_step),
    1001      &                         vcov,ucov,teta,q,masse,ps)
    1002                 else
    1003988                  CALL dynredem1("restart.nc",start_time,
    1004989     &                         vcov,ucov,teta,q,masse,ps)
    1005                 endif
    1006990              ENDIF ! of IF(itau.EQ.itaufin)
    1007991
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3390 r3411  
    17031703      ! Surface pressure.
    17041704      ps(1:ngrid) = pplev(1:ngrid,1) + pdpsrf(1:ngrid)*ptimestep
     1705      call globalaverage2d(ngrid,ps,globave)
    17051706
    17061707      ! pressure density !pluto specific
     
    23212322                              2,zdqssed(:,igcm_ch4_gas))
    23222323             endif
    2323              if (metcloud) then
     2324             if (metcloud.and.(.not.fast)) then
    23242325               call writediagfi(ngrid,"zdtch4cloud","ch4 cloud","T s-1",&
    23252326                           3,zdtch4cloud)
Note: See TracChangeset for help on using the changeset viewer.