Ignore:
Timestamp:
Mar 30, 2017, 4:16:38 PM (7 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2785:2838 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/open_climoz_m.F90

    r1910 r2839  
    11! $Id$
    2 module open_climoz_m
     2MODULE open_climoz_m
    33
    4   implicit none
     4  USE print_control_mod, ONLY: lunout
     5  IMPLICIT NONE
    56
    6 contains
     7CONTAINS
    78
    8   subroutine open_climoz(ncid, press_in_edg)
     9!-------------------------------------------------------------------------------
     10!
     11SUBROUTINE open_climoz(ncid, press_in_cen, press_in_edg, time_in, daily, adjust)
     12!
     13!-------------------------------------------------------------------------------
     14  USE netcdf95, ONLY: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid
     15  USE netcdf,   ONLY: nf90_nowrite
     16  USE mod_phys_lmdz_mpi_data,      ONLY: is_mpi_root
     17  USE mod_phys_lmdz_mpi_transfert, ONLY: bcast_mpi
     18  USE phys_cal_mod,                ONLY: calend, year_len, year_cur
     19!-------------------------------------------------------------------------------
     20! Purpose: This procedure should be called once per "gcm" run, by a single
     21!          thread of each MPI process.
     22!          The root MPI process opens "climoz_LMDZ.nc", reads the pressure
     23! levels and the times and broadcasts them to the other processes.
     24!          We assume that, in "climoz_LMDZ.nc", the pressure levels are in hPa
     25! and in strictly ascending order.
     26!-------------------------------------------------------------------------------
     27! Arguments (OpenMP shared):
     28  INTEGER, INTENT(OUT):: ncid      !--- "climoz_LMDZ.nc" identifier
     29  REAL, POINTER :: press_in_cen(:) !--- at cells centers
     30  REAL, POINTER :: press_in_edg(:) !--- at the interfaces (pressure intervals)
     31  REAL, POINTER :: time_in(:)      !--- records times, in days since Jan. 1st
     32  LOGICAL, INTENT(IN) :: daily     !--- daily files (calendar dependent days nb)
     33  LOGICAL, INTENT(IN) :: adjust    !--- tropopause adjustement required
     34!   pressure levels press_in_cen/edg are in Pa a,d strictly ascending order.
     35!   time_in is only used for monthly files (14 records)
     36!-------------------------------------------------------------------------------
     37! Local variables:
     38  INTEGER :: varid                 !--- NetCDF variables identifier
     39  INTEGER :: nlev, ntim            !--- pressure levels and time records numbers
     40  CHARACTER(LEN=80)  :: sub
     41  CHARACTER(LEN=320) :: msg
     42!-------------------------------------------------------------------------------
     43  sub="open_climoz"
     44  WRITE(lunout,*)"Entering routine "//TRIM(sub)
    945
    10     ! This procedure should be called once per "gcm" run, by a single
    11     ! thread of each MPI process.
    12     ! The root MPI process opens "climoz_LMDZ.nc", reads the pressure
    13     ! levels and broadcasts them to the other processes.
     46  IF(is_mpi_root) THEN
    1447
    15     ! We assume that, in "climoz_LMDZ.nc", the pressure levels are in hPa
    16     ! and in strictly ascending order.
     48    !--- OPEN FILE, READ PRESSURE LEVELS AND TIME VECTOR
     49    CALL nf95_open("climoz_LMDZ.nc", nf90_nowrite, ncid)
     50    CALL nf95_inq_varid(ncid, "plev", varid)
     51    CALL nf95_gw_var(ncid, varid, press_in_cen)
     52    ! Convert from hPa to Pa because "paprs" and "pplay" are in Pa:
     53    press_in_cen = press_in_cen * 100.
     54    nlev = SIZE(press_in_cen)
     55    CALL NF95_INQ_VARID(ncID, "time", varID)
     56    CALL NF95_GW_VAR(ncid, varid, time_in)
     57    ntim = SIZE(time_in)
    1758
    18     use netcdf95, only: nf95_open, nf95_close, nf95_gw_var, nf95_inq_varid
    19     use netcdf, only: nf90_nowrite
     59    !--- BUILD EDGES OF PRESSURE INTERVALS: HALFWAY IN LOGARITHMS
     60    ALLOCATE(press_in_edg(nlev+1))
     61    press_in_edg=[0.,SQRT(press_in_cen(1:nlev-1)*press_in_cen(2:nlev)),HUGE(0.)]
    2062
    21     use mod_phys_lmdz_mpi_data, only: is_mpi_root
    22     use mod_phys_lmdz_mpi_transfert, only: bcast_mpi ! broadcast
     63    !--- CHECK RECORDS NUMBER AND DISPLAY CORRESPONDING INFORMATION
     64    IF(daily.AND.ntim/=year_len) THEN
     65      WRITE(msg,'(a,3(i4,a))')TRIM(sub)//': Expecting a daily ozone file with',&
     66     &year_len,' records (year ',year_cur,') ; found ',ntim,' instead'
     67      CALL abort_physic(sub, msg, 1)
     68    ELSE IF(ALL([360,14]/=ntim)) THEN
     69      WRITE(msg,'(a,i4,a)')TRIM(sub)//': Expecting an ozone file with 14 (mont'&
     70     &//'hly case) or 360 (old style files) records ; found ',ntim,' instead'
     71      CALL abort_physic(sub, msg, 1)
     72    ELSE
     73      IF(daily) THEN
     74         WRITE(msg,'(a,2(i4,a))')'daily file (',ntim,' days in ',year_cur,')'
     75       ELSE IF(ntim==14) THEN
     76         msg='14 records monthly file'
     77       ELSE
     78         msg='360 records files (old convention)'
     79       END IF
     80      WRITE(lunout,*)TRIM(sub)//': Using a '//TRIM(msg)
     81    END IF
    2382
    24     integer, intent(out):: ncid ! of "climoz_LMDZ.nc", OpenMP shared
     83    !--- MESSAGE ABOUT OPTIONAL STRETCHING FOR TROPOPAUSES MATCHING
     84    IF(adjust) THEN
     85      WRITE(lunout,*)TRIM(sub)//': Adjusting O3 field to match gcm tropopause.'
     86    ELSE
     87      WRITE(lunout,*)TRIM(sub)//': Interpolating O3 field directly on gcm levels.'
     88    END IF
    2589
    26     real, pointer:: press_in_edg(:)
    27     ! edges of pressure intervals for ozone climatology, in Pa, in strictly
    28     ! ascending order, OpenMP shared
     90  END IF
     91  CALL bcast_mpi(nlev)
     92  IF(.NOT.is_mpi_root) ALLOCATE(press_in_cen(nlev  )); CALL bcast_mpi(press_in_cen)
     93  IF(.NOT.is_mpi_root) ALLOCATE(press_in_edg(nlev+1)); CALL bcast_mpi(press_in_edg)
     94  CALL bcast_mpi(ntim)
     95  IF(.NOT.is_mpi_root) ALLOCATE(time_in(ntim));        CALL bcast_mpi(time_in)
    2996
    30     ! Variables local to the procedure:
     97END SUBROUTINE open_climoz
     98!
     99!-------------------------------------------------------------------------------
    31100
    32     real, pointer:: plev(:)
    33     ! (pressure levels for ozone climatology, converted to Pa, in strictly
    34     ! ascending order)
    35 
    36     integer varid ! for NetCDF
    37     integer n_plev ! number of pressure levels in the input data
    38     integer k
    39 
    40     !---------------------------------------
    41 
    42     print *, "Call sequence information: open_climoz"
    43 
    44     if (is_mpi_root) then
    45        call nf95_open("climoz_LMDZ.nc", nf90_nowrite, ncid)
    46 
    47        call nf95_inq_varid(ncid, "plev", varid)
    48        call nf95_gw_var(ncid, varid, plev)
    49        ! Convert from hPa to Pa because "paprs" and "pplay" are in Pa:
    50        plev = plev * 100.
    51        n_plev = size(plev)
    52     end if
    53 
    54     call bcast_mpi(n_plev)
    55     if (.not. is_mpi_root) allocate(plev(n_plev))
    56     call bcast_mpi(plev)
    57    
    58     ! Compute edges of pressure intervals:
    59     allocate(press_in_edg(n_plev + 1))
    60     if (is_mpi_root) then
    61        press_in_edg(1) = 0.
    62        ! We choose edges halfway in logarithm:
    63        forall (k = 2:n_plev) press_in_edg(k) = sqrt(plev(k - 1) * plev(k))
    64        press_in_edg(n_plev + 1) = huge(0.)
    65        ! (infinity, but any value guaranteed to be greater than the
    66        ! surface pressure would do)
    67     end if
    68     call bcast_mpi(press_in_edg)
    69     deallocate(plev) ! pointer
    70 
    71   end subroutine open_climoz
    72 
    73 end module open_climoz_m
     101END MODULE open_climoz_m
Note: See TracChangeset for help on using the changeset viewer.