Ignore:
Timestamp:
Mar 4, 2019, 4:03:08 PM (6 years ago)
Author:
jvatant
Message:

Fix some problems for the microphysics :
+ Altitude of the last level at 1e7m from physics was certainly source of divergence
+ Sanity check for negative is moved from within mm_microphysic to the end of calmufi avoiding rounding pbs
--JVO

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

Legend:

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

    r1947 r2109  
    3131  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: temp  !! Temperature at the center of each layer (K).
    3232
    33   REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: pq    !! Tracers (\(kg.kg^{-1}}\)).
    34   REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: zdqfi !! Tendency from former processes for tracers (\(kg.kg^{-1}}\)).
    35   REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdq   !! Microphysical tendency for tracers (\(kg.kg^{-1}}\)).
     33  REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: pq    !! Tracers (\(X.kg^{-1}}\)).
     34  REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: zdqfi !! Tendency from former processes for tracers (\(X.kg^{-1}}\)).
     35  REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdq   !! Microphysical tendency for tracers (\(X.kg^{-1}}\)).
    3636 
    37   REAL(kind=8), DIMENSION(:,:,:), ALLOCATABLE :: zq !! Local tracers updated from former processes (\(kg.kg^{-1}}\)).
     37  REAL(kind=8), DIMENSION(:,:,:), ALLOCATABLE :: zq !! Local tracers updated from former processes (\(X.kg^{-1}}\)).
    3838 
    3939  REAL(kind=8), DIMENSION(:), ALLOCATABLE :: m0as !! 0th order moment of the spherical mode (\(m^{-2}\)).
     
    5656  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: dgazs !! Tendencies of each condensible gaz species !(\(mol.mol^{-1}\)).
    5757
    58   REAL(kind=8), DIMENSION(:,:), ALLOCATABLE ::  int2ext
     58  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE ::  int2ext !! (\(m^{-2}\)).
    5959  TYPE(error) :: err
    6060
     
    165165      enddo
    166166    endif
     167
     168    ! Sanity check ( way safer to be done here rather than within YAMMS )
     169    WHERE (zq+zdq < 0.0) ; zdq = -zq ; END WHERE
     170
    167171  END DO ! loop on ilon
    168172
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r2098 r2109  
    10821082 
    10831083         if (callmufi) then
     1084            zzlev(:,nlayer+1)=zzlay(:,nlayer)+(zzlay(:,nlayer)-zzlev(:,nlayer)) ! JVO 19 : We assume zzlev isn't reused later on
    10841085#ifdef USE_QTEST
    10851086            dtpq(:,:,:) = 0.0 ! we want tpq to go only through mufi
     
    10871088            tpq(:,:,:) = tpq(:,:,:) + zdqmufi(:,:,:)*ptimestep ! only manipulation of tpq->*ptimestep here
    10881089#else
    1089             call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,gzlat,pt,pq,pdq,zdqmufi) ! JVO 19 : To be fixed, what altitude do we need ?
     1090            call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,gzlat,pt,pq,pdq,zdqmufi)
    10901091            pdq(:,:,:) = pdq(:,:,:) + zdqmufi(:,:,:)
    10911092#endif
Note: See TracChangeset for help on using the changeset viewer.