[1154] | 1 | ! $Id$ |
---|
[2820] | 2 | MODULE open_climoz_m |
---|
[1154] | 3 | |
---|
[2820] | 4 | USE print_control_mod, ONLY: lunout |
---|
| 5 | IMPLICIT NONE |
---|
[1154] | 6 | |
---|
[2820] | 7 | CONTAINS |
---|
[1154] | 8 | |
---|
[2820] | 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 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 |
---|
[4489] | 29 | REAL, allocatable, intent(out):: press_in_cen(:) !--- at cells centers |
---|
| 30 | REAL, allocatable, INTENT(OUT):: press_in_edg(:) !--- at the interfaces (pressure intervals) |
---|
| 31 | REAL, allocatable, intent(out):: time_in(:) !--- records times, in days since Jan. 1st |
---|
[2820] | 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) |
---|
[1154] | 45 | |
---|
[2820] | 46 | IF(is_mpi_root) THEN |
---|
[1154] | 47 | |
---|
[2820] | 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) |
---|
[1154] | 58 | |
---|
[2820] | 59 | !--- BUILD EDGES OF PRESSURE INTERVALS: HALFWAY IN LOGARITHMS |
---|
| 60 | ALLOCATE(press_in_edg(nlev+1)) |
---|
[2821] | 61 | press_in_edg=[0.,SQRT(press_in_cen(1:nlev-1)*press_in_cen(2:nlev)),HUGE(0.)] |
---|
[1154] | 62 | |
---|
[2820] | 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)' |
---|
[2788] | 79 | END IF |
---|
[2820] | 80 | WRITE(lunout,*)TRIM(sub)//': Using a '//TRIM(msg) |
---|
| 81 | END IF |
---|
[2788] | 82 | |
---|
[2820] | 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 |
---|
[1154] | 89 | |
---|
[2820] | 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) |
---|
[2788] | 96 | |
---|
[2820] | 97 | END SUBROUTINE open_climoz |
---|
| 98 | ! |
---|
| 99 | !------------------------------------------------------------------------------- |
---|
[1154] | 100 | |
---|
[2820] | 101 | END MODULE open_climoz_m |
---|