source: LMDZ5/trunk/libf/phylmd/regr_pr_time_av_m.F90 @ 2793

Last change on this file since 2793 was 2788, checked in by dcugnet, 8 years ago

Changes in ce0l about the way ozone forcing files are generated:

1) 3D raw input files "climoz.nc" are now handled.
2) Default behaviour is now to let the gcm interpolate in time online.

This helps to avoid huge forcing files (in particular for 3D fields).
In this case, the output files "climoz_LMDZ.nc" all have 14 records:

  • records 2-13 are obtained with records 1-12 of "climoz.nc".
  • records 1 and 14 are obtained respectively with:
    • record 12 of "climoz_m.nc" if available, of "climoz.nc" otherwise.
    • record 1 of "climoz_p.nc" if available, of "climoz.nc" otherwise.

3) If ok_daily_climoz key is TRUE, the time interpolation (one record

a day) is forced, using the 14 records described below.
This now depends on the calendar (it was on a 360 days basis only).

Changes in the gcm about the way zone forcing files are read/interpolated:

1) 3D horizontally interpolated "climoz_LMDZ.nc" files are now handled.
2) Daily files (already interpolated in time) are still handled, but their

number of records must match the expected number of days, that depends
on the calendar (records step is no longer 1/360 year).

3) 14 records monthly files are now handled (and prefered). This reduces

the I/O to a minimum and the aditional computational cost is low (simple
online linear time interpolation).

4) If adjust_tropopause key is TRUE, the input fields are stretched using

following method:

  • LMDZ dynamical tropopause is detected: Ptrop_lmdz = MAX ( P(Potential Vorticity==2PVU), P(theta==380K) )
  • file chemical tropopause is detected: Ptrop_file = P( tro3 == o3t ), where:

o3t = 91. + 28. * SIN(PI*(month-2)/6) (ppbV)

This formula comes from Thouret & al., ACP 6, 1033-1051, 2006.
The second term of the expression is multiplied by TANH(lat_deg/20.)
to account for latitude dependency.

  • File profile is streched in a +/- 5kms zone around the mean tropopause to ensure resulting tropopause matches the one of LMDZ. See procedure regr_pr_time_av for more details.
File size: 19.2 KB
Line 
1! $Id$
2MODULE regr_pr_time_av_m
3
4  USE write_field_phy
5  USE mod_phys_lmdz_transfert_para, ONLY: bcast
6  IMPLICIT NONE
7
8!-------------------------------------------------------------------------------
9! Purpose: Regrid pressure with an averaging method. Operations done:
10!  * on the root process: read a NetCDF 3D or 4D field at a given day.
11!  * pack the fields to the LMDZ "horizontal "physics" grid and scatter
12!    to all threads of all processes;
13!  * in all the threads of all the processes, regrid the fields in pressure
14!    to the LMDZ vertical grid.
15!  * input files fields are stretched in the viscinity (+/- 5 kms) of the mean
16!    tropopause (geometrical mean of LMDZ and input fields tropopauses) to force
17!    the resulting field tropopause height to the one of LMDZ. To switch this
18!    feature on, the following arguments must be present:
19!     - "lat_in":   input file latitudes.
20!     - "pcen_in":  input file cells center pressure levels.
21!     - "ptrop_ou": target grid (LMDZ) tropopause pressure.
22!    Note that the ozone quantity conservation is not ensured.
23!-------------------------------------------------------------------------------
24! Initial routine: regr_pr_av_m module (L. Guez).
25! Present version: David Cugnet ; corresponding additions:
26!    - time interpolation
27!    - 3D compliant
28!    - vertical stretching of the field to allow tropopause and ground pressure
29!      matching between input field and current lmdz field.
30!-------------------------------------------------------------------------------
31! Remarks:
32!  * 3D fields are zonal means, with dimensions (latitude, pressure, julian day)
33!  * 4D fields have the dimensions:  (longitude, latitude, pressure, julian day)
34!  * All the fields are already on the horizontal grid (rlatu) or (rlatu,rlonv),
35!    except that the latitudes are in ascending order in the input file.
36!  * We assume that all the input fields have the same coordinates.
37!  * The target vertical LMDZ grid is the grid of layer boundaries.
38!  * Regridding in pressure is conservative, second order.
39!  * All the fields are regridded as a single multi-dimensional array, so it
40!    saves CPU time to call this procedure once for several NetCDF variables
41!    rather than several times, each time for a single NetCDF variable.
42!  * The input file pressure at tropopause can be (in decreasing priority):
43!    1) read from the file if "tropopause_air_pressure" field is available.
44!    2) computed from the input file ozone field using:
45!       - o3 concentration at tropopause if "tro3_at_tropopause" is available.
46!       - a default value (100ppbv) if not.
47!  * If available, the field "ps" (input file pressure at surface) is used.
48!    If not, the current LMDZ ground pressure is taken instead.
49!  * The O3 threshold for tropopause is defined using 3 coefficients:
50!    o3t(ppbV)=co1+co2*SIN(PI*(month-2)/6)*TANH(lat_deg/c)
51!     => co1 and co2 are in ppmV, and co3 in degrees.
52!     => co3 allow a smooth transition between north and south hemispheres.
53!-------------------------------------------------------------------------------
54! * Fields with suffix "m"/"p" are at the closest records earlier/later than the
55!   middle of the julian day "julien", on the global "dynamics" horizontal grid.
56! * Fields(i,j,k,l) are at longitude-latitude "rlonv(i)-rlatu(j)", pressure
57!   interval "pint_in(k:k+1)]" and variable "nam(l)".
58! * In the 2D file case, the values are the same for all longitudes.
59! * The following fields are on the global "dynamics" grid, as read from files:
60  REAL,    SAVE, ALLOCATABLE :: v1m(:,:,:,:)       !--- Previous ozone fields
61  REAL,    SAVE, ALLOCATABLE :: v1p(:,:,:,:)       !--- Next ozone fields
62  REAL,    SAVE, ALLOCATABLE :: psm(:,:), psp(:,:) !--- Surface pressure
63  REAL,    SAVE, ALLOCATABLE :: ptm(:,:), ptp(:,:) !--- Tropopause pressure
64  REAL,    SAVE, ALLOCATABLE :: otm(:,:), otp(:,:) !--- Tropopause o3 mix. ratio
65  INTEGER, SAVE :: irec                            !--- Current time index
66!      * for daily   input files: current julian day number
67!      * for monthly input files: julien is in [time_in(irec),time_in(irec+1)]
68  LOGICAL, SAVE :: linterp                         !--- Interpolation in time
69  LOGICAL, SAVE :: lPrSurf                         !--- Surface pressure flag
70  LOGICAL, SAVE :: lPrTrop                         !--- Tropopause pressure flag
71  LOGICAL, SAVE :: lO3Trop                         !--- Tropopause ozone flag
72  LOGICAL, SAVE :: lfirst=.TRUE.                   !--- First call flag
73  REAL, PARAMETER :: co3(3)=[91.,28.,20.]          !--- Coeffs for o3 threshold
74  REAL, PARAMETER :: prtrop=5.E+3  !--- Value lower than the tropopause pressure
75  REAL, PARAMETER :: delta =5.     !--- Dist. around tropopause for strain (kms)
76
77CONTAINS
78
79!-------------------------------------------------------------------------------
80!
81SUBROUTINE regr_pr_time_av(fID, nam, julien, pint_in, pcen_ou, v3, time_in,    &
82                                     lat_in, pcen_in, ptrop_ou)
83!
84!-------------------------------------------------------------------------------
85  USE dimphy,         ONLY: klon
86  USE netcdf95,       ONLY: NF95_INQ_VARID, NF95_INQUIRE_VARIABLE, handle_err
87  USE netcdf,         ONLY: NF90_INQ_VARID, NF90_GET_VAR, NF90_NOERR
88  USE assert_m,       ONLY: assert
89  USE assert_eq_m,    ONLY: assert_eq
90  USE comvert_mod,    ONLY: scaleheight
91  USE interpolation,  ONLY: locate
92  USE regr_conserv_m, ONLY: regr_conserv
93  USE regr_lint_m,    ONLY: regr_lint
94  USE slopes_m,       ONLY: slopes
95  USE mod_phys_lmdz_mpi_data,       ONLY: is_mpi_root
96  USE mod_grid_phy_lmdz,            ONLY: nbp_lon, nbp_lat, nbp_lev
97  USE mod_phys_lmdz_transfert_para, ONLY: scatter2d, scatter
98  USE phys_cal_mod,                 ONLY: calend, year_len, days_elapsed, jH_cur
99!-------------------------------------------------------------------------------
100! Arguments:
101  INTEGER, INTENT(IN)  :: fID           !--- NetCDF file ID
102  CHARACTER(LEN=13), INTENT(IN) :: nam(:)     !--- NetCDF variables names
103  REAL,    INTENT(IN)  :: julien        !--- Days since Jan 1st
104  REAL,    INTENT(IN)  :: pint_in(:)    !--- Interfaces Pressure, Pa, ascending
105  REAL,    INTENT(IN)  :: pcen_ou(:,:)  !--- Mid-layers LMDZ Pres, Pa (klon,llm+1)
106  REAL,    INTENT(OUT) :: v3(:,:,:)     !--- Regridded field (klon,llm,SIZE(nam))
107  REAL,    INTENT(IN), OPTIONAL :: time_in(:) !--- Records times, in days
108                                              !    since Jan 1 of current year
109  REAL,    INTENT(IN), OPTIONAL :: lat_in(:)  !--- Input/output latitudes vector
110  REAL,    INTENT(IN), OPTIONAL :: pcen_in(:) !--- Mid-layers pressure
111  REAL,    INTENT(IN), OPTIONAL :: ptrop_ou(:)!--- Output tropopause pressure (klon)
112!-------------------------------------------------------------------------------
113! Local variables:
114  include "clesphys.h"
115  include "YOMCST.h"
116  CHARACTER(LEN=80)  :: sub
117  CHARACTER(LEN=320) :: msg
118  INTEGER :: vID, ncerr, n_var, nlev_in, ndim, i, ibot, itop, itrp, itrp0
119  LOGICAL :: ltrop                            !--- Need to adjust tropopause
120  REAL    :: y_frac                           !--- Elapsed year fraction
121  REAL    :: alpha, beta, al                  !--- For strectching/interpolation
122  REAL    :: SigT_in, SigT_ou, SigT_mn        !--- Tropopause: in/out/mean
123  REAL    :: SigA_bot, SigA_top               !--- Strained domain bounds
124  REAL    :: Sig_in (SIZE(pint_in))           !--- Input field sigma levels
125  REAL    :: phi    (SIZE(pint_in))           !--- Stretching exponent anomaly
126  REAl    :: Pint_st(SIZE(pint_in))           !--- Stretched pressure levels
127  REAL    :: v1(nbp_lon,nbp_lat,SIZE(pint_in)-1,SIZE(nam))
128  REAL    :: v2(klon,           SIZE(pint_in)-1,SIZE(nam))
129! v1: Field read/interpol at time "julien" on the global "dynamics" horiz. grid.
130! v2: Field scattered to the partial "physics" horizontal grid.
131!     In the 2D file case, the values are the same for all longitudes.
132!     "v2(i,    k, l)" is at longitude-latitude  "xlon(i)-xlat(i)".
133! Both are for pressure interval "press_in_edg(k:k+1)]" and variable "nam(l)"
134  REAL, DIMENSION(nbp_lon, nbp_lat) ::  ps1, pt1, ot1
135  REAL, DIMENSION(klon)             ::  ps2, pt2, ot2
136!-------------------------------------------------------------------------------
137  sub="regr_pr_time_av"
138  CALL assert(SIZE(v3,1)==klon,                 TRIM(sub)//" v3 klon")
139  CALL assert(SIZE(v3,2)==nbp_lev,              TRIM(sub)//" v3 nbp_lev")
140  n_var = assert_eq(SIZE(nam), SIZE(v3,3),      TRIM(sub)//" v3 n_var")
141  CALL assert(SHAPE(pcen_ou)==[klon, nbp_lev+1],TRIM(sub)//" pcen_ou")
142  IF(PRESENT(lat_in))   CALL assert(SIZE(lat_in  )==klon,TRIM(sub)//" lat_in klon")
143  IF(PRESENT(ptrop_ou)) CALL assert(SIZE(ptrop_ou)==klon,TRIM(sub)//" ptrop_ou klon")
144  ltrop=PRESENT(lat_in).AND.PRESENT(pcen_in).AND.PRESENT(ptrop_ou)
145  nlev_in=SIZE(pint_in)-1
146
147  !$OMP MASTER
148  IF(is_mpi_root) THEN
149
150    !=== CHECK WHICH FIELDS ARE AVAILABLE IN THE INPUT FILE
151    IF(lfirst) THEN
152      lPrSurf=NF90_INQ_VARID(fID,"ps"                     ,vID)==NF90_NOERR
153      lPrTrop=NF90_INQ_VARID(fID,"tropopause_air_pressure",vID)==NF90_NOERR
154      lO3Trop=NF90_INQ_VARID(fID,"tro3_at_tropopause"     ,vID)==NF90_NOERR
155      linterp=PRESENT(time_in)
156      IF(linterp) linterp=SIZE(time_in,1)==14
157      IF(linterp) THEN
158        ALLOCATE(v1m(nbp_lon,nbp_lat,nlev_in,n_var))
159        ALLOCATE(v1p(nbp_lon,nbp_lat,nlev_in,n_var))
160        ALLOCATE(psm(nbp_lon,nbp_lat),psp(nbp_lon,nbp_lat))
161        ALLOCATE(ptm(nbp_lon,nbp_lat),ptp(nbp_lon,nbp_lat))
162        IF(lO3Trop) ALLOCATE(otm(nbp_lon,nbp_lat),otp(nbp_lon,nbp_lat))
163      END IF
164      IF(PRESENT(pcen_in)) itrp0=locate(pcen_in,prtrop) !--- Above tropopause: 50hPa
165      IF(lPrSurf) WRITE(*,*)' >> Using GROUND PRESSURE from input O3 forcing file.'
166      IF(linterp) WRITE(*,*)' >> Monthly O3 files => ONLINE TIME INTERPOLATION.'
167      WRITE(*,*)' >> o3 forcing file tropopause location uses:'
168      IF(lPrTrop) THEN;      WRITE(*,*)'    PRESSURE AT TROPOPAUSE from file.'
169      ELSE IF(lO3Trop) THEN; WRITE(*,*)'    O3 CONCENTRATION AT TROPOPAUSE from file.'
170      ELSE;                  WRITE(*,*)'    PARAMETRIZATION of O3 concentration at tropopause.'
171      END IF
172    END IF
173
174    !=== UPDATE (ALWAYS FOR DAILY FILES, EACH MONTH FOR MONTHLY FILES)
175    IF(.NOT.linterp.OR.(linterp.AND.(lfirst.OR.julien>=time_in(irec+1)))) &
176      CALL update_fields()
177
178    !=== TIME INTERPOLATION FOR MONTHLY INPUT FILES
179    IF(linterp) THEN
180      WRITE(*,'(3(a,f7.3))')'  >> Interpolating O3 at julian day ',julien,' fr&
181      &om forcing fields at times ',time_in(irec),' and ', time_in(irec+1)
182      al=(time_in(irec+1)-julien)/(time_in(irec+1)-time_in(irec))
183      v1=al*v1m+(1.-al)*v1p
184      IF(lPrSurf) ps1=al*psm+(1.-al)*psp
185      IF(lPrTrop) pt1=al*ptm+(1.-al)*ptp
186      IF(lO3Trop) ot1=al*otm+(1.-al)*otp
187    END IF
188  END IF
189  !$OMP END MASTER
190  !$OMP BARRIER
191  CALL scatter2d(v1,v2)
192  IF(PRESENT(pcen_in)) CALL bcast(itrp0)
193  !--- "ps" not in input file => assume it is equal to current LMDZ value
194  IF(lPrSurf) THEN; CALL scatter2d(ps1,ps2); ELSE; ps2=pcen_ou(:,1); END IF
195  IF(lPrTrop) CALL scatter2d(pt1,pt2)
196  IF(lO3Trop) CALL scatter2d(ot1,ot2)
197
198  !--- REGRID IN PRESSURE ; 3rd index inverted because "paprs" is decreasing
199  IF(.NOT.ltrop) THEN
200    DO i=1,klon
201      CALL regr_conserv(1,v2(i,:,:) , Pint_in , Pcen_ou(i,nbp_lev+1:1:-1),    &
202                          v3(i,nbp_lev:1:-1,:), slopes(1,v2(i,:,:),pint_in))
203    END DO
204  ELSE
205    y_frac=(REAL(days_elapsed)+jH_cur)/year_len
206    DO i=1,klon
207      SigT_in = get_SigTrop(i,itrp)        !--- input  (file) tropopause
208      SigT_ou = ptrop_ou(i)/pcen_ou(i,1)   !--- output (lmdz) tropopause
209      SigT_mn = SQRT(SigT_in*SigT_ou)      !--- mean tropopause>strained domain
210
211      !--- DEFINE THE VERTICAL LAYER IN WHICH THE PROFILE IS STRECHED
212      beta=EXP(delta/scaleheight); Sig_in(:) = [pint_in(1:nlev_in)/ps2(i),1.]
213      SigA_bot = SigT_mn*beta ; ibot=locate(Sig_in(:),SigA_bot)
214      SigA_top = SigT_mn/beta ; itop=locate(Sig_in(:),SigA_top)+1
215
216      !--- HAT FUNCTION phi (/=0 in [SigA_bot,SigA_top] only)
217      phi(:)=0.
218      phi(itop:itrp)=(Sig_in(itop:itrp)-SigA_top)/(SigT_in-SigA_top)
219      phi(itrp:ibot)=(SigA_bot-Sig_in(itrp:ibot))/(SigA_bot-SigT_in)
220
221      !--- STRAINED INPUT logP PROFILE ; alpha: MAX. STRETCH. EXPONENT INCREMENT
222      alpha = LOG(SigT_ou/SigT_in)/LOG(SigT_in)
223      Pint_st(:) = pcen_ou(i,1) * Sig_in(:)**(1+alpha*phi(:))
224
225      !--- REGRID INPUT PROFILE ON STRAINED VERTICAL LEVELS
226      CALL regr_conserv(1,v2(i,:,:) , Pint_st,  Pcen_ou(i,nbp_lev+1:1:-1),     &
227                          v3(i,nbp_lev:1:-1,:), slopes(1,v2(i,:,:),Pint_st))
228    END DO
229  END IF
230
231
232CONTAINS
233
234
235!-------------------------------------------------------------------------------
236!
237SUBROUTINE update_fields()
238!
239!-------------------------------------------------------------------------------
240  IF(.NOT.linterp) THEN                 !=== DAILY FILES: NO TIME INTERPOLATION
241    WRITE(*,*)' >> Updating Ozone forcing field: read from file.'
242    irec=INT(julien)+1                  !--- irec is just the julian day number
243    CALL get_3Dfields(v1)               !--- Read ozone field(s)
244    IF(ltrop) THEN                      !--- Additional files for fields strain
245      IF(lPrSurf) CALL get_2Dfield(ps1,"ps")
246      IF(lPrTrop) CALL get_2Dfield(pt1,"tropopause_air_pressure")
247      IF(lO3Trop) CALL get_2Dfield(ot1,"tro3_at_tropopause")
248    END IF
249  ELSE                                  !=== MONTHLY FILES: GET 2 NEAREST RECS
250    WRITE(*,*)' >> Refreshing adjacent Ozone forcing fields.'
251    IF(lfirst) THEN                     !=== READ EARLIEST TIME FIELDS
252      irec=locate(time_in,julien)       !--- Need to locate surrounding times
253      CALL get_3Dfields(v1m)            !--- Read ozone field(s)
254      IF(ltrop) THEN                    !--- Additional files for fields strain
255        IF(lPrSurf) CALL get_2Dfield(psm,"ps")
256        IF(lPrTrop) CALL get_2Dfield(ptm,"tropopause_air_pressure")
257        IF(lO3Trop) CALL get_2Dfield(otm,"tro3_at_tropopause")
258      END IF
259    ELSE                                !=== SHIFT FIELDS
260      v1m=v1p                           !--- Ozone fields
261      IF(ltrop) THEN                    !--- Additional files for fields strain
262        IF(lPrSurf) psm=psp             !--- Surface pressure
263        IF(lPrTrop) ptm=ptp             !--- Tropopause pressure
264        IF(lO3Trop) otm=otp             !--- Tropopause ozone
265      END IF
266    END IF
267    irec=irec+1
268    CALL get_3Dfields(v1p)              !--- Read ozone field(s)
269    IF(ltrop) THEN                      !--- Additional files for fields strain
270      IF(lPrSurf) CALL get_2Dfield(psp,"ps")
271      IF(lPrTrop) CALL get_2Dfield(ptp,"tropopause_air_pressure")
272      IF(lO3Trop) CALL get_2Dfield(otp,"tro3_at_tropopause")
273    END IF
274    IF(lfirst) irec=irec-1
275  END IF
276  lfirst=.FALSE.
277
278END SUBROUTINE update_fields
279!
280!-------------------------------------------------------------------------------
281
282
283!-------------------------------------------------------------------------------
284!
285SUBROUTINE get_2Dfield(v,var)
286!
287!-------------------------------------------------------------------------------
288! Purpose: Shortcut to get the "irec"th record of the surface field named "var"
289!          from the input file.
290! Remark: In case the field is zonal, it is duplicated along first dimension.
291!-------------------------------------------------------------------------------
292! Arguments:
293  REAL,             INTENT(INOUT) :: v(:,:)
294  CHARACTER(LEN=*), INTENT(IN)    :: var
295!-------------------------------------------------------------------------------
296  CALL NF95_INQ_VARID(fID, TRIM(var), vID)
297  CALL NF95_INQUIRE_VARIABLE(fID, vID, ndims=ndim)
298  IF(ndim==2) ncerr=NF90_GET_VAR(fID,vID,v(1,:), start=[  1,irec])
299  IF(ndim==3) ncerr=NF90_GET_VAR(fID,vID,v(:,:), start=[1,1,irec])
300  CALL handle_err(TRIM(sub)//" NF90_GET_VAR "//TRIM(var),ncerr,fID)
301
302  !--- Flip latitudes: ascending in input file, descending in "rlatu".
303  IF(ndim==3) THEN
304    v(1,:) = v(1,nbp_lat:1:-1)
305    v(2:,:)= SPREAD(v(1,:),DIM=1,ncopies=nbp_lon-1)  !--- Duplication
306  ELSE
307    v(:,:) = v(:,nbp_lat:1:-1)
308  END IF
309
310END SUBROUTINE get_2Dfield
311!
312!-------------------------------------------------------------------------------
313
314
315!-------------------------------------------------------------------------------
316!
317SUBROUTINE get_3Dfields(v)
318!
319!-------------------------------------------------------------------------------
320! Purpose: Shortcut to get the "irec"th record of the 3D fields named "nam"
321!          from the input file. Fields are stacked on fourth dimension.
322! Remark: In case the field is zonal, it is duplicated along first dimension.
323!-------------------------------------------------------------------------------
324! Arguments:
325  REAL, INTENT(INOUT) :: v(:,:,:,:)
326!-------------------------------------------------------------------------------
327  DO i=1,SIZE(nam)
328    CALL NF95_INQ_VARID(fID, TRIM(nam(i)), vID)
329    CALL NF95_INQUIRE_VARIABLE(fID, vID, ndims=ndim)
330    IF(ndim==3) ncerr=NF90_GET_VAR(fID,vID,v(1,:,:,i), start=[  1,1,irec])
331    IF(ndim==4) ncerr=NF90_GET_VAR(fID,vID,v(:,:,:,i), start=[1,1,1,irec])
332    CALL handle_err(TRIM(sub)//" NF90_GET_VAR "//TRIM(nam(i)),ncerr,fID)
333  END DO
334
335  !--- Flip latitudes: ascending in input file, descending in "rlatu".
336  IF(ndim==3) THEN
337    v(1,:,:,:) = v(1,nbp_lat:1:-1,:,:)
338    v(2:,:,:,:)= SPREAD(v(1,:,:,:),DIM=1,ncopies=nbp_lon-1)  !--- Duplication
339  ELSE
340    v(:,:,:,:) = v(:,nbp_lat:1:-1,:,:)
341  END IF
342
343END SUBROUTINE get_3Dfields
344!
345!-------------------------------------------------------------------------------
346
347
348!-------------------------------------------------------------------------------
349!
350FUNCTION get_SigTrop(ih,it)
351!
352!-------------------------------------------------------------------------------
353! Arguments:
354  INTEGER, INTENT(IN)  :: ih
355  INTEGER, INTENT(OUT) :: it
356  REAL                 :: get_Sigtrop
357!-------------------------------------------------------------------------------
358! Local variables:
359  INTEGER :: ii                                !--- Idx of layer containing o3t
360  REAL    :: o3t                               !--- Ozone concent. at tropopause
361  REAL    :: prt                               !--- Air pressure   at tropopause
362  REAL    :: al                                !--- Interpolation coefficient
363  REAL    :: y_frac                            !--- Elapsed year fraction
364  REAL    :: coef                              !--- Coef: North/South transition
365!-------------------------------------------------------------------------------
366  !--- DETERMINE PRESSURE AT TROPOPAUSE AND DIVIDE IT BY GROUND PRESSURE
367  IF(lPrTrop) THEN                             !--- PrTrop KNOWN FROM FILE
368    get_SigTrop=pt2(ih)/ps2(ih)
369    it=locate(pint_in(:),pt2(ih))
370  ELSE                                         !--- O3 THRESHOLD
371    coef = TANH(lat_in(i)/co3(3))              !--- Latitude dependant ponderat.
372    coef = SIN (2.*RPI*(y_frac-1./6.)) * coef  !--- Time-dependant ponderation
373    o3t  = 1.E-9 * (co3(1)+co3(2)*coef)        !--- Value from parametrization
374    IF(lO3Trop) o3t=ot2(ih)                    !--- Value from file
375    !--- Starts from 50hPa and go down.
376    it=itrp0; DO WHILE(v2(ih,it+1,1)>=o3t); it=it+1; END DO
377    al=(v2(ih,it,1)-o3t)/(v2(ih,it,1)-v2(ih,it+1,1))
378    get_SigTrop = ( pcen_in(it)**(1.-al) * pcen_in(it+1)**al )/ps2(ih)
379  END IF
380
381END FUNCTION get_SigTrop
382!
383!-------------------------------------------------------------------------------
384
385
386END SUBROUTINE regr_pr_time_av
387!
388!-------------------------------------------------------------------------------
389
390END MODULE regr_pr_time_av_m
Note: See TracBrowser for help on using the repository browser.