Ignore:
Timestamp:
Jan 29, 2018, 12:10:20 PM (7 years ago)
Author:
jvatant
Message:

r1901 was still bugged with mufi tendencies multiplied
2 times by ptimestep !
+ Pass ptimestep to calmufi in order to have tendencies
in X.s-1 in output of the routine.
As YAMMS spits integrated tendencies it's the
only way to rectify the things.
--JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/calmufi.F90

    r1897 r1902  
    11
    22
    3 SUBROUTINE calmufi(plev, zlev, play, zlay, temp, pq, zdq)
     3SUBROUTINE calmufi(dt, plev, zlev, play, zlay, temp, pq, zdq)
    44  !! Interface subroutine to YAMMS model for Titan LMDZ GCM.
    55  !!
     
    2222  IMPLICIT NONE
    2323
     24  REAL(kind=8), INTENT(IN) :: dt  !! Physics timestep (s).
     25 
    2426  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: plev  !! Pressure levels (Pa).
    2527  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: zlev  !! Altitude levels (m).
     
    151153  END DO ! loop on ilon
    152154
     155  ! YAMMS gives a tendency which is integrated for all the timestep but in the GCM
     156  ! we want to have routines spitting tendencies in s-1 -> let's divide !
     157  zdq(:,:,:) = zdq(:,:,:) / dt
     158
    153159END SUBROUTINE calmufi
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1901 r1902  
    403403    !   Or one can put calmufi in MMP_GCM module (in muphytitan).
    404404    INTERFACE
    405       SUBROUTINE calmufi(plev, zlev, play, zlay, temp, pq, zdq)
     405      SUBROUTINE calmufi(dt, plev, zlev, play, zlay, temp, pq, zdq)
     406        REAL(kind=8), INTENT(IN)                 :: dt    !! Physics timestep (s).
    406407        REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: plev  !! Pressure levels (Pa).
    407408        REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: zlev  !! Altitude levels (m).
     
    11421143#ifdef USE_QTEST
    11431144               if (ngrid.eq.1) then ! We obviously don't have access to (and don't need) zonal means in 1D
    1144                   call calmufi(pplev,zzlev,pplay,zzlay,pt,tpq,zdqmufi)
     1145                  call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,tpq,zdqmufi)
    11451146               else
    1146                   call calmufi(zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,tpq,zdqmufi)
     1147                  call calmufi(ptimestep,zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,tpq,zdqmufi)
    11471148               endif
    1148                tpq(:,:,:) = tpq(:,:,:) + zdqmufi(1:ngrid,1:nlayer,1:nq)
     1149               tpq(:,:,:) = tpq(:,:,:) + zdqmufi(1:ngrid,1:nlayer,1:nq)*ptimestep ! only manipulation of tpq->*ptimesep here
    11491150#else
    11501151            ! Inside this routine we will split 2D->1D, intensive->extensive and separate different types of tracers
     
    11521153
    11531154               if (ngrid.eq.1) then ! We obviously don't have access to (and don't need) zonal means in 1D
    1154                   call calmufi(pplev,zzlev,pplay,zzlay,pt,pq,zdqmufi)
     1155                  call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,pt,pq,zdqmufi)
    11551156               else
    1156                   call calmufi(zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,pq,zdqmufi)
     1157                  call calmufi(ptimestep,zplevbar,zzlevbar,zplaybar,zzlaybar,ztfibar,pq,zdqmufi)
    11571158               endif
    11581159
    11591160            pdq(1:ngrid,1:nlayer,1:nq) = pdq(1:ngrid,1:nlayer,1:nq) + zdqmufi(1:ngrid,1:nlayer,1:nq)
    1160             ! We don't re-multiply by timestep, it is already taken into account in zdqmufi,
    1161             ! since inimufi has initialized YAMMS with a given ts.
    11621161#endif
    11631162         endif ! end of 'callmufi'
Note: See TracChangeset for help on using the changeset viewer.