Ignore:
Timestamp:
Nov 5, 2018, 3:24:59 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Undoing merge with trunk (r3356) to properly register Yann's latest modifications

Location:
LMDZ6/branches/DYNAMICO-conv
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv

  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/stratosphere_mask.F90

    r3356 r3411  
    22! $Id$
    33!
    4 SUBROUTINE stratosphere_mask(missing_val, pphis, t_seri, pplay, xlat)
     4SUBROUTINE stratosphere_mask(missing_val, t_seri, pplay, xlat)
    55
    66!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    88! determination of tropopause height and temperature from gridded temperature data
    99!
    10 ! reference: Reichler, T., M. Dameris, and R. Sausen (GRL, 10.1029/2003GL018240, 2003)
     10! reference: Reichler, T., M. Dameris, and R. Sausen (2003):
    1111! modified: 6/28/06 tjr
    1212! adapted to LMDZ by C. Kleinschmitt (2016-02-15)
    13 ! committed to LMDz by O. Boucher (2016) with a mistake
    14 ! mistake corrected by O. Boucher (2017-12-11)
    15 !
    16 ! input:  temp(nlon,nlat,nlev)  3D-temperature field
    17 !         ps(nlon,nlat)         2D-surface pressure field
    18 !         zs(nlon,nlat)         2D-surface height
    19 !         nlon                  grid points in x
    20 !         nlat                  grid points in y
    21 !         pfull(nlon,nlat,nlev) full pressure levels in Pa
    22 !         plimu                 upper limit for tropopause pressure
    23 !         pliml                 lower limit for tropopause pressure
    24 !         gamma                 tropopause criterion, e.g. -0.002 K/m
    25 !
    26 ! output: p_tropopause(klon)    tropopause pressure in Pa with missing values
    27 !         t_tropopause(klon)    tropopause temperature in K with missing values
    28 !         z_tropopause(klon)    tropopause height in m with missing values
    29 !         stratomask            stratospheric mask withtout missing values
    30 !         ifil                  # of undetermined values
     13!
     14! input:    temp(nlon,nlat,nlev)    3D-temperature field
     15!       ps(nlon,nlat)       2D-surface pressure field
     16!       zs(nlon,nlat)       2D-surface height
     17!       nlon            grid points in x
     18!       nlat            grid points in y
     19!       pfull(nlon,nlat,nlev)   full pressure levels in Pa
     20!       plimu           upper limit for tropopause pressure
     21!       pliml           lower limit for tropopause pressure
     22!       gamma           tropopause criterion, e.g. -0.002 K/m
     23!
     24! output:   p_tropopause(klon)     tropopause pressure in Pa with missing values
     25!           t_tropopause(klon)     tropopause temperature in K with missing values
     26!           z_tropopause(klon)     tropopause height in m with missing values
     27!           stratomask             stratospheric mask withtout missing values
     28!           ifil                  # of undetermined values
    3129!
    3230!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    3937IMPLICIT NONE
    4038
    41 INCLUDE "YOMCST.h"
    42 
    4339REAL, INTENT(IN)                       :: missing_val ! missing value, also XIOS
    44 REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! Geopotentiel de surface
    4540REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
    4641REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
     
    6560  ENDDO
    6661  psrf=pplay(i,1)
    67   zsrf=pphis(i)/RG           !--altitude de la surface
     62  zsrf=0.0
    6863  call twmo(missing_val, klev, t, p, psrf, zsrf, plimu, pliml, gamma, ptrp, ttrp, ztrp)
    6964  tp(i)=ptrp
     
    109104subroutine twmo(missing_val, level, t, p, ps, zs, plimu, pliml, gamma, ptrp, ttrp, ztrp)
    110105
    111 ! reference: Reichler, T., M. Dameris, and R. Sausen (GRL, 10.1029/2003GL018240, 2003)
    112 
    113106implicit none
    114107
     
    135128ztrp=missing_val
    136129
    137 faktor = -RG/RD
     130faktor = -RG/R
    138131
    139132do j=level,2,-1
     
    225218TDLNP = TDLNP + TM*DLNP
    226219
    227 ZTRP = ZS + TDLNP*RD/RG
    228 
    229 !!if (ZTRP .lt. 0) then
    230 !!  print*,'ZTRP=',ZTRP
    231 !!  print*,'PS=',PS
    232 !!  print*,'P=',P
    233 !!  print*,'T=',T
    234 !!  print*,'ZS=',ZS
    235 !!  stop
    236 !!endif
     220ZTRP = ZS + TDLNP*R/RG
     221
     222if (ZTRP .lt. 0) then
     223  print*,ZTRP
     224  print*,PS
     225  print*,P
     226  print*,T
     227  print*,ZS
     228  stop
     229endif
    237230
    238231return
Note: See TracChangeset for help on using the changeset viewer.