Ignore:
Timestamp:
Mar 8, 2017, 3:34:12 PM (7 years ago)
Author:
dcugnet
Message:
  • Modification to allow previous convention climoz files (360 records for all calendars) to be handled again:
    • read_climoz=1 / 2 (tro3 only / tro3 and tro3_daylight) => 360 records file
    • read_climoz=3 / 4 (same) => daily (calendar compliant) file or monthly (14 records) file
  • Few fixes in the ozone forcing reading routine
File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/regr_pr_time_av_m.F90

    r2788 r2819  
    7171  LOGICAL, SAVE :: lO3Trop                         !--- Tropopause ozone flag
    7272  LOGICAL, SAVE :: lfirst=.TRUE.                   !--- First call flag
     73!$OMP THREADPRIVATE(lfirst)
    7374  REAL, PARAMETER :: co3(3)=[91.,28.,20.]          !--- Coeffs for o3 threshold
    7475  REAL, PARAMETER :: prtrop=5.E+3  !--- Value lower than the tropopause pressure
     
    7980!-------------------------------------------------------------------------------
    8081!
    81 SUBROUTINE regr_pr_time_av(fID, nam, julien, pint_in, pcen_ou, v3, time_in,    &
     82SUBROUTINE regr_pr_time_av(fID, nam, julien, pint_in, pint_ou, v3, time_in,    &
    8283                                     lat_in, pcen_in, ptrop_ou)
    8384!
     
    102103  CHARACTER(LEN=13), INTENT(IN) :: nam(:)     !--- NetCDF variables names
    103104  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)
     105  REAL,    INTENT(IN)  :: pint_in(:)    !--- Interfaces file Pres, Pa, ascending
     106  REAL,    INTENT(IN)  :: pint_ou(:,:)  !--- Interfaces LMDZ Pres, Pa (klon,llm+1)
    106107  REAL,    INTENT(OUT) :: v3(:,:,:)     !--- Regridded field (klon,llm,SIZE(nam))
    107108  REAL,    INTENT(IN), OPTIONAL :: time_in(:) !--- Records times, in days
    108109                                              !    since Jan 1 of current year
    109110  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 :: pcen_in(:) !--- Mid-layers file pressure
    111112  REAL,    INTENT(IN), OPTIONAL :: ptrop_ou(:)!--- Output tropopause pressure (klon)
    112113!-------------------------------------------------------------------------------
     
    136137!-------------------------------------------------------------------------------
    137138  sub="regr_pr_time_av"
     139  nlev_in=SIZE(pint_in)-1
    138140  CALL assert(SIZE(v3,1)==klon,                 TRIM(sub)//" v3 klon")
    139141  CALL assert(SIZE(v3,2)==nbp_lev,              TRIM(sub)//" v3 nbp_lev")
    140142  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")
     143  CALL assert(SHAPE(pint_ou)==[klon, nbp_lev+1],TRIM(sub)//" pint_ou")
    142144  IF(PRESENT(lat_in))   CALL assert(SIZE(lat_in  )==klon,TRIM(sub)//" lat_in klon")
    143145  IF(PRESENT(ptrop_ou)) CALL assert(SIZE(ptrop_ou)==klon,TRIM(sub)//" ptrop_ou klon")
     146  IF(PRESENT(pcen_in))  CALL assert(SIZE(pcen_in)==nlev_in,TRIM(sub)//" pcen_in")
    144147  ltrop=PRESENT(lat_in).AND.PRESENT(pcen_in).AND.PRESENT(ptrop_ou)
    145   nlev_in=SIZE(pint_in)-1
    146148
    147149  !$OMP MASTER
     
    162164        IF(lO3Trop) ALLOCATE(otm(nbp_lon,nbp_lat),otp(nbp_lon,nbp_lat))
    163165      END IF
    164       IF(PRESENT(pcen_in)) itrp0=locate(pcen_in,prtrop) !--- Above tropopause: 50hPa
     166      !--- INITIAL INDEX: LOCATE A LAYER WELL ABOVE TROPOPAUSE (50hPa)
     167      IF(PRESENT(pcen_in)) THEN
     168        itrp0=locate(pcen_in,prtrop)
     169      ELSE
     170        itrp0=locate(SQRT(pint_in(1:nlev_in)*pint_in(2:nlev_in+1)),prtrop)
     171      END IF
    165172      IF(lPrSurf) WRITE(*,*)' >> Using GROUND PRESSURE from input O3 forcing file.'
    166173      IF(linterp) WRITE(*,*)' >> Monthly O3 files => ONLINE TIME INTERPOLATION.'
     
    178185    !=== TIME INTERPOLATION FOR MONTHLY INPUT FILES
    179186    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)
     187      WRITE(*,'(3(a,f7.3))')'  >> Interpolating O3 at julian day ',julien,     &
     188      &' from forcing fields at times ',time_in(irec),' and ', time_in(irec+1)
    182189      al=(time_in(irec+1)-julien)/(time_in(irec+1)-time_in(irec))
    183190      v1=al*v1m+(1.-al)*v1p
     
    188195  END IF
    189196  !$OMP END MASTER
    190   !$OMP BARRIER
    191197  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
     198  CALL bcast(itrp0)
     199  !--- No "ps" in input file => assumed to be equal to current LMDZ ground press
     200  IF(lPrSurf) THEN; CALL scatter2d(ps1,ps2); ELSE; ps2=Pint_ou(:,1); END IF
    195201  IF(lPrTrop) CALL scatter2d(pt1,pt2)
    196202  IF(lO3Trop) CALL scatter2d(ot1,ot2)
     
    199205  IF(.NOT.ltrop) THEN
    200206    DO i=1,klon
    201       CALL regr_conserv(1,v2(i,:,:) , Pint_in , Pcen_ou(i,nbp_lev+1:1:-1),    &
     207      CALL regr_conserv(1,v2(i,:,:) , Pint_in , Pint_ou(i,nbp_lev+1:1:-1),    &
    202208                          v3(i,nbp_lev:1:-1,:), slopes(1,v2(i,:,:),pint_in))
    203209    END DO
     
    206212    DO i=1,klon
    207213      SigT_in = get_SigTrop(i,itrp)        !--- input  (file) tropopause
    208       SigT_ou = ptrop_ou(i)/pcen_ou(i,1)   !--- output (lmdz) tropopause
     214      SigT_ou = ptrop_ou(i)/pint_ou(i,1)   !--- output (lmdz) tropopause
    209215      SigT_mn = SQRT(SigT_in*SigT_ou)      !--- mean tropopause>strained domain
    210216
     
    221227      !--- STRAINED INPUT logP PROFILE ; alpha: MAX. STRETCH. EXPONENT INCREMENT
    222228      alpha = LOG(SigT_ou/SigT_in)/LOG(SigT_in)
    223       Pint_st(:) = pcen_ou(i,1) * Sig_in(:)**(1+alpha*phi(:))
     229      Pint_st(:) = pint_ou(i,1) * Sig_in(:)**(1+alpha*phi(:))
    224230
    225231      !--- REGRID INPUT PROFILE ON STRAINED VERTICAL LEVELS
    226       CALL regr_conserv(1,v2(i,:,:) , Pint_st,  Pcen_ou(i,nbp_lev+1:1:-1),     &
     232      CALL regr_conserv(1,v2(i,:,:) , Pint_st,  Pint_ou(i,nbp_lev+1:1:-1),     &
    227233                          v3(i,nbp_lev:1:-1,:), slopes(1,v2(i,:,:),Pint_st))
    228234    END DO
     
    275281  END IF
    276282  lfirst=.FALSE.
     283  CALL bcast(lfirst)
    277284
    278285END SUBROUTINE update_fields
     
    361368  REAL    :: prt                               !--- Air pressure   at tropopause
    362369  REAL    :: al                                !--- Interpolation coefficient
    363   REAL    :: y_frac                            !--- Elapsed year fraction
    364370  REAL    :: coef                              !--- Coef: North/South transition
    365371!-------------------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.