source: LMDZ6/branches/Ocean_skin/libf/phylmd/open_climoz_m.F90 @ 3627

Last change on this file since 3627 was 2821, checked in by dcugnet, 7 years ago

Fix bug introduced in rev. 2820.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.3 KB
Line 
1! $Id$
2MODULE open_climoz_m
3
4  USE print_control_mod, ONLY: lunout
5  IMPLICIT NONE
6
7CONTAINS
8
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)
45
46  IF(is_mpi_root) THEN
47
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)
58
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.)]
62
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
82
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
89
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)
96
97END SUBROUTINE open_climoz
98!
99!-------------------------------------------------------------------------------
100
101END MODULE open_climoz_m
Note: See TracBrowser for help on using the repository browser.