1 | ! $Id$ |
---|
2 | MODULE open_climoz_m |
---|
3 | |
---|
4 | USE lmdz_print_control, ONLY: lunout |
---|
5 | IMPLICIT NONE |
---|
6 | |
---|
7 | CONTAINS |
---|
8 | |
---|
9 | !------------------------------------------------------------------------------- |
---|
10 | |
---|
11 | SUBROUTINE 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 lmdz_phys_mpi_data, ONLY: is_mpi_root |
---|
17 | USE lmdz_phys_mpi_transfert, ONLY: bcast_mpi |
---|
18 | USE phys_cal_mod, ONLY: calend, year_len, year_cur |
---|
19 | USE lmdz_abort_physic, ONLY: abort_physic |
---|
20 | !------------------------------------------------------------------------------- |
---|
21 | ! Purpose: This procedure should be called once per "gcm" run, by a single |
---|
22 | ! thread of each MPI process. |
---|
23 | ! The root MPI process opens "climoz_LMDZ.nc", reads the pressure |
---|
24 | ! levels and the times and broadcasts them to the other processes. |
---|
25 | ! We assume that, in "climoz_LMDZ.nc", the pressure levels are in hPa |
---|
26 | ! and in strictly ascending order. |
---|
27 | !------------------------------------------------------------------------------- |
---|
28 | ! Arguments (OpenMP shared): |
---|
29 | INTEGER, INTENT(OUT) :: ncid !--- "climoz_LMDZ.nc" identifier |
---|
30 | REAL, ALLOCATABLE, INTENT(OUT) :: press_in_cen(:) !--- at cells centers |
---|
31 | REAL, ALLOCATABLE, INTENT(OUT) :: press_in_edg(:) !--- at the interfaces (pressure intervals) |
---|
32 | REAL, ALLOCATABLE, INTENT(OUT) :: time_in(:) !--- records times, in days since Jan. 1st |
---|
33 | LOGICAL, INTENT(IN) :: daily !--- daily files (calendar dependent days nb) |
---|
34 | LOGICAL, INTENT(IN) :: adjust !--- tropopause adjustement required |
---|
35 | ! pressure levels press_in_cen/edg are in Pa a,d strictly ascending order. |
---|
36 | ! time_in is only used for monthly files (14 records) |
---|
37 | !------------------------------------------------------------------------------- |
---|
38 | ! Local variables: |
---|
39 | INTEGER :: varid !--- NetCDF variables identifier |
---|
40 | INTEGER :: nlev, ntim !--- pressure levels and time records numbers |
---|
41 | CHARACTER(LEN = 80) :: sub |
---|
42 | CHARACTER(LEN = 320) :: msg |
---|
43 | !------------------------------------------------------------------------------- |
---|
44 | sub = "open_climoz" |
---|
45 | WRITE(lunout, *)"Entering routine " // TRIM(sub) |
---|
46 | |
---|
47 | IF(is_mpi_root) THEN |
---|
48 | |
---|
49 | !--- OPEN FILE, READ PRESSURE LEVELS AND TIME VECTOR |
---|
50 | CALL nf95_open("climoz_LMDZ.nc", nf90_nowrite, ncid) |
---|
51 | CALL nf95_inq_varid(ncid, "plev", varid) |
---|
52 | CALL nf95_gw_var(ncid, varid, press_in_cen) |
---|
53 | ! Convert from hPa to Pa because "paprs" and "pplay" are in Pa: |
---|
54 | press_in_cen = press_in_cen * 100. |
---|
55 | nlev = SIZE(press_in_cen) |
---|
56 | CALL nf95_inq_varid(ncID, "time", varID) |
---|
57 | CALL nf95_gw_var(ncid, varid, time_in) |
---|
58 | ntim = SIZE(time_in) |
---|
59 | |
---|
60 | !--- BUILD EDGES OF PRESSURE INTERVALS: HALFWAY IN LOGARITHMS |
---|
61 | ALLOCATE(press_in_edg(nlev + 1)) |
---|
62 | press_in_edg = [0., SQRT(press_in_cen(1:nlev - 1) * press_in_cen(2:nlev)), HUGE(0.)] |
---|
63 | |
---|
64 | !--- CHECK RECORDS NUMBER AND DISPLAY CORRESPONDING INFORMATION |
---|
65 | IF(daily.AND.ntim/=year_len) THEN |
---|
66 | WRITE(msg, '(a,3(i4,a))')TRIM(sub) // ': Expecting a daily ozone file with', & |
---|
67 | year_len, ' records (year ', year_cur, ') ; found ', ntim, ' instead' |
---|
68 | CALL abort_physic(sub, msg, 1) |
---|
69 | ELSE IF(ALL([360, 14]/=ntim)) THEN |
---|
70 | WRITE(msg, '(a,i4,a)')TRIM(sub) // ': Expecting an ozone file with 14 (mont'& |
---|
71 | // 'hly case) or 360 (old style files) records ; found ', ntim, ' instead' |
---|
72 | CALL abort_physic(sub, msg, 1) |
---|
73 | ELSE |
---|
74 | IF(daily) THEN |
---|
75 | WRITE(msg, '(a,2(i4,a))')'daily file (', ntim, ' days in ', year_cur, ')' |
---|
76 | ELSE IF(ntim==14) THEN |
---|
77 | msg = '14 records monthly file' |
---|
78 | ELSE |
---|
79 | msg = '360 records files (old convention)' |
---|
80 | END IF |
---|
81 | WRITE(lunout, *)TRIM(sub) // ': Using a ' // TRIM(msg) |
---|
82 | END IF |
---|
83 | |
---|
84 | !--- MESSAGE ABOUT OPTIONAL STRETCHING FOR TROPOPAUSES MATCHING |
---|
85 | IF(adjust) THEN |
---|
86 | WRITE(lunout, *)TRIM(sub) // ': Adjusting O3 field to match gcm tropopause.' |
---|
87 | ELSE |
---|
88 | WRITE(lunout, *)TRIM(sub) // ': Interpolating O3 field directly on gcm levels.' |
---|
89 | END IF |
---|
90 | |
---|
91 | END IF |
---|
92 | CALL bcast_mpi(nlev) |
---|
93 | IF(.NOT.is_mpi_root) ALLOCATE(press_in_cen(nlev)); CALL bcast_mpi(press_in_cen) |
---|
94 | IF(.NOT.is_mpi_root) ALLOCATE(press_in_edg(nlev + 1)); CALL bcast_mpi(press_in_edg) |
---|
95 | CALL bcast_mpi(ntim) |
---|
96 | IF(.NOT.is_mpi_root) ALLOCATE(time_in(ntim)); CALL bcast_mpi(time_in) |
---|
97 | |
---|
98 | END SUBROUTINE open_climoz |
---|
99 | |
---|
100 | !------------------------------------------------------------------------------- |
---|
101 | |
---|
102 | END MODULE open_climoz_m |
---|