GCC Code Coverage Report


Directory: ./
File: phys/regr_horiz_time_climoz_m.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 0 288 0.0%
Branches: 0 999 0.0%

Line Branch Exec Source
1 MODULE regr_horiz_time_climoz_m
2
3 USE interpolation, ONLY: locate
4 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid_type, unstructured
5 USE nrtype, ONLY: pi
6 USE netcdf, ONLY: NF90_CLOBBER, NF90_FLOAT, NF90_GET_VAR, NF90_OPEN, &
7 NF90_NOWRITE, NF90_NOERR, NF90_GET_ATT, NF90_GLOBAL
8 USE netcdf95, ONLY: NF95_DEF_DIM, NF95_INQ_DIMID, NF95_INQUIRE_DIMENSION, &
9 NF95_DEF_VAR, NF95_INQ_VARID, NF95_INQUIRE_VARIABLE, &
10 NF95_OPEN, NF95_CREATE, NF95_GET_ATT, NF95_GW_VAR, HANDLE_ERR, &
11 NF95_CLOSE, NF95_ENDDEF, NF95_PUT_ATT, NF95_PUT_VAR, NF95_COPY_ATT
12 USE print_control_mod, ONLY: lunout
13 USE dimphy
14 IMPLICIT NONE
15 PRIVATE
16 PUBLIC :: regr_horiz_time_climoz
17 REAL, PARAMETER :: deg2rad=pi/180.
18 CHARACTER(LEN=13), PARAMETER :: vars_in(2)=['tro3 ','tro3_daylight']
19
20 INTEGER :: nlat_ou, nlon_ou
21 REAL, ALLOCATABLE :: latitude_glo(:)
22 !$OMP THREADPRIVATE(latitude_glo)
23 INTEGER, ALLOCATABLE :: ind_cell_glo_glo(:)
24 !$OMP THREADPRIVATE(ind_cell_glo_glo)
25
26 CONTAINS
27
28 !-------------------------------------------------------------------------------
29 !
30 SUBROUTINE regr_horiz_time_climoz(read_climoz,interpt)
31 !
32 !-------------------------------------------------------------------------------
33 ! Purpose: Regrid horizontally and in time zonal or 3D ozone climatologies.
34 ! * Read ozone climatology from netcdf file
35 ! * Regrid it horizontaly to LMDZ grid (quasi-conservative method)
36 ! * If interpt=T, interpolate linearly in time (one record each day)
37 ! If interpt=F, keep original time sampling (14 months).
38 ! * Save it to a new netcdf file.
39 !-------------------------------------------------------------------------------
40 ! Remarks:
41 ! * Up to 2 variables treated: "tro3" and "tro3_daylight" (if read_climoz=2)
42 ! * Input fields coordinates: (longitudes, latitudes, pressure_levels, time)
43 ! * Output grid cells centers coordinates given by [rlonv,] rlatu.
44 ! * Output grid cells edges coordinates given by [rlonu,] rlatv.
45 ! * Input file [longitudes and] latitudes given in degrees.
46 ! * Input file pressure levels are given in Pa or hPa.
47 ! * All coordinates variables are stricly monotonic.
48 ! * Monthly fields are interpolated linearly in time to get daily values.
49 ! * Fields are known at the middle of the months, so interpolation requires an
50 ! additional record both for 1st half of january and 2nd half of december:
51 ! - For a 14-records "climoz.nc": records 1 and 14.
52 ! - For 12-records files:
53 ! record 12 of "climoz_m.nc" if available, or record 1 of "climoz.nc".
54 ! record 1 of "climoz_p.nc" if available, or record 12 of "climoz.nc".
55 ! * Calendar is taken into account to get one record each day (not 360 always).
56 ! * Missing values are filled in from sky to ground by copying lowest valid one.
57 ! Attribute "missing_value" or "_FillValue" must be present in input file.
58 !-------------------------------------------------------------------------------
59 USE assert_m, ONLY: assert
60 USE cal_tools_m, ONLY: year_len, mid_month
61 !! USE control_mod, ONLY: anneeref
62 USE time_phylmdz_mod, ONLY: annee_ref
63 USE ioipsl, ONLY: ioget_year_len, ioget_calendar
64 USE regr_conserv_m, ONLY: regr_conserv
65 USE regr_lint_m, ONLY: regr_lint
66 USE regular_lonlat_mod, ONLY: boundslon_reg, boundslat_reg, south, west, east
67 USE slopes_m, ONLY: slopes
68 USE mod_phys_lmdz_para, ONLY: is_mpi_root, is_master, is_omp_master, gather, gather_mpi, bcast_mpi, klon_mpi
69 USE geometry_mod, ONLY : latitude_deg, ind_cell_glo
70 USE mod_grid_phy_lmdz, ONLY: klon_glo
71
72 !-------------------------------------------------------------------------------
73 ! Arguments:
74 INTEGER, INTENT(IN) :: read_climoz ! read ozone climatology, 1 or 2
75 ! 1: read a single ozone climatology used day and night
76 ! 2: same + read also a daylight climatology
77 LOGICAL, INTENT(IN) :: interpt ! TRUE => daily interpolation
78 ! FALSE => no interpolation (14 months)
79 !-------------------------------------------------------------------------------
80 ! Local variables:
81
82 !--- Input files variables
83 INTEGER :: nlon_in ! Number of longitudes
84 INTEGER :: nlat_in ! Number of latitudes
85 INTEGER :: nlev_in ! Number of pressure levels
86 INTEGER :: nmth_in ! Number of months
87 REAL, POINTER :: lon_in(:) ! Longitudes (ascending order, rad)
88 REAL, POINTER :: lat_in(:) ! Latitudes (ascending order, rad)
89 REAL, POINTER :: lev_in(:) ! Pressure levels (ascen. order, hPa)
90 REAL, ALLOCATABLE :: lon_in_edge(:) ! Longitude intervals edges
91 ! (ascending order, / )
92 REAL, ALLOCATABLE :: sinlat_in_edge(:) ! Sinus of latitude intervals edges
93 ! (ascending order, / )
94 LOGICAL :: ldec_lon, ldec_lat, ldec_lev ! Decreasing order in input file
95 CHARACTER(LEN=20) :: cal_in ! Calendar
96 REAL, ALLOCATABLE :: o3_in3(:,:,:,:,:) ! Ozone climatologies
97 REAL, ALLOCATABLE :: o3_in3bis(:,:,:,:,:) ! Ozone climatologies
98 REAL, ALLOCATABLE :: o3_in2 (:,:,:,:) ! Ozone climatologies
99 REAL, ALLOCATABLE :: o3_in2bis(:,:,:,:,:) ! Ozone climatologies
100 ! last index: 1 for the day-night average, 2 for the daylight field.
101 REAL :: NaN
102
103 !--- Partially or totally regridded variables (:,:,nlev_in,:,read_climoz)
104 REAL, ALLOCATABLE :: o3_regr_lon (:,:,:,:,:) ! (nlon_ou,nlat_in,:,0:13 ,:)
105 REAL, ALLOCATABLE :: o3_regr_lonlat(:,:,:,:,:) ! (nlon_ou,nlat_ou,:,0:13 ,:)
106 REAL, ALLOCATABLE :: o3_out3 (:,:,:,:,:) ! (nlon_ou,nlat_ou,:,ntim_ou,:)
107 REAL, ALLOCATABLE :: o3_out3_glo (:,:,:,:) ! (nbp_lat,:,ntim_ou,:)
108 REAL, ALLOCATABLE :: o3_regr_lat (:,:,:,:) ! (nlat_in,:,0:13 ,:)
109 REAL, ALLOCATABLE :: o3_out2 (:,:,:,:) ! (nlat_ou,:,ntim_ou,:)
110 REAL, ALLOCATABLE :: o3_out2_glo (:,:,:,:) ! (nbp_lat,:,ntim_ou,:)
111 REAL, ALLOCATABLE :: o3_out (:,:,:,:) ! (nbp_lat,:,ntim_ou,:)
112 ! Dimension number | Interval | Contains | For variables:
113 ! 1 (longitude) | [rlonu(i-1), rlonu(i)] | rlonv(i) | all
114 ! 2 (latitude) | [rlatv(j), rlatv(j-1)] | rlatu(j) | all but o3_regr_lon
115 ! 3 (press level) | | lev(k) | all
116 ! Note that rlatv(0)=pi/2 and rlatv(nlat_ou)=-pi/2.
117 ! Dimension 4 is: month number (all vars but o3_out)
118 ! days elapsed since Jan. 1st 0h at mid-day (o3_out only)
119 REAL, ALLOCATABLE :: v1(:)
120
121 !--- For NetCDF:
122 INTEGER :: fID_in_m, fID_in, levID_ou, dimid, vID_in(read_climoz), ntim_ou
123 INTEGER :: fID_in_p, fID_ou, timID_ou, varid, vID_ou(read_climoz), ndims, ncerr
124 INTEGER, POINTER :: dIDs(:)
125 CHARACTER(LEN=20) :: cal_ou !--- Calendar; no time inter => same as input
126 CHARACTER(LEN=80) :: press_unit !--- Pressure unit
127 REAL :: tmidmonth(0:13) !--- Elapsed days since Jan-1 0h at mid-months
128 ! Additional records 0, 13 for interpolation
129 REAL, ALLOCATABLE :: tmidday(:) !--- Output times (mid-days since Jan 1st 0h)
130 LOGICAL :: lprev, lnext !--- Flags: previous/next files are present
131 LOGICAL :: l3D, l2D !--- Flag: input fields are 3D or zonal
132 INTEGER :: ii, i, j, k, l, m, dln, ib, ie, iv, dx1, dx2
133 INTEGER, ALLOCATABLE :: sta(:), cnt(:)
134 CHARACTER(LEN=80) :: sub, dim_nam, msg
135 REAL :: null_array(0)
136 LOGICAL,SAVE :: first=.TRUE.
137 !$OMP THREADPRIVATE(first)
138 REAL, ALLOCATABLE :: test_o3_in(:,:)
139 REAL, ALLOCATABLE :: test_o3_out(:)
140
141
142 IF (grid_type==unstructured) THEN
143 IF (first) THEN
144 IF (is_master) THEN
145 ALLOCATE(latitude_glo(klon_glo))
146 ALLOCATE(ind_cell_glo_glo(klon_glo))
147 ELSE
148 ALLOCATE(latitude_glo(0))
149 ALLOCATE(ind_cell_glo_glo(0))
150 ENDIF
151 CALL gather(latitude_deg, latitude_glo)
152 CALL gather(ind_cell_glo, ind_cell_glo_glo)
153 ENDIF
154 ENDIF
155
156 IF (is_omp_master) THEN
157 nlat_ou=nbp_lat
158 nlon_ou=nbp_lon
159
160 !-------------------------------------------------------------------------------
161 IF (is_mpi_root) THEN
162 sub="regr_horiz_time_climoz"
163 WRITE(lunout,*)"Call sequence information: "//TRIM(sub)
164 CALL assert(read_climoz == 1 .OR. read_climoz == 2, "regr_lat_time_climoz")
165
166 CALL NF95_OPEN("climoz.nc" , NF90_NOWRITE, fID_in)
167 lprev=NF90_OPEN("climoz_m.nc", NF90_NOWRITE, fID_in_m)==NF90_NOERR
168 lnext=NF90_OPEN("climoz_p.nc", NF90_NOWRITE, fID_in_p)==NF90_NOERR
169
170 !--- Get coordinates from the input file. Converts lon/lat in radians.
171 ! Few inversions because "regr_conserv" and gcm need ascending vectors.
172 CALL NF95_INQ_VARID(fID_in, vars_in(1), varid)
173 CALL NF95_INQUIRE_VARIABLE(fID_in, varid, dimids=dIDs, ndims=ndims)
174 l3D=ndims==4; l2D=ndims==3
175 IF(l3D) WRITE(lunout,*)"Input files contain full 3D ozone fields."
176 IF(l2D) WRITE(lunout,*)"Input files contain zonal 2D ozone fields."
177 DO i=1,ndims
178 CALL NF95_INQUIRE_DIMENSION(fID_in, dIDs(i), name=dim_nam, nclen=dln)
179 CALL NF95_INQ_VARID(fID_in, dim_nam, varid)
180 ii=i; IF(l2D) ii=i+1 !--- ndims==3:NO LONGITUDE
181 SELECT CASE(ii)
182 CASE(1) !--- LONGITUDE
183 CALL NF95_GW_VAR(fID_in, varid, lon_in)
184 ldec_lon=lon_in(1)>lon_in(dln); IF(ldec_lon) lon_in=lon_in(dln:1:-1)
185 nlon_in=dln; lon_in=lon_in*deg2rad
186 CASE(2) !--- LATITUDE
187 CALL NF95_GW_VAR(fID_in, varid, lat_in)
188 ldec_lat=lat_in(1)>lat_in(dln); IF(ldec_lat) lat_in=lat_in(dln:1:-1)
189 nlat_in=dln; lat_in=lat_in*deg2rad
190 CASE(3) !--- PRESSURE LEVELS
191 CALL NF95_GW_VAR(fID_in, varid, lev_in)
192 ldec_lev=lev_in(1)>lev_in(dln); IF(ldec_lev) lev_in=lev_in(dln:1:-1)
193 nlev_in=dln
194 CALL NF95_GET_ATT(fID_in, varid, "units", press_unit)
195 k=LEN_TRIM(press_unit)
196 DO WHILE(ICHAR(press_unit(k:k))==0)
197 press_unit(k:k)=' '; k=LEN_TRIM(press_unit) !--- REMOVE NULL END CHAR
198 END DO
199 IF(press_unit == "Pa") THEN
200 lev_in = lev_in/100. !--- CONVERT TO hPa
201 ELSE IF(press_unit /= "hPa") THEN
202 CALL abort_physic(sub, "the only recognized units are Pa and hPa.",1)
203 END IF
204 CASE(4) !--- TIME
205 CALL NF95_INQUIRE_DIMENSION(fID_in, dIDs(i), nclen=nmth_in)
206 cal_in='gregorian'
207 IF(NF90_GET_ATT(fID_in, varid, 'calendar', cal_in)/=NF90_NOERR) &
208 WRITE(lunout,*)'WARNING: missing "calendar" attribute for "'// &
209 TRIM(dim_nam)//'" in "climoz.nc". Choosing default: "gregorian".'
210 k=LEN_TRIM(cal_in)
211 DO WHILE(ICHAR(cal_in(k:k))==0)
212 cal_in(k:k)=' '; k=LEN_TRIM(cal_in) !--- REMOVE NULL END CHAR
213 END DO
214 END SELECT
215 END DO
216
217 !--- Prepare quantities for time interpolation
218 tmidmonth=mid_month(annee_ref, cal_in)
219 IF(interpt) THEN
220 ntim_ou=ioget_year_len(annee_ref)
221 ALLOCATE(tmidday(ntim_ou))
222 tmidday=[(REAL(k)-0.5,k=1,ntim_ou)]
223 CALL ioget_calendar(cal_ou)
224 ELSE
225 ntim_ou=14
226 cal_ou=cal_in
227 END IF
228 ENDIF
229
230 IF (grid_type==unstructured) THEN
231 CALL bcast_mpi(nlon_in)
232 CALL bcast_mpi(nlat_in)
233 CALL bcast_mpi(nlev_in)
234 CALL bcast_mpi(l3d)
235 CALL bcast_mpi(tmidmonth)
236 CALL bcast_mpi(tmidday)
237 CALL bcast_mpi(ntim_ou)
238
239
240 IF (first) THEN
241 first=.FALSE.
242 RETURN
243 ENDIF
244 ENDIF
245
246
247 IF (is_mpi_root) THEN
248 !--- Longitudes management:
249 ! * Need to shift data if the origin of input file longitudes /= -pi
250 ! * Need to add some margin in longitude to ensure input interval contains
251 ! all the output intervals => at least one longitudes slice has to be
252 ! duplicated, possibly more for undersampling.
253 IF(l3D) THEN
254 IF (grid_type==unstructured) THEN
255 dx2=0
256 ELSE
257 !--- Compute input edges longitudes vector (no end point yet)
258 ALLOCATE(v1(nlon_in+1))
259 v1(1)=(lon_in(nlon_in)+lon_in(1))/2.-pi
260 FORALL(i=2:nlon_in) v1(i)=(lon_in(i-1)+lon_in(i))/2.
261 v1(nlon_in+1)=v1(1)+2.*pi
262 DEALLOCATE(lon_in)
263
264 !--- Shift input longitudes vector until it contains first output point boundslon_reg(1,west)
265 v1=v1+2*pi*REAL(FLOOR((boundslon_reg(1,west)-v1(1))/(2.*pi)))
266
267 !--- Ensure first input longitudes interval contains first output point boundslon_reg(1,west)
268 dx1=locate(v1,boundslon_reg(1,west))-1
269 v1=CSHIFT(v1,SHIFT=dx1,DIM=1)
270 v1(nlon_in-dx1+2:)=v1(nlon_in-dx1+2:)+2.*pi
271
272 !--- Extend input longitudes vector until last interval contains boundslon_reg(nlat_ou,east)
273 dx2=0; DO WHILE(v1(1+dx2)+2.*pi<=boundslon_reg(nlon_ou,east)); dx2=dx2+1; END DO
274
275 !--- Final edges longitudes vector (with margin and end point)
276 ALLOCATE(lon_in_edge(nlon_in+dx2+1)); lon_in_edge=[v1,v1(2:1+dx2)+2.*pi]
277 DEALLOCATE(v1)
278 ENDIF
279 END IF
280
281 !--- Compute sinus of intervals edges latitudes:
282 ALLOCATE(sinlat_in_edge(nlat_in+1))
283 sinlat_in_edge(1) = -1. ; sinlat_in_edge(nlat_in+1) = 1.
284 FORALL(j=2:nlat_in) sinlat_in_edge(j)=SIN((lat_in(j-1)+lat_in(j))/2.)
285 DEALLOCATE(lat_in)
286
287
288
289 !--- Check for contiguous years:
290 ib=0; ie=13
291 IF(nmth_in == 14) THEN; lprev=.FALSE.; lnext=.FALSE.
292 WRITE(lunout,*)'Using 14 months ozone climatology "climoz.nc"...'
293 ELSE
294 IF( lprev) WRITE(lunout,*)'Using "climoz_m.nc" last record (previous year).'
295 IF(.NOT.lprev) WRITE(lunout,*)"No previous year file ; assuming periodicity."
296 IF( lnext) WRITE(lunout,*)'Using "climoz_p.nc" first record (next year).'
297 IF(.NOT.lnext) WRITE(lunout,*)"No next year file ; assuming periodicity."
298 IF(.NOT.lprev) ib=1
299 IF(.NOT.lnext) ie=12
300 END IF
301 ALLOCATE(sta(ndims),cnt(ndims)); sta(:)=1
302 IF(l3D) cnt=[nlon_in,nlat_in,nlev_in,1]
303 IF(l2D) cnt=[ nlat_in,nlev_in,1]
304 IF(l3D) ALLOCATE(o3_in3(nlon_in+dx2,nlat_in,nlev_in,ib:ie,read_climoz))
305 IF(l2D) ALLOCATE(o3_in2( nlat_in,nlev_in,ib:ie,read_climoz))
306
307 !--- Read full current file and one record each available contiguous file
308 DO iv=1,read_climoz
309 msg=TRIM(sub)//" NF90_GET_VAR "//TRIM(vars_in(iv))
310 CALL NF95_INQ_VARID(fID_in, vars_in(1), vID_in(iv))
311 IF(l3D) ncerr=NF90_GET_VAR(fID_in, vID_in(iv), o3_in3(1:nlon_in,:,:,1:12,iv))
312 IF(l2D) ncerr=NF90_GET_VAR(fID_in, vID_in(iv), o3_in2( :,:,1:12,iv))
313 CALL handle_err(TRIM(msg), ncerr, fID_in)
314 IF(lprev) THEN; sta(ndims)=12
315 CALL NF95_INQ_VARID(fID_in_m, vars_in(1), vID_in(iv))
316 IF(l3D) ncerr=NF90_GET_VAR(fID_in_m,vID_in(iv),o3_in3(1:nlon_in,:,:, 0,iv),sta,cnt)
317 IF(l2d) ncerr=NF90_GET_VAR(fID_in_m,vID_in(iv),o3_in2( :,:, 0,iv),sta,cnt)
318 CALL handle_err(TRIM(msg)//" previous", ncerr, fID_in_m)
319 END IF
320 IF(lnext) THEN; sta(ndims)=1
321 CALL NF95_INQ_VARID(fID_in_p, vars_in(1), vID_in(iv))
322 IF(l3D) ncerr=NF90_GET_VAR(fID_in_p,vID_in(iv),o3_in3(1:nlon_in,:,:,13,iv),sta,cnt)
323 IF(l2D) ncerr=NF90_GET_VAR(fID_in_p,vID_in(iv),o3_in2( :,:,13,iv),sta,cnt)
324 CALL handle_err(TRIM(msg)//" next", ncerr, fID_in_p)
325 END IF
326 END DO
327 IF(lprev.OR.lnext) DEALLOCATE(sta,cnt)
328 IF(lprev) CALL NF95_CLOSE(fID_in_m)
329 IF(lnext) CALL NF95_CLOSE(fID_in_p)
330
331 !--- Revert decreasing coordinates vector
332 IF(l3D) THEN
333 IF(ldec_lon) o3_in3(1:nlon_in,:,:,:,:) = o3_in3(nlon_in:1:-1,:,:,:,:)
334 IF(ldec_lat) o3_in3 = o3_in3(:,nlat_in:1:-1,:,:,:)
335 IF(ldec_lev) o3_in3 = o3_in3(:,:,nlev_in:1:-1,:,:)
336
337 IF (grid_type /= unstructured) THEN
338 !--- Shift values for longitude and duplicate some longitudes slices
339 o3_in3(1:nlon_in,:,:,:,:)=CSHIFT(o3_in3(1:nlon_in,:,:,:,:),SHIFT=dx1,DIM=1)
340 o3_in3(nlon_in+1:nlon_in+dx2,:,:,:,:)=o3_in3(1:dx2,:,:,:,:)
341 ENDIF
342 ELSE
343 IF(ldec_lat) o3_in2 = o3_in2( nlat_in:1:-1,:,:,:)
344 IF(ldec_lev) o3_in2 = o3_in2( :,nlev_in:1:-1,:,:)
345 END IF
346
347 !--- Deal with missing values
348 DO m=1, read_climoz
349 WRITE(msg,'(a,i0)')"regr_lat_time_climoz: field Nr.",m
350 IF(NF90_GET_ATT(fID_in,vID_in(m),"missing_value",NaN)/= NF90_NOERR) THEN
351 IF(NF90_GET_ATT(fID_in, vID_in(m),"_FillValue",NaN)/= NF90_NOERR) THEN
352 WRITE(lunout,*)TRIM(msg)//": no missing value attribute found."; CYCLE
353 END IF
354 END IF
355 WRITE(lunout,*)TRIM(msg)//": missing value attribute found."
356 WRITE(lunout,*)"Trying to fill in NaNs ; a full field would be better."
357
358 !--- Check top layer contains no NaNs & search NaNs from top to ground
359 msg=TRIM(sub)//": NaNs in top layer !"
360 IF(l3D) THEN
361 IF(ANY(o3_in3(:,:,1,:,m)==NaN)) CALL abort_physic(sub,msg,1)
362 DO k = 2,nlev_in
363 WHERE(o3_in3(:,:,k,:,m)==NaN) o3_in3(:,:,k,:,m)=o3_in3(:,:,k-1,:,m)
364 END DO
365 ELSE
366 IF(ANY(o3_in2( :,1,:,m)==NaN)) THEN
367 WRITE(lunout,*)msg
368 !--- Fill in latitudes where all values are missing
369 DO l=1,nmth_in
370 !--- Next to south pole
371 j=1; DO WHILE(o3_in2(j,1,l,m)==NaN); j=j+1; END DO
372 IF(j>1) &
373 o3_in2(:j-1,:,l,m)=SPREAD(o3_in2(j,:,l,m),DIM=1,ncopies=j-1)
374 !--- Next to north pole
375 j=nlat_in; DO WHILE(o3_in2(j,1,l,m)==NaN); j=j+1; END DO
376 IF(j<nlat_in) &
377 o3_in2(j+1:,:,l,m)=SPREAD(o3_in2(j,:,l,m),DIM=1,ncopies=nlat_in-j)
378 END DO
379 END IF
380
381 !--- Fill in high latitudes missing values
382 !--- Highest level been filled-in, so has always valid values.
383 DO k = 2,nlev_in
384 WHERE(o3_in2(:,k,:,m)==NaN) o3_in2(:,k,:,m)=o3_in2(:,k-1,:,m)
385 END DO
386 END IF
387 END DO
388
389 ENDIF
390
391 !=============================================================================
392 IF(l3D) THEN !=== 3D FIELDS
393 !=============================================================================
394 IF (grid_type==unstructured) THEN
395 ELSE
396
397 !--- Regrid in longitude
398 ALLOCATE(o3_regr_lon(nlon_ou, nlat_in, nlev_in, ie-ib+1, read_climoz))
399 CALL regr_conserv(1, o3_in3, xs = lon_in_edge, &
400 xt = [boundslon_reg(1,west),boundslon_reg(:,east)], &
401 vt = o3_regr_lon, slope = slopes(1,o3_in3, lon_in_edge))
402 DEALLOCATE(o3_in3)
403
404 !--- Regrid in latitude: averaging with respect to SIN(lat) is
405 ! equivalent to weighting by COS(lat)
406 !--- (inverted indices in "o3_regr_lonlat" because "rlatu" is decreasing)
407 ALLOCATE(o3_regr_lonlat(nlon_ou, nlat_ou, nlev_in, 0:13, read_climoz))
408 CALL regr_conserv(2, o3_regr_lon, xs = sinlat_in_edge, &
409 xt = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.], &
410 vt = o3_regr_lonlat(:,nlat_ou:1:- 1,:,ib:ie,:), &
411 slope = slopes(2,o3_regr_lon, sinlat_in_edge))
412 DEALLOCATE(o3_regr_lon)
413
414 ENDIF
415
416 !--- Duplicate previous/next record(s) if they are not available
417 IF(.NOT.lprev) o3_regr_lonlat(:,:,:, 0,:) = o3_regr_lonlat(:,:,:,12,:)
418 IF(.NOT.lnext) o3_regr_lonlat(:,:,:,13,:) = o3_regr_lonlat(:,:,:, 1,:)
419
420 !--- Regrid in time by linear interpolation:
421 ALLOCATE(o3_out3(nlon_ou, nlat_ou, nlev_in, ntim_ou, read_climoz))
422 IF( interpt) CALL regr_lint(4,o3_regr_lonlat,tmidmonth,tmidday,o3_out3)
423 IF(.NOT.interpt) o3_out3=o3_regr_lonlat
424 DEALLOCATE(o3_regr_lonlat)
425
426 nlat_ou=nbp_lat
427 IF (grid_type==unstructured) THEN
428 ENDIF
429
430 !--- Create the output file and get the variable IDs:
431 CALL prepare_out(fID_in,nlev_in,ntim_ou, fID_ou,levID_ou,timID_ou,vID_ou, &
432 ndims, cal_ou)
433
434 IF (is_mpi_root) THEN
435 !--- Write remaining coordinate variables:
436 CALL NF95_PUT_VAR(fID_ou, levID_ou, lev_in); DEALLOCATE(lev_in)
437 IF( interpt) CALL NF95_PUT_VAR(fID_ou, timID_ou, tmidday)
438 IF(.NOT.interpt) CALL NF95_PUT_VAR(fID_ou, timID_ou, tmidmonth)
439
440 !--- Write to file (the order of "rlatu" is inverted in the output file):
441 IF (grid_type==unstructured) THEN
442
443 ALLOCATE(o3_out(nlat_ou, nlev_in, ntim_ou, read_climoz))
444 DO i=1,klon_glo
445 o3_out(ind_cell_glo_glo(i),:,:,:)=o3_out3_glo(i,:,:,:)
446 ENDDO
447
448 DO m = 1, read_climoz
449 CALL NF95_PUT_VAR(fID_ou, vID_ou(m), o3_out(nlat_ou:1:-1,:,:,m))
450 END DO
451
452 ELSE
453 DO m = 1, read_climoz
454 CALL NF95_PUT_VAR(fID_ou, vID_ou(m), o3_out3(:,nlat_ou:1:-1,:,:,m))
455 END DO
456 ENDIF
457 CALL NF95_CLOSE(fID_ou)
458
459
460 ENDIF
461
462
463 !=============================================================================
464 ELSE !=== ZONAL FIELDS
465 !=============================================================================
466
467 IF (grid_type==unstructured) THEN
468
469 ELSE
470 !--- Regrid in latitude: averaging with respect to SIN(lat) is
471 ! equivalent to weighting by COS(lat)
472 !--- (inverted indices in "o3_regr_lat" because "rlatu" is decreasing)
473 ALLOCATE(o3_regr_lat(nlat_ou, nlev_in, 0:13, read_climoz))
474 CALL regr_conserv(1, o3_in2, xs = sinlat_in_edge, &
475 xt = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.], &
476 vt = o3_regr_lat(nlat_ou:1:- 1,:,ib:ie,:), &
477 slope = slopes(1,o3_in2, sinlat_in_edge))
478 DEALLOCATE(o3_in2)
479
480 !--- Duplicate previous/next record(s) if they are not available
481 IF(.NOT.lprev) o3_regr_lat(:,:, 0,:) = o3_regr_lat(:,:,12,:)
482 IF(.NOT.lnext) o3_regr_lat(:,:,13,:) = o3_regr_lat(:,:, 1,:)
483
484 ENDIF
485
486 !--- Regrid in time by linear interpolation:
487 ALLOCATE(o3_out2(nlat_ou, nlev_in, ntim_ou, read_climoz))
488 IF( interpt) CALL regr_lint(3,o3_regr_lat, tmidmonth, tmidday, o3_out2)
489 IF(.NOT.interpt) o3_out2=o3_regr_lat
490 DEALLOCATE(o3_regr_lat)
491
492 nlat_ou=nbp_lat
493
494 IF (grid_type==unstructured) THEN
495 ndims=3
496 ALLOCATE(o3_out2_glo(nlat_ou, nlev_in, ntim_ou, read_climoz))
497 CALL gather_mpi(o3_out2, o3_out2_glo)
498 ENDIF
499
500 !--- Create the output file and get the variable IDs:
501 CALL prepare_out(fID_in,nlev_in,ntim_ou, fID_ou,levID_ou,timID_ou,vID_ou, &
502 ndims, cal_ou)
503
504 IF (is_mpi_root) THEN
505
506 !--- Write remaining coordinate variables:
507 CALL NF95_PUT_VAR(fID_ou, levID_ou, lev_in); DEALLOCATE(lev_in)
508 IF( interpt) CALL NF95_PUT_VAR(fID_ou, timID_ou, tmidday)
509 IF(.NOT.interpt) CALL NF95_PUT_VAR(fID_ou, timID_ou, tmidmonth)
510
511 IF (grid_type==unstructured) THEN
512
513 ALLOCATE(o3_out3_glo(nlat_ou, nlev_in, ntim_ou, read_climoz))
514 DO i=1,klon_glo
515 o3_out(ind_cell_glo_glo(i),:,:,:)=o3_out2_glo(i,:,:,:)
516 ENDDO
517
518
519 DO m = 1, read_climoz
520 CALL NF95_PUT_VAR(fID_ou, vID_ou(m), o3_out(nlat_ou:1:-1,:,:,m))
521 END DO
522 ELSE
523 !--- Write to file (the order of "rlatu" is inverted in the output file):
524 DO m = 1, read_climoz
525 CALL NF95_PUT_VAR(fID_ou, vID_ou(m), o3_out2(nlat_ou:1:-1,:,:,m))
526 END DO
527 ENDIF
528
529 CALL NF95_CLOSE(fID_ou)
530
531 ENDIF
532
533 !=============================================================================
534 END IF
535 !=============================================================================
536
537 IF (is_mpi_root) CALL NF95_CLOSE(fID_in)
538
539 ENDIF ! is_omp_master
540
541 first=.FALSE.
542 END SUBROUTINE regr_horiz_time_climoz
543 !
544 !-------------------------------------------------------------------------------
545
546
547 !-------------------------------------------------------------------------------
548 !
549 SUBROUTINE prepare_out(fID_in, nlev_in, ntim_ou, fID_ou, vlevID, vtimID, &
550 vID_ou, ndims, cal_ou)
551 !-------------------------------------------------------------------------------
552 ! Purpose: This subroutine creates the NetCDF output file, defines
553 ! dimensions and variables, and writes some of the coordinate variables.
554 !-------------------------------------------------------------------------------
555 USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
556 USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
557 USE mod_phys_lmdz_para, ONLY: is_mpi_root
558 USE mod_grid_phy_lmdz, ONLY: klon_glo
559 !
560 !-------------------------------------------------------------------------------
561 ! Arguments:
562 INTEGER, INTENT(IN) :: fID_in, nlev_in, ntim_ou
563 INTEGER, INTENT(OUT) :: fID_ou, vlevID, vtimID
564 INTEGER, INTENT(OUT) :: vID_ou(:) ! dim(1/2) 1: O3day&night 2: O3daylight
565 INTEGER, INTENT(IN) :: ndims ! fields rank (3 or 4)
566 CHARACTER(LEN=*), INTENT(IN) :: cal_ou ! calendar
567 !-------------------------------------------------------------------------------
568 ! Local variables:
569 INTEGER :: dlonID, dlatID, dlevID, dtimID, dIDs(4)
570 INTEGER :: vlonID, vlatID, ncerr, is
571 REAL,ALLOCATABLE :: latitude_glo_(:)
572 CHARACTER(LEN=80) :: sub
573 INTEGER :: i
574
575
576 !-------------------------------------------------------------------------------
577
578 IF (is_mpi_root) THEN
579 sub="prepare_out"
580 WRITE(lunout,*)"CALL sequence information: "//TRIM(sub)
581 CALL NF95_CREATE("climoz_LMDZ.nc", NF90_clobber, fID_ou)
582
583 !--- Dimensions:
584 IF(ndims==4) &
585 CALL NF95_DEF_DIM(fID_ou, "rlonv", nlon_ou, dlonID)
586 CALL NF95_DEF_DIM(fID_ou, "rlatu", nlat_ou, dlatID)
587 CALL NF95_DEF_DIM(fID_ou, "plev", nlev_in, dlevID)
588 CALL NF95_DEF_DIM(fID_ou, "time", ntim_ou, dtimID)
589
590 !--- Define coordinate variables:
591 IF(ndims==4) &
592 CALL NF95_DEF_VAR(fID_ou, "rlonv", NF90_FLOAT, dlonID, vlonID)
593 CALL NF95_DEF_VAR(fID_ou, "rlatu", NF90_FLOAT, dlatID, vlatID)
594 CALL NF95_DEF_VAR(fID_ou, "plev", NF90_FLOAT, dlevID, vlevID)
595 CALL NF95_DEF_VAR(fID_ou, "time", NF90_FLOAT, dtimID, vtimID)
596 IF(ndims==4) &
597 CALL NF95_PUT_ATT(fID_ou, vlonID, "units", "degrees_east")
598 CALL NF95_PUT_ATT(fID_ou, vlatID, "units", "degrees_north")
599 CALL NF95_PUT_ATT(fID_ou, vlevID, "units", "millibar")
600 CALL NF95_PUT_ATT(fID_ou, vtimID, "units", "days since 2000-1-1")
601 IF(ndims==4) &
602 CALL NF95_PUT_ATT(fID_ou, vlonID, "standard_name", "longitude")
603 CALL NF95_PUT_ATT(fID_ou, vlatID, "standard_name", "latitude")
604 CALL NF95_PUT_ATT(fID_ou, vlevID, "standard_name", "air_pressure")
605 CALL NF95_PUT_ATT(fID_ou, vtimID, "standard_name", "time")
606 CALL NF95_PUT_ATT(fID_ou, vlevID, "long_name", "air pressure")
607 CALL NF95_PUT_ATT(fID_ou, vtimID, "calendar", cal_ou)
608
609 !--- Define the main variables:
610 IF(ndims==3) dIDs(1:3) = [ dlatID, dlevID, dtimID]
611 IF(ndims==4) dIDs=[dlonID, dlatID, dlevID, dtimID]
612 CALL NF95_DEF_VAR(fID_ou, vars_in(1), NF90_FLOAT, dIDs(1:ndims), vID_ou(1))
613 CALL NF95_PUT_ATT(fID_ou, vID_ou(1), "long_name", "ozone mole fraction")
614 CALL NF95_PUT_ATT(fID_ou, vID_ou(1), "standard_name", "mole_fraction_of_ozone&
615 &_in_air")
616 IF(SIZE(vID_ou) == 2) THEN
617 CALL NF95_DEF_VAR(fID_ou, vars_in(2), NF90_FLOAT, dIDs(1:ndims), vID_ou(2))
618 CALL NF95_PUT_ATT(fID_ou, vID_ou(2), "long_name","ozone mole fraction in da&
619 &ylight")
620 END IF
621
622 !--- Global attributes:
623 ! The following commands, copying attributes, may fail. That is OK.
624 ! It should just mean that the attribute is not defined in the input file.
625 CALL NF95_COPY_ATT(fID_in,NF90_GLOBAL,"Conventions",fID_ou,NF90_GLOBAL, ncerr)
626 CALL handle_err_copy_att("Conventions")
627 CALL NF95_COPY_ATT(fID_in,NF90_GLOBAL,"title", fID_ou,NF90_GLOBAL, ncerr)
628 CALL handle_err_copy_att("title")
629 CALL NF95_COPY_ATT(fID_in,NF90_GLOBAL,"institution",fID_ou,NF90_GLOBAL, ncerr)
630 CALL handle_err_copy_att("institution")
631 CALL NF95_COPY_ATT(fID_in,NF90_GLOBAL,"source", fID_ou,NF90_GLOBAL, ncerr)
632 CALL handle_err_copy_att("source")
633 CALL NF95_PUT_ATT (fID_ou,NF90_GLOBAL,"comment", "Regridded for LMDZ")
634 CALL NF95_ENDDEF(fID_ou)
635
636 IF (grid_type==unstructured) THEN
637 ALLOCATE(latitude_glo_(klon_glo))
638 DO i=1,klon_glo
639 latitude_glo_(ind_cell_glo_glo(i))=latitude_glo(i)
640 ENDDO
641 CALL NF95_PUT_VAR(fID_ou, vlatID, latitude_glo_)
642 ELSE
643 !--- Write one of the coordinate variables:
644 IF(ndims==4) CALL NF95_PUT_VAR(fID_ou, vlonID, lon_reg/deg2rad)
645 CALL NF95_PUT_VAR(fID_ou, vlatID, lat_reg(nlat_ou:1:-1)/deg2rad)
646 ! (convert from rad to degrees and sort in ascending order)
647 ENDIF
648 ENDIF
649
650 CONTAINS
651
652 !-------------------------------------------------------------------------------
653 !
654 SUBROUTINE handle_err_copy_att(att_name)
655 !
656 !-------------------------------------------------------------------------------
657 USE netcdf, ONLY: NF90_NOERR, NF90_strerror
658 !-------------------------------------------------------------------------------
659 ! Arguments:
660 CHARACTER(LEN=*), INTENT(IN) :: att_name
661 !-------------------------------------------------------------------------------
662 IF(ncerr /= NF90_NOERR) &
663 WRITE(lunout,*)TRIM(sub)//" prepare_out NF95_COPY_ATT "//TRIM(att_name)// &
664 " -- "//TRIM(NF90_strerror(ncerr))
665
666 END SUBROUTINE handle_err_copy_att
667 !
668 !-------------------------------------------------------------------------------
669
670 END SUBROUTINE prepare_out
671 !
672 !-------------------------------------------------------------------------------
673
674 END MODULE regr_horiz_time_climoz_m
675 !
676 !-------------------------------------------------------------------------------
677