1 | MODULE iom |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE iom *** |
---|
4 | !! Input/Output manager : Library to read input files |
---|
5 | !!====================================================================== |
---|
6 | !! History : 2.0 ! 2005-12 (J. Belier) Original code |
---|
7 | !! 2.0 ! 2006-02 (S. Masson) Adaptation to NEMO |
---|
8 | !! 3.0 ! 2007-07 (D. Storkey) Changes to iom_gettime |
---|
9 | !! 3.4 ! 2012-12 (R. Bourdalle-Badie and G. Reffray) add C1D case |
---|
10 | !! 3.6 ! 2014-15 DIMG format removed |
---|
11 | !! 3.6 ! 2015-15 (J. Harle) Added procedure to read REAL attributes |
---|
12 | !! 4.0 ! 2017-11 (M. Andrejczuk) Extend IOM interface to write any 3D fields |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | !! iom_open : open a file read only |
---|
17 | !! iom_close : close a file or all files opened by iom |
---|
18 | !! iom_get : read a field (interfaced to several routines) |
---|
19 | !! iom_varid : get the id of a variable in a file |
---|
20 | !! iom_rstput : write a field in a restart file (interfaced to several routines) |
---|
21 | !!---------------------------------------------------------------------- |
---|
22 | USE dom_oce ! ocean space and time domain |
---|
23 | USE domutl ! |
---|
24 | USE c1d ! 1D vertical configuration |
---|
25 | USE flo_oce ! floats module declarations |
---|
26 | USE lbclnk ! lateal boundary condition / mpp exchanges |
---|
27 | USE iom_def ! iom variables definitions |
---|
28 | USE iom_nf90 ! NetCDF format with native NetCDF library |
---|
29 | USE in_out_manager ! I/O manager |
---|
30 | USE lib_mpp ! MPP library |
---|
31 | #if defined key_iomput |
---|
32 | USE sbc_oce , ONLY : nn_fsbc, ght_abl, ghw_abl, e3t_abl, e3w_abl, jpka, jpkam1 |
---|
33 | USE icb_oce , ONLY : nclasses, class_num ! !: iceberg classes |
---|
34 | #if defined key_si3 |
---|
35 | USE ice , ONLY : jpl |
---|
36 | #endif |
---|
37 | USE phycst ! physical constants |
---|
38 | USE dianam ! build name of file |
---|
39 | USE xios |
---|
40 | # endif |
---|
41 | USE ioipsl, ONLY : ju2ymds ! for calendar |
---|
42 | USE crs ! Grid coarsening |
---|
43 | #if defined key_top |
---|
44 | USE trc, ONLY : profsed |
---|
45 | #endif |
---|
46 | USE lib_fortran |
---|
47 | USE diu_bulk, ONLY : ln_diurnal_only, ln_diurnal |
---|
48 | |
---|
49 | IMPLICIT NONE |
---|
50 | PUBLIC ! must be public to be able to access iom_def through iom |
---|
51 | |
---|
52 | #if defined key_iomput |
---|
53 | LOGICAL, PUBLIC, PARAMETER :: lk_iomput = .TRUE. !: iom_put flag |
---|
54 | #else |
---|
55 | LOGICAL, PUBLIC, PARAMETER :: lk_iomput = .FALSE. !: iom_put flag |
---|
56 | #endif |
---|
57 | PUBLIC iom_init, iom_init_closedef, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_get_var |
---|
58 | PUBLIC iom_chkatt, iom_getatt, iom_putatt, iom_getszuld, iom_rstput, iom_delay_rst, iom_put |
---|
59 | PUBLIC iom_use, iom_context_finalize, iom_update_file_name, iom_miss_val |
---|
60 | |
---|
61 | PRIVATE iom_rp0d_sp, iom_rp1d_sp, iom_rp2d_sp, iom_rp3d_sp |
---|
62 | PRIVATE iom_rp0d_dp, iom_rp1d_dp, iom_rp2d_dp, iom_rp3d_dp |
---|
63 | PRIVATE iom_get_123d |
---|
64 | PRIVATE iom_g0d_sp, iom_g1d_sp, iom_g2d_sp, iom_g3d_sp |
---|
65 | PRIVATE iom_g0d_dp, iom_g1d_dp, iom_g2d_dp, iom_g3d_dp |
---|
66 | PRIVATE iom_p1d_sp, iom_p2d_sp, iom_p3d_sp, iom_p4d_sp |
---|
67 | PRIVATE iom_p1d_dp, iom_p2d_dp, iom_p3d_dp, iom_p4d_dp |
---|
68 | #if defined key_iomput |
---|
69 | PRIVATE iom_set_domain_attr, iom_set_axis_attr, iom_set_field_attr, iom_set_file_attr, iom_get_file_attr, iom_set_grid_attr |
---|
70 | PRIVATE set_grid, set_grid_bounds, set_scalar, set_xmlatt, set_mooring, iom_sdate |
---|
71 | PRIVATE iom_set_rst_context, iom_set_rstw_active, iom_set_rstr_active |
---|
72 | # endif |
---|
73 | PUBLIC iom_set_rstw_var_active, iom_set_rstw_core, iom_set_rst_vars |
---|
74 | |
---|
75 | INTERFACE iom_get |
---|
76 | MODULE PROCEDURE iom_g0d_sp, iom_g1d_sp, iom_g2d_sp, iom_g3d_sp |
---|
77 | MODULE PROCEDURE iom_g0d_dp, iom_g1d_dp, iom_g2d_dp, iom_g3d_dp |
---|
78 | END INTERFACE |
---|
79 | INTERFACE iom_getatt |
---|
80 | MODULE PROCEDURE iom_g0d_iatt, iom_g1d_iatt, iom_g0d_ratt, iom_g1d_ratt, iom_g0d_catt |
---|
81 | END INTERFACE |
---|
82 | INTERFACE iom_putatt |
---|
83 | MODULE PROCEDURE iom_p0d_iatt, iom_p1d_iatt, iom_p0d_ratt, iom_p1d_ratt, iom_p0d_catt |
---|
84 | END INTERFACE |
---|
85 | INTERFACE iom_rstput |
---|
86 | MODULE PROCEDURE iom_rp0d_sp, iom_rp1d_sp, iom_rp2d_sp, iom_rp3d_sp |
---|
87 | MODULE PROCEDURE iom_rp0d_dp, iom_rp1d_dp, iom_rp2d_dp, iom_rp3d_dp |
---|
88 | END INTERFACE |
---|
89 | INTERFACE iom_put |
---|
90 | MODULE PROCEDURE iom_p0d_sp, iom_p1d_sp, iom_p2d_sp, iom_p3d_sp, iom_p4d_sp |
---|
91 | MODULE PROCEDURE iom_p0d_dp, iom_p1d_dp, iom_p2d_dp, iom_p3d_dp, iom_p4d_dp |
---|
92 | END INTERFACE iom_put |
---|
93 | |
---|
94 | !! * Substitutions |
---|
95 | # include "do_loop_substitute.h90" |
---|
96 | !!---------------------------------------------------------------------- |
---|
97 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
98 | !! $Id$ |
---|
99 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
100 | !!---------------------------------------------------------------------- |
---|
101 | CONTAINS |
---|
102 | |
---|
103 | SUBROUTINE iom_init( cdname, fname, ld_closedef ) |
---|
104 | !!---------------------------------------------------------------------- |
---|
105 | !! *** ROUTINE *** |
---|
106 | !! |
---|
107 | !! ** Purpose : |
---|
108 | !! |
---|
109 | !!---------------------------------------------------------------------- |
---|
110 | CHARACTER(len=*), INTENT(in) :: cdname |
---|
111 | CHARACTER(len=*), OPTIONAL, INTENT(in) :: fname |
---|
112 | LOGICAL , OPTIONAL, INTENT(in) :: ld_closedef |
---|
113 | #if defined key_iomput |
---|
114 | ! |
---|
115 | TYPE(xios_duration) :: dtime = xios_duration(0, 0, 0, 0, 0, 0) |
---|
116 | TYPE(xios_date) :: start_date |
---|
117 | CHARACTER(len=lc) :: clname |
---|
118 | INTEGER :: irefyear, irefmonth, irefday |
---|
119 | INTEGER :: ji |
---|
120 | LOGICAL :: llrst_context ! is context related to restart |
---|
121 | ! |
---|
122 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds |
---|
123 | REAL(wp), DIMENSION(2,jpkam1) :: za_bnds ! ABL vertical boundaries |
---|
124 | LOGICAL :: ll_closedef = .TRUE. |
---|
125 | LOGICAL :: ll_exist |
---|
126 | !!---------------------------------------------------------------------- |
---|
127 | ! |
---|
128 | IF ( PRESENT(ld_closedef) ) ll_closedef = ld_closedef |
---|
129 | ! |
---|
130 | ALLOCATE( zt_bnds(2,jpk), zw_bnds(2,jpk) ) |
---|
131 | ! |
---|
132 | clname = cdname |
---|
133 | IF( TRIM(Agrif_CFixed()) /= '0' ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) |
---|
134 | CALL xios_context_initialize(TRIM(clname), mpi_comm_oce) |
---|
135 | CALL iom_swap( cdname ) |
---|
136 | llrst_context = (TRIM(cdname) == TRIM(crxios_context) .OR. TRIM(cdname) == TRIM(cwxios_context)) |
---|
137 | |
---|
138 | ! Calendar type is now defined in xml file |
---|
139 | IF (.NOT.(xios_getvar('ref_year' ,irefyear ))) irefyear = 1900 |
---|
140 | IF (.NOT.(xios_getvar('ref_month',irefmonth))) irefmonth = 01 |
---|
141 | IF (.NOT.(xios_getvar('ref_day' ,irefday ))) irefday = 01 |
---|
142 | |
---|
143 | SELECT CASE ( nleapy ) ! Choose calendar for IOIPSL |
---|
144 | CASE ( 1) ; CALL xios_define_calendar( TYPE = "Gregorian", time_origin = xios_date(irefyear,irefmonth,irefday,0,0,0), & |
---|
145 | & start_date = xios_date( nyear, nmonth, nday,0,0,0) ) |
---|
146 | CASE ( 0) ; CALL xios_define_calendar( TYPE = "NoLeap" , time_origin = xios_date(irefyear,irefmonth,irefday,0,0,0), & |
---|
147 | & start_date = xios_date( nyear, nmonth, nday,0,0,0) ) |
---|
148 | CASE (30) ; CALL xios_define_calendar( TYPE = "D360" , time_origin = xios_date(irefyear,irefmonth,irefday,0,0,0), & |
---|
149 | & start_date = xios_date( nyear, nmonth, nday,0,0,0) ) |
---|
150 | END SELECT |
---|
151 | |
---|
152 | ! horizontal grid definition |
---|
153 | IF(.NOT.llrst_context) CALL set_scalar |
---|
154 | ! |
---|
155 | IF( TRIM(cdname) == TRIM(cxios_context) ) THEN |
---|
156 | CALL set_grid( "T", glamt, gphit, .FALSE., .FALSE. ) |
---|
157 | CALL set_grid( "U", glamu, gphiu, .FALSE., .FALSE. ) |
---|
158 | CALL set_grid( "V", glamv, gphiv, .FALSE., .FALSE. ) |
---|
159 | CALL set_grid( "W", glamt, gphit, .FALSE., .FALSE. ) |
---|
160 | CALL set_grid_znl( gphit ) |
---|
161 | ! |
---|
162 | IF( ln_cfmeta ) THEN ! Add additional grid metadata |
---|
163 | CALL iom_set_domain_attr("grid_T", area = real( e1e2t(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
164 | CALL iom_set_domain_attr("grid_U", area = real( e1e2u(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
165 | CALL iom_set_domain_attr("grid_V", area = real( e1e2v(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
166 | CALL iom_set_domain_attr("grid_W", area = real( e1e2t(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
167 | CALL set_grid_bounds( "T", glamf, gphif, glamt, gphit ) |
---|
168 | CALL set_grid_bounds( "U", glamv, gphiv, glamu, gphiu ) |
---|
169 | CALL set_grid_bounds( "V", glamu, gphiu, glamv, gphiv ) |
---|
170 | CALL set_grid_bounds( "W", glamf, gphif, glamt, gphit ) |
---|
171 | ENDIF |
---|
172 | ENDIF |
---|
173 | ! |
---|
174 | IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN |
---|
175 | CALL dom_grid_crs ! Save the parent grid information & Switch to coarse grid domain |
---|
176 | ! |
---|
177 | CALL set_grid( "T", glamt_crs, gphit_crs, .FALSE., .FALSE. ) |
---|
178 | CALL set_grid( "U", glamu_crs, gphiu_crs, .FALSE., .FALSE. ) |
---|
179 | CALL set_grid( "V", glamv_crs, gphiv_crs, .FALSE., .FALSE. ) |
---|
180 | CALL set_grid( "W", glamt_crs, gphit_crs, .FALSE., .FALSE. ) |
---|
181 | CALL set_grid_znl( gphit_crs ) |
---|
182 | ! |
---|
183 | CALL dom_grid_glo ! Return to parent grid domain |
---|
184 | ! |
---|
185 | IF( ln_cfmeta .AND. .NOT. llrst_context) THEN ! Add additional grid metadata |
---|
186 | CALL iom_set_domain_attr("grid_T", area = real(e1e2t_crs(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
187 | CALL iom_set_domain_attr("grid_U", area = real(e1u_crs(Nis0:Nie0, Njs0:Nje0) * e2u_crs(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
188 | CALL iom_set_domain_attr("grid_V", area = real(e1v_crs(Nis0:Nie0, Njs0:Nje0) * e2v_crs(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
189 | CALL iom_set_domain_attr("grid_W", area = real(e1e2t_crs(Nis0:Nie0, Njs0:Nje0), dp)) |
---|
190 | CALL set_grid_bounds( "T", glamf_crs, gphif_crs, glamt_crs, gphit_crs ) |
---|
191 | CALL set_grid_bounds( "U", glamv_crs, gphiv_crs, glamu_crs, gphiu_crs ) |
---|
192 | CALL set_grid_bounds( "V", glamu_crs, gphiu_crs, glamv_crs, gphiv_crs ) |
---|
193 | CALL set_grid_bounds( "W", glamf_crs, gphif_crs, glamt_crs, gphit_crs ) |
---|
194 | ENDIF |
---|
195 | ENDIF |
---|
196 | ! |
---|
197 | ! vertical grid definition |
---|
198 | IF(.NOT.llrst_context) THEN |
---|
199 | CALL iom_set_axis_attr( "deptht", paxis = gdept_1d ) |
---|
200 | CALL iom_set_axis_attr( "depthu", paxis = gdept_1d ) |
---|
201 | CALL iom_set_axis_attr( "depthv", paxis = gdept_1d ) |
---|
202 | CALL iom_set_axis_attr( "depthw", paxis = gdepw_1d ) |
---|
203 | |
---|
204 | ! ABL |
---|
205 | IF( .NOT. ALLOCATED(ght_abl) ) THEN ! force definition for xml files (xios) |
---|
206 | ALLOCATE( ght_abl(jpka), ghw_abl(jpka), e3t_abl(jpka), e3w_abl(jpka) ) ! default allocation needed by iom |
---|
207 | ght_abl(:) = -1._wp ; ghw_abl(:) = -1._wp |
---|
208 | e3t_abl(:) = -1._wp ; e3w_abl(:) = -1._wp |
---|
209 | ENDIF |
---|
210 | CALL iom_set_axis_attr( "ght_abl", ght_abl(2:jpka) ) |
---|
211 | CALL iom_set_axis_attr( "ghw_abl", ghw_abl(2:jpka) ) |
---|
212 | |
---|
213 | ! Add vertical grid bounds |
---|
214 | zt_bnds(2,: ) = gdept_1d(:) |
---|
215 | zt_bnds(1,2:jpk ) = gdept_1d(1:jpkm1) |
---|
216 | zt_bnds(1,1 ) = gdept_1d(1) - e3w_1d(1) |
---|
217 | zw_bnds(1,: ) = gdepw_1d(:) |
---|
218 | zw_bnds(2,1:jpkm1) = gdepw_1d(2:jpk) |
---|
219 | zw_bnds(2,jpk: ) = gdepw_1d(jpk) + e3t_1d(jpk) |
---|
220 | CALL iom_set_axis_attr( "deptht", bounds=zw_bnds ) |
---|
221 | CALL iom_set_axis_attr( "depthu", bounds=zw_bnds ) |
---|
222 | CALL iom_set_axis_attr( "depthv", bounds=zw_bnds ) |
---|
223 | CALL iom_set_axis_attr( "depthw", bounds=zt_bnds ) |
---|
224 | |
---|
225 | ! ABL |
---|
226 | za_bnds(1,:) = ghw_abl(1:jpkam1) |
---|
227 | za_bnds(2,:) = ghw_abl(2:jpka ) |
---|
228 | CALL iom_set_axis_attr( "ght_abl", bounds=za_bnds ) |
---|
229 | za_bnds(1,:) = ght_abl(2:jpka ) |
---|
230 | za_bnds(2,:) = ght_abl(2:jpka ) + e3w_abl(2:jpka) |
---|
231 | CALL iom_set_axis_attr( "ghw_abl", bounds=za_bnds ) |
---|
232 | |
---|
233 | CALL iom_set_axis_attr( "nfloat", (/ (REAL(ji,wp), ji=1,jpnfl) /) ) |
---|
234 | # if defined key_si3 |
---|
235 | CALL iom_set_axis_attr( "ncatice", (/ (REAL(ji,wp), ji=1,jpl) /) ) |
---|
236 | ! SIMIP diagnostics (4 main arctic straits) |
---|
237 | CALL iom_set_axis_attr( "nstrait", (/ (REAL(ji,wp), ji=1,4) /) ) |
---|
238 | # endif |
---|
239 | #if defined key_top |
---|
240 | IF( ALLOCATED(profsed) ) CALL iom_set_axis_attr( "profsed", paxis = profsed ) |
---|
241 | #endif |
---|
242 | CALL iom_set_axis_attr( "icbcla", class_num ) |
---|
243 | CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) ) ! strange syntaxe and idea... |
---|
244 | CALL iom_set_axis_attr( "iax_26C", (/ REAL(26,wp) /) ) ! strange syntaxe and idea... |
---|
245 | CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) ) ! strange syntaxe and idea... |
---|
246 | ! for diaprt, we need to define an axis which size can be 1 (default) or 5 (if the file subbasins.nc exists) |
---|
247 | INQUIRE( FILE = 'subbasins.nc', EXIST = ll_exist ) |
---|
248 | nbasin = 1 + 4 * COUNT( (/ll_exist/) ) |
---|
249 | CALL iom_set_axis_attr( "basin" , (/ (REAL(ji,wp), ji=1,nbasin) /) ) |
---|
250 | ENDIF |
---|
251 | ! |
---|
252 | ! automatic definitions of some of the xml attributs |
---|
253 | IF( TRIM(cdname) == TRIM(crxios_context) ) THEN |
---|
254 | !set names of the fields in restart file IF using XIOS to read data |
---|
255 | CALL iom_set_rst_context(.TRUE.) |
---|
256 | CALL iom_set_rst_vars(rst_rfields) |
---|
257 | !set which fields are to be read from restart file |
---|
258 | CALL iom_set_rstr_active() |
---|
259 | ELSE IF( TRIM(cdname) == TRIM(cwxios_context) ) THEN |
---|
260 | !set names of the fields in restart file IF using XIOS to write data |
---|
261 | CALL iom_set_rst_context(.FALSE.) |
---|
262 | CALL iom_set_rst_vars(rst_wfields) |
---|
263 | !set which fields are to be written to a restart file |
---|
264 | CALL iom_set_rstw_active(fname) |
---|
265 | ELSE |
---|
266 | CALL set_xmlatt |
---|
267 | ENDIF |
---|
268 | ! |
---|
269 | ! set time step length |
---|
270 | dtime%second = rn_Dt |
---|
271 | CALL xios_set_timestep( dtime ) |
---|
272 | ! |
---|
273 | ! conditional closure of context definition |
---|
274 | IF ( ll_closedef ) CALL iom_init_closedef |
---|
275 | ! |
---|
276 | DEALLOCATE( zt_bnds, zw_bnds ) |
---|
277 | ! |
---|
278 | #endif |
---|
279 | ! |
---|
280 | END SUBROUTINE iom_init |
---|
281 | |
---|
282 | SUBROUTINE iom_init_closedef |
---|
283 | !!---------------------------------------------------------------------- |
---|
284 | !! *** SUBROUTINE iom_init_closedef *** |
---|
285 | !!---------------------------------------------------------------------- |
---|
286 | !! |
---|
287 | !! ** Purpose : Closure of context definition |
---|
288 | !! |
---|
289 | !!---------------------------------------------------------------------- |
---|
290 | |
---|
291 | #if defined key_iomput |
---|
292 | CALL xios_close_context_definition() |
---|
293 | CALL xios_update_calendar( 0 ) |
---|
294 | #else |
---|
295 | IF( .FALSE. ) WRITE(numout,*) 'iom_init_closedef: should not see this' ! useless statement to avoid compilation warnings |
---|
296 | #endif |
---|
297 | |
---|
298 | END SUBROUTINE iom_init_closedef |
---|
299 | |
---|
300 | SUBROUTINE iom_set_rstw_var_active(field) |
---|
301 | !!--------------------------------------------------------------------- |
---|
302 | !! *** SUBROUTINE iom_set_rstw_var_active *** |
---|
303 | !! |
---|
304 | !! ** Purpose : enable variable in restart file when writing with XIOS |
---|
305 | !!--------------------------------------------------------------------- |
---|
306 | CHARACTER(len = *), INTENT(IN) :: field |
---|
307 | INTEGER :: i |
---|
308 | LOGICAL :: llis_set |
---|
309 | CHARACTER(LEN=256) :: clinfo ! info character |
---|
310 | |
---|
311 | #if defined key_iomput |
---|
312 | llis_set = .FALSE. |
---|
313 | |
---|
314 | DO i = 1, max_rst_fields |
---|
315 | IF(TRIM(rst_wfields(i)%vname) == field) THEN |
---|
316 | rst_wfields(i)%active = .TRUE. |
---|
317 | llis_set = .TRUE. |
---|
318 | EXIT |
---|
319 | ENDIF |
---|
320 | ENDDO |
---|
321 | !Warn if variable is not in defined in rst_wfields |
---|
322 | IF(.NOT.llis_set) THEN |
---|
323 | WRITE(ctmp1,*) 'iom_set_rstw_var_active: variable ', field ,' is available for writing but not defined' |
---|
324 | CALL ctl_stop( 'iom_set_rstw_var_active:', ctmp1 ) |
---|
325 | ENDIF |
---|
326 | #else |
---|
327 | clinfo = 'iom_set_rstw_var_active: key_iomput is needed to use XIOS restart read/write functionality' |
---|
328 | CALL ctl_stop('STOP', TRIM(clinfo)) |
---|
329 | #endif |
---|
330 | |
---|
331 | END SUBROUTINE iom_set_rstw_var_active |
---|
332 | |
---|
333 | SUBROUTINE iom_set_rstr_active() |
---|
334 | !!--------------------------------------------------------------------- |
---|
335 | !! *** SUBROUTINE iom_set_rstr_active *** |
---|
336 | !! |
---|
337 | !! ** Purpose : define file name in XIOS context for reading restart file, |
---|
338 | !! enable variables present in restart file for reading with XIOS |
---|
339 | !!--------------------------------------------------------------------- |
---|
340 | |
---|
341 | !sets enabled = .TRUE. for each field in restart file |
---|
342 | CHARACTER(len=256) :: rst_file |
---|
343 | |
---|
344 | #if defined key_iomput |
---|
345 | TYPE(xios_field) :: field_hdl |
---|
346 | TYPE(xios_file) :: file_hdl |
---|
347 | TYPE(xios_filegroup) :: filegroup_hdl |
---|
348 | INTEGER :: i |
---|
349 | CHARACTER(lc) :: clpath |
---|
350 | |
---|
351 | clpath = TRIM(cn_ocerst_indir) |
---|
352 | IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' |
---|
353 | IF( TRIM(Agrif_CFixed()) == '0' ) THEN |
---|
354 | rst_file = TRIM(clpath)//TRIM(cn_ocerst_in) |
---|
355 | ELSE |
---|
356 | rst_file = TRIM(clpath)//TRIM(Agrif_CFixed())//'_'//TRIM(cn_ocerst_in) |
---|
357 | ENDIF |
---|
358 | !set name of the restart file and enable available fields |
---|
359 | if(lwp) WRITE(numout,*) 'Setting restart filename (for XIOS) to: ',rst_file |
---|
360 | CALL xios_get_handle("file_definition", filegroup_hdl ) |
---|
361 | CALL xios_add_child(filegroup_hdl, file_hdl, 'rrestart') |
---|
362 | CALL xios_set_file_attr( "rrestart", name=trim(rst_file), type="one_file", & |
---|
363 | par_access="collective", enabled=.TRUE., mode="read", & |
---|
364 | output_freq=xios_timestep) |
---|
365 | !define variables for restart context |
---|
366 | DO i = 1, max_rst_fields |
---|
367 | IF( TRIM(rst_rfields(i)%vname) /= "NO_NAME") THEN |
---|
368 | IF( iom_varid( numror, TRIM(rst_rfields(i)%vname), ldstop = .FALSE. ) > 0 ) THEN |
---|
369 | CALL xios_add_child(file_hdl, field_hdl, TRIM(rst_rfields(i)%vname)) |
---|
370 | SELECT CASE (TRIM(rst_rfields(i)%grid)) |
---|
371 | CASE ("grid_N_3D") |
---|
372 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_rfields(i)%vname), & |
---|
373 | domain_ref="grid_N", axis_ref="nav_lev", operation = "instant") |
---|
374 | CASE ("grid_N") |
---|
375 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_rfields(i)%vname), & |
---|
376 | domain_ref="grid_N", operation = "instant") |
---|
377 | CASE ("grid_vector") |
---|
378 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_rfields(i)%vname), & |
---|
379 | axis_ref="nav_lev", operation = "instant") |
---|
380 | CASE ("grid_scalar") |
---|
381 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_rfields(i)%vname), & |
---|
382 | scalar_ref = "grid_scalar", operation = "instant") |
---|
383 | END SELECT |
---|
384 | IF(lwp) WRITE(numout,*) 'XIOS read: ', TRIM(rst_rfields(i)%vname), ' enabled in ', TRIM(rst_file) |
---|
385 | ENDIF |
---|
386 | ENDIF |
---|
387 | END DO |
---|
388 | #endif |
---|
389 | END SUBROUTINE iom_set_rstr_active |
---|
390 | |
---|
391 | SUBROUTINE iom_set_rstw_core(cdmdl) |
---|
392 | !!--------------------------------------------------------------------- |
---|
393 | !! *** SUBROUTINE iom_set_rstw_core *** |
---|
394 | !! |
---|
395 | !! ** Purpose : set variables which are always in restart file |
---|
396 | !!--------------------------------------------------------------------- |
---|
397 | CHARACTER (len=*), INTENT (IN) :: cdmdl ! model OPA or SAS |
---|
398 | CHARACTER(LEN=256) :: clinfo ! info character |
---|
399 | #if defined key_iomput |
---|
400 | IF(cdmdl == "OPA") THEN |
---|
401 | !from restart.F90 |
---|
402 | CALL iom_set_rstw_var_active("rn_Dt") |
---|
403 | IF ( .NOT. ln_diurnal_only ) THEN |
---|
404 | CALL iom_set_rstw_var_active('ub' ) |
---|
405 | CALL iom_set_rstw_var_active('vb' ) |
---|
406 | CALL iom_set_rstw_var_active('tb' ) |
---|
407 | CALL iom_set_rstw_var_active('sb' ) |
---|
408 | CALL iom_set_rstw_var_active('sshb') |
---|
409 | ! |
---|
410 | CALL iom_set_rstw_var_active('un' ) |
---|
411 | CALL iom_set_rstw_var_active('vn' ) |
---|
412 | CALL iom_set_rstw_var_active('tn' ) |
---|
413 | CALL iom_set_rstw_var_active('sn' ) |
---|
414 | CALL iom_set_rstw_var_active('sshn') |
---|
415 | CALL iom_set_rstw_var_active('rhop') |
---|
416 | ENDIF |
---|
417 | IF(ln_diurnal) CALL iom_set_rstw_var_active('Dsst') |
---|
418 | !from trasbc.F90 |
---|
419 | CALL iom_set_rstw_var_active('sbc_hc_b') |
---|
420 | CALL iom_set_rstw_var_active('sbc_sc_b') |
---|
421 | ENDIF |
---|
422 | #else |
---|
423 | clinfo = 'iom_set_rstw_core: key_iomput is needed to use XIOS restart read/write functionality' |
---|
424 | CALL ctl_stop('STOP', TRIM(clinfo)) |
---|
425 | #endif |
---|
426 | END SUBROUTINE iom_set_rstw_core |
---|
427 | |
---|
428 | SUBROUTINE iom_set_rst_vars(fields) |
---|
429 | !!--------------------------------------------------------------------- |
---|
430 | !! *** SUBROUTINE iom_set_rst_vars *** |
---|
431 | !! |
---|
432 | !! ** Purpose : Fill array fields with the information about all |
---|
433 | !! possible variables and corresponding grids definition |
---|
434 | !! for reading/writing restart with XIOS |
---|
435 | !!--------------------------------------------------------------------- |
---|
436 | TYPE(RST_FIELD), INTENT(INOUT) :: fields(max_rst_fields) |
---|
437 | INTEGER :: i |
---|
438 | |
---|
439 | i = 0 |
---|
440 | i = i + 1; fields(i)%vname="rn_Dt"; fields(i)%grid="grid_scalar" |
---|
441 | i = i + 1; fields(i)%vname="un"; fields(i)%grid="grid_N_3D" |
---|
442 | i = i + 1; fields(i)%vname="ub"; fields(i)%grid="grid_N_3D" |
---|
443 | i = i + 1; fields(i)%vname="vn"; fields(i)%grid="grid_N_3D" |
---|
444 | i = i + 1; fields(i)%vname="vb"; fields(i)%grid="grid_N_3D" |
---|
445 | i = i + 1; fields(i)%vname="tn"; fields(i)%grid="grid_N_3D" |
---|
446 | i = i + 1; fields(i)%vname="tb"; fields(i)%grid="grid_N_3D" |
---|
447 | i = i + 1; fields(i)%vname="sn"; fields(i)%grid="grid_N_3D" |
---|
448 | i = i + 1; fields(i)%vname="sb"; fields(i)%grid="grid_N_3D" |
---|
449 | i = i + 1; fields(i)%vname="sshn"; fields(i)%grid="grid_N" |
---|
450 | i = i + 1; fields(i)%vname="sshb"; fields(i)%grid="grid_N" |
---|
451 | i = i + 1; fields(i)%vname="rhop"; fields(i)%grid="grid_N_3D" |
---|
452 | i = i + 1; fields(i)%vname="kt"; fields(i)%grid="grid_scalar" |
---|
453 | i = i + 1; fields(i)%vname="ndastp"; fields(i)%grid="grid_scalar" |
---|
454 | i = i + 1; fields(i)%vname="adatrj"; fields(i)%grid="grid_scalar" |
---|
455 | i = i + 1; fields(i)%vname="utau_b"; fields(i)%grid="grid_N" |
---|
456 | i = i + 1; fields(i)%vname="vtau_b"; fields(i)%grid="grid_N" |
---|
457 | i = i + 1; fields(i)%vname="qns_b"; fields(i)%grid="grid_N" |
---|
458 | i = i + 1; fields(i)%vname="emp_b"; fields(i)%grid="grid_N" |
---|
459 | i = i + 1; fields(i)%vname="sfx_b"; fields(i)%grid="grid_N" |
---|
460 | i = i + 1; fields(i)%vname="en" ; fields(i)%grid="grid_N_3D" |
---|
461 | i = i + 1; fields(i)%vname="avt_k"; fields(i)%grid="grid_N_3D" |
---|
462 | i = i + 1; fields(i)%vname="avm_k"; fields(i)%grid="grid_N_3D" |
---|
463 | i = i + 1; fields(i)%vname="dissl"; fields(i)%grid="grid_N_3D" |
---|
464 | i = i + 1; fields(i)%vname="sbc_hc_b"; fields(i)%grid="grid_N" |
---|
465 | i = i + 1; fields(i)%vname="sbc_sc_b"; fields(i)%grid="grid_N" |
---|
466 | i = i + 1; fields(i)%vname="qsr_hc_b"; fields(i)%grid="grid_N_3D" |
---|
467 | i = i + 1; fields(i)%vname="fraqsr_1lev"; fields(i)%grid="grid_N" |
---|
468 | i = i + 1; fields(i)%vname="greenland_icesheet_mass" |
---|
469 | fields(i)%grid="grid_scalar" |
---|
470 | i = i + 1; fields(i)%vname="greenland_icesheet_timelapsed" |
---|
471 | fields(i)%grid="grid_scalar" |
---|
472 | i = i + 1; fields(i)%vname="greenland_icesheet_mass_roc" |
---|
473 | fields(i)%grid="grid_scalar" |
---|
474 | i = i + 1; fields(i)%vname="antarctica_icesheet_mass" |
---|
475 | fields(i)%grid="grid_scalar" |
---|
476 | i = i + 1; fields(i)%vname="antarctica_icesheet_timelapsed" |
---|
477 | fields(i)%grid="grid_scalar" |
---|
478 | i = i + 1; fields(i)%vname="antarctica_icesheet_mass_roc" |
---|
479 | fields(i)%grid="grid_scalar" |
---|
480 | i = i + 1; fields(i)%vname="frc_v"; fields(i)%grid="grid_scalar" |
---|
481 | i = i + 1; fields(i)%vname="frc_t"; fields(i)%grid="grid_scalar" |
---|
482 | i = i + 1; fields(i)%vname="frc_s"; fields(i)%grid="grid_scalar" |
---|
483 | i = i + 1; fields(i)%vname="frc_wn_t"; fields(i)%grid="grid_scalar" |
---|
484 | i = i + 1; fields(i)%vname="frc_wn_s"; fields(i)%grid="grid_scalar" |
---|
485 | i = i + 1; fields(i)%vname="ssh_ini"; fields(i)%grid="grid_N" |
---|
486 | i = i + 1; fields(i)%vname="e3t_ini"; fields(i)%grid="grid_N_3D" |
---|
487 | i = i + 1; fields(i)%vname="hc_loc_ini"; fields(i)%grid="grid_N_3D" |
---|
488 | i = i + 1; fields(i)%vname="sc_loc_ini"; fields(i)%grid="grid_N_3D" |
---|
489 | i = i + 1; fields(i)%vname="ssh_hc_loc_ini"; fields(i)%grid="grid_N" |
---|
490 | i = i + 1; fields(i)%vname="ssh_sc_loc_ini"; fields(i)%grid="grid_N" |
---|
491 | i = i + 1; fields(i)%vname="tilde_e3t_b"; fields(i)%grid="grid_N" |
---|
492 | i = i + 1; fields(i)%vname="tilde_e3t_n"; fields(i)%grid="grid_N" |
---|
493 | i = i + 1; fields(i)%vname="hdiv_lf"; fields(i)%grid="grid_N" |
---|
494 | i = i + 1; fields(i)%vname="ub2_b"; fields(i)%grid="grid_N" |
---|
495 | i = i + 1; fields(i)%vname="vb2_b"; fields(i)%grid="grid_N" |
---|
496 | i = i + 1; fields(i)%vname="sshbb_e"; fields(i)%grid="grid_N" |
---|
497 | i = i + 1; fields(i)%vname="ubb_e"; fields(i)%grid="grid_N" |
---|
498 | i = i + 1; fields(i)%vname="vbb_e"; fields(i)%grid="grid_N" |
---|
499 | i = i + 1; fields(i)%vname="sshb_e"; fields(i)%grid="grid_N" |
---|
500 | i = i + 1; fields(i)%vname="ub_e"; fields(i)%grid="grid_N" |
---|
501 | i = i + 1; fields(i)%vname="vb_e"; fields(i)%grid="grid_N" |
---|
502 | i = i + 1; fields(i)%vname="fwf_isf_b"; fields(i)%grid="grid_N" |
---|
503 | i = i + 1; fields(i)%vname="isf_sc_b"; fields(i)%grid="grid_N" |
---|
504 | i = i + 1; fields(i)%vname="isf_hc_b"; fields(i)%grid="grid_N" |
---|
505 | i = i + 1; fields(i)%vname="ssh_ibb"; fields(i)%grid="grid_N" |
---|
506 | i = i + 1; fields(i)%vname="rnf_b"; fields(i)%grid="grid_N" |
---|
507 | i = i + 1; fields(i)%vname="rnf_hc_b"; fields(i)%grid="grid_N" |
---|
508 | i = i + 1; fields(i)%vname="rnf_sc_b"; fields(i)%grid="grid_N" |
---|
509 | i = i + 1; fields(i)%vname="nn_fsbc"; fields(i)%grid="grid_scalar" |
---|
510 | i = i + 1; fields(i)%vname="ssu_m"; fields(i)%grid="grid_N" |
---|
511 | i = i + 1; fields(i)%vname="ssv_m"; fields(i)%grid="grid_N" |
---|
512 | i = i + 1; fields(i)%vname="sst_m"; fields(i)%grid="grid_N" |
---|
513 | i = i + 1; fields(i)%vname="sss_m"; fields(i)%grid="grid_N" |
---|
514 | i = i + 1; fields(i)%vname="ssh_m"; fields(i)%grid="grid_N" |
---|
515 | i = i + 1; fields(i)%vname="e3t_m"; fields(i)%grid="grid_N" |
---|
516 | i = i + 1; fields(i)%vname="frq_m"; fields(i)%grid="grid_N" |
---|
517 | i = i + 1; fields(i)%vname="avmb"; fields(i)%grid="grid_vector" |
---|
518 | i = i + 1; fields(i)%vname="avtb"; fields(i)%grid="grid_vector" |
---|
519 | i = i + 1; fields(i)%vname="ub2_i_b"; fields(i)%grid="grid_N" |
---|
520 | i = i + 1; fields(i)%vname="vb2_i_b"; fields(i)%grid="grid_N" |
---|
521 | i = i + 1; fields(i)%vname="ntime"; fields(i)%grid="grid_scalar" |
---|
522 | i = i + 1; fields(i)%vname="Dsst"; fields(i)%grid="grid_scalar" |
---|
523 | i = i + 1; fields(i)%vname="tmask"; fields(i)%grid="grid_N_3D" |
---|
524 | i = i + 1; fields(i)%vname="umask"; fields(i)%grid="grid_N_3D" |
---|
525 | i = i + 1; fields(i)%vname="vmask"; fields(i)%grid="grid_N_3D" |
---|
526 | i = i + 1; fields(i)%vname="smask"; fields(i)%grid="grid_N_3D" |
---|
527 | i = i + 1; fields(i)%vname="gdepw_n"; fields(i)%grid="grid_N_3D" |
---|
528 | i = i + 1; fields(i)%vname="e3t_n"; fields(i)%grid="grid_N_3D" |
---|
529 | i = i + 1; fields(i)%vname="e3u_n"; fields(i)%grid="grid_N_3D" |
---|
530 | i = i + 1; fields(i)%vname="e3v_n"; fields(i)%grid="grid_N_3D" |
---|
531 | i = i + 1; fields(i)%vname="surf_ini"; fields(i)%grid="grid_N" |
---|
532 | i = i + 1; fields(i)%vname="e3t_b"; fields(i)%grid="grid_N_3D" |
---|
533 | i = i + 1; fields(i)%vname="hmxl_n"; fields(i)%grid="grid_N_3D" |
---|
534 | i = i + 1; fields(i)%vname="un_bf"; fields(i)%grid="grid_N" |
---|
535 | i = i + 1; fields(i)%vname="vn_bf"; fields(i)%grid="grid_N" |
---|
536 | i = i + 1; fields(i)%vname="hbl"; fields(i)%grid="grid_N" |
---|
537 | i = i + 1; fields(i)%vname="hbli"; fields(i)%grid="grid_N" |
---|
538 | i = i + 1; fields(i)%vname="wn"; fields(i)%grid="grid_N_3D" |
---|
539 | |
---|
540 | IF( i-1 > max_rst_fields) THEN |
---|
541 | WRITE(ctmp1,*) 'E R R O R : iom_set_rst_vars SIZE of RST_FIELD array is too small' |
---|
542 | CALL ctl_stop( 'iom_set_rst_vars:', ctmp1 ) |
---|
543 | ENDIF |
---|
544 | END SUBROUTINE iom_set_rst_vars |
---|
545 | |
---|
546 | |
---|
547 | SUBROUTINE iom_set_rstw_active(cdrst_file) |
---|
548 | !!--------------------------------------------------------------------- |
---|
549 | !! *** SUBROUTINE iom_set_rstw_active *** |
---|
550 | !! |
---|
551 | !! ** Purpose : define file name in XIOS context for writing restart |
---|
552 | !! enable variables present in restart file for writing |
---|
553 | !!--------------------------------------------------------------------- |
---|
554 | !sets enabled = .TRUE. for each field in restart file |
---|
555 | CHARACTER(len=*) :: cdrst_file |
---|
556 | #if defined key_iomput |
---|
557 | TYPE(xios_field) :: field_hdl |
---|
558 | TYPE(xios_file) :: file_hdl |
---|
559 | TYPE(xios_filegroup) :: filegroup_hdl |
---|
560 | INTEGER :: i |
---|
561 | CHARACTER(lc) :: clpath |
---|
562 | |
---|
563 | !set name of the restart file and enable available fields |
---|
564 | IF(lwp) WRITE(numout,*) 'Setting restart filename (for XIOS write) to: ',cdrst_file |
---|
565 | CALL xios_get_handle("file_definition", filegroup_hdl ) |
---|
566 | CALL xios_add_child(filegroup_hdl, file_hdl, 'wrestart') |
---|
567 | IF(nxioso.eq.1) THEN |
---|
568 | CALL xios_set_file_attr( "wrestart", type="one_file", enabled=.TRUE.,& |
---|
569 | mode="write", output_freq=xios_timestep) |
---|
570 | if(lwp) write(numout,*) 'OPEN ', trim(cdrst_file), ' in one_file mode' |
---|
571 | ELSE |
---|
572 | CALL xios_set_file_attr( "wrestart", type="multiple_file", enabled=.TRUE.,& |
---|
573 | mode="write", output_freq=xios_timestep) |
---|
574 | if(lwp) write(numout,*) 'OPEN ', trim(cdrst_file), ' in multiple_file mode' |
---|
575 | ENDIF |
---|
576 | CALL xios_set_file_attr( "wrestart", name=trim(cdrst_file)) |
---|
577 | !define fields for restart context |
---|
578 | DO i = 1, max_rst_fields |
---|
579 | IF( rst_wfields(i)%active ) THEN |
---|
580 | CALL xios_add_child(file_hdl, field_hdl, TRIM(rst_wfields(i)%vname)) |
---|
581 | SELECT CASE (TRIM(rst_wfields(i)%grid)) |
---|
582 | CASE ("grid_N_3D") |
---|
583 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_wfields(i)%vname), & |
---|
584 | domain_ref="grid_N", axis_ref="nav_lev", prec = 8, operation = "instant") |
---|
585 | CASE ("grid_N") |
---|
586 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_wfields(i)%vname), & |
---|
587 | domain_ref="grid_N", prec = 8, operation = "instant") |
---|
588 | CASE ("grid_vector") |
---|
589 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_wfields(i)%vname), & |
---|
590 | axis_ref="nav_lev", prec = 8, operation = "instant") |
---|
591 | CASE ("grid_scalar") |
---|
592 | CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_wfields(i)%vname), & |
---|
593 | scalar_ref = "grid_scalar", prec = 8, operation = "instant") |
---|
594 | END SELECT |
---|
595 | ENDIF |
---|
596 | END DO |
---|
597 | #endif |
---|
598 | END SUBROUTINE iom_set_rstw_active |
---|
599 | |
---|
600 | SUBROUTINE iom_set_rst_context(ld_rstr) |
---|
601 | !!--------------------------------------------------------------------- |
---|
602 | !! *** SUBROUTINE iom_set_rst_context *** |
---|
603 | !! |
---|
604 | !! ** Purpose : Define domain, axis and grid for restart (read/write) |
---|
605 | !! context |
---|
606 | !! |
---|
607 | !!--------------------------------------------------------------------- |
---|
608 | LOGICAL, INTENT(IN) :: ld_rstr |
---|
609 | !ld_rstr is true for restart context. There is no need to define grid for |
---|
610 | !restart read, because it's read from file |
---|
611 | #if defined key_iomput |
---|
612 | TYPE(xios_domaingroup) :: domaingroup_hdl |
---|
613 | TYPE(xios_domain) :: domain_hdl |
---|
614 | TYPE(xios_axisgroup) :: axisgroup_hdl |
---|
615 | TYPE(xios_axis) :: axis_hdl |
---|
616 | TYPE(xios_scalar) :: scalar_hdl |
---|
617 | TYPE(xios_scalargroup) :: scalargroup_hdl |
---|
618 | |
---|
619 | CALL xios_get_handle("domain_definition",domaingroup_hdl) |
---|
620 | CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_N") |
---|
621 | CALL set_grid("N", glamt, gphit, .TRUE., ld_rstr) |
---|
622 | |
---|
623 | CALL xios_get_handle("axis_definition",axisgroup_hdl) |
---|
624 | CALL xios_add_child(axisgroup_hdl, axis_hdl, "nav_lev") |
---|
625 | !AGRIF fails to compile when unit= is in call to xios_set_axis_attr |
---|
626 | ! CALL xios_set_axis_attr( "nav_lev", long_name="Vertical levels", unit="m", positive="down") |
---|
627 | CALL xios_set_axis_attr( "nav_lev", long_name="Vertical levels in meters", positive="down") |
---|
628 | CALL iom_set_axis_attr( "nav_lev", paxis = gdept_1d ) |
---|
629 | |
---|
630 | CALL xios_get_handle("scalar_definition", scalargroup_hdl) |
---|
631 | CALL xios_add_child(scalargroup_hdl, scalar_hdl, "grid_scalar") |
---|
632 | #endif |
---|
633 | END SUBROUTINE iom_set_rst_context |
---|
634 | |
---|
635 | SUBROUTINE iom_swap( cdname ) |
---|
636 | !!--------------------------------------------------------------------- |
---|
637 | !! *** SUBROUTINE iom_swap *** |
---|
638 | !! |
---|
639 | !! ** Purpose : swap context between different agrif grid for xmlio_server |
---|
640 | !!--------------------------------------------------------------------- |
---|
641 | CHARACTER(len=*), INTENT(in) :: cdname |
---|
642 | #if defined key_iomput |
---|
643 | TYPE(xios_context) :: nemo_hdl |
---|
644 | |
---|
645 | IF( TRIM(Agrif_CFixed()) == '0' ) THEN |
---|
646 | CALL xios_get_handle(TRIM(cdname),nemo_hdl) |
---|
647 | ELSE |
---|
648 | CALL xios_get_handle(TRIM(Agrif_CFixed())//"_"//TRIM(cdname),nemo_hdl) |
---|
649 | ENDIF |
---|
650 | ! |
---|
651 | CALL xios_set_current_context(nemo_hdl) |
---|
652 | #endif |
---|
653 | ! |
---|
654 | END SUBROUTINE iom_swap |
---|
655 | |
---|
656 | |
---|
657 | SUBROUTINE iom_open( cdname, kiomid, ldwrt, ldstop, ldiof, kdlev, cdcomp ) |
---|
658 | !!--------------------------------------------------------------------- |
---|
659 | !! *** SUBROUTINE iom_open *** |
---|
660 | !! |
---|
661 | !! ** Purpose : open an input file (return 0 if not found) |
---|
662 | !!--------------------------------------------------------------------- |
---|
663 | CHARACTER(len=*), INTENT(in ) :: cdname ! File name |
---|
664 | INTEGER , INTENT( out) :: kiomid ! iom identifier of the opened file |
---|
665 | LOGICAL , INTENT(in ), OPTIONAL :: ldwrt ! open in write modeb (default = .FALSE.) |
---|
666 | LOGICAL , INTENT(in ), OPTIONAL :: ldstop ! stop if open to read a non-existing file (default = .TRUE.) |
---|
667 | LOGICAL , INTENT(in ), OPTIONAL :: ldiof ! Interp On the Fly, needed for AGRIF (default = .FALSE.) |
---|
668 | INTEGER , INTENT(in ), OPTIONAL :: kdlev ! number of vertical levels |
---|
669 | CHARACTER(len=3), INTENT(in ), OPTIONAL :: cdcomp ! name of component calling iom_nf90_open |
---|
670 | ! |
---|
671 | CHARACTER(LEN=256) :: clname ! the name of the file based on cdname [[+clcpu]+clcpu] |
---|
672 | CHARACTER(LEN=256) :: cltmpn ! tempory name to store clname (in writting mode) |
---|
673 | CHARACTER(LEN=10) :: clsuffix ! ".nc" |
---|
674 | CHARACTER(LEN=15) :: clcpu ! the cpu number (max jpmax_digits digits) |
---|
675 | CHARACTER(LEN=256) :: clinfo ! info character |
---|
676 | LOGICAL :: llok ! check the existence |
---|
677 | LOGICAL :: llwrt ! local definition of ldwrt |
---|
678 | LOGICAL :: llstop ! local definition of ldstop |
---|
679 | LOGICAL :: lliof ! local definition of ldiof |
---|
680 | INTEGER :: icnt ! counter for digits in clcpu (max = jpmax_digits) |
---|
681 | INTEGER :: iln, ils ! lengths of character |
---|
682 | INTEGER :: istop ! |
---|
683 | ! local number of points for x,y dimensions |
---|
684 | ! position of first local point for x,y dimensions |
---|
685 | ! position of last local point for x,y dimensions |
---|
686 | ! start halo size for x,y dimensions |
---|
687 | ! end halo size for x,y dimensions |
---|
688 | !--------------------------------------------------------------------- |
---|
689 | ! Initializations and control |
---|
690 | ! ============= |
---|
691 | kiomid = -1 |
---|
692 | clinfo = ' iom_open ~~~ ' |
---|
693 | istop = nstop |
---|
694 | ! if iom_open is called for the first time: initialize iom_file(:)%nfid to 0 |
---|
695 | ! (could be done when defining iom_file in f95 but not in f90) |
---|
696 | IF( Agrif_Root() ) THEN |
---|
697 | IF( iom_open_init == 0 ) THEN |
---|
698 | iom_file(:)%nfid = 0 |
---|
699 | iom_open_init = 1 |
---|
700 | ENDIF |
---|
701 | ENDIF |
---|
702 | ! do we read or write the file? |
---|
703 | IF( PRESENT(ldwrt) ) THEN ; llwrt = ldwrt |
---|
704 | ELSE ; llwrt = .FALSE. |
---|
705 | ENDIF |
---|
706 | ! do we call ctl_stop if we try to open a non-existing file in read mode? |
---|
707 | IF( PRESENT(ldstop) ) THEN ; llstop = ldstop |
---|
708 | ELSE ; llstop = .TRUE. |
---|
709 | ENDIF |
---|
710 | ! are we using interpolation on the fly? |
---|
711 | IF( PRESENT(ldiof) ) THEN ; lliof = ldiof |
---|
712 | ELSE ; lliof = .FALSE. |
---|
713 | ENDIF |
---|
714 | ! create the file name by added, if needed, TRIM(Agrif_CFixed()) and TRIM(clsuffix) |
---|
715 | ! ============= |
---|
716 | clname = trim(cdname) |
---|
717 | IF ( .NOT. Agrif_Root() .AND. .NOT. lliof ) THEN |
---|
718 | iln = INDEX(clname,'/') |
---|
719 | cltmpn = clname(1:iln) |
---|
720 | clname = clname(iln+1:LEN_TRIM(clname)) |
---|
721 | clname=TRIM(cltmpn)//TRIM(Agrif_CFixed())//'_'//TRIM(clname) |
---|
722 | ENDIF |
---|
723 | ! which suffix should we use? |
---|
724 | clsuffix = '.nc' |
---|
725 | ! Add the suffix if needed |
---|
726 | iln = LEN_TRIM(clname) |
---|
727 | ils = LEN_TRIM(clsuffix) |
---|
728 | IF( iln <= ils .OR. INDEX( TRIM(clname), TRIM(clsuffix), back = .TRUE. ) /= iln - ils + 1 ) & |
---|
729 | & clname = TRIM(clname)//TRIM(clsuffix) |
---|
730 | cltmpn = clname ! store this name |
---|
731 | ! try to find if the file to be opened already exist |
---|
732 | ! ============= |
---|
733 | INQUIRE( FILE = clname, EXIST = llok ) |
---|
734 | IF( .NOT.llok ) THEN |
---|
735 | ! we try to add the cpu number to the name |
---|
736 | WRITE(clcpu,*) narea-1 |
---|
737 | |
---|
738 | clcpu = TRIM(ADJUSTL(clcpu)) |
---|
739 | iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.) |
---|
740 | clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix) |
---|
741 | icnt = 0 |
---|
742 | INQUIRE( FILE = clname, EXIST = llok ) |
---|
743 | ! we try different formats for the cpu number by adding 0 |
---|
744 | DO WHILE( .NOT.llok .AND. icnt < jpmax_digits ) |
---|
745 | clcpu = "0"//trim(clcpu) |
---|
746 | clname = clname(1:iln-1)//'_'//TRIM(clcpu)//TRIM(clsuffix) |
---|
747 | INQUIRE( FILE = clname, EXIST = llok ) |
---|
748 | icnt = icnt + 1 |
---|
749 | END DO |
---|
750 | ELSE |
---|
751 | lxios_sini = .TRUE. |
---|
752 | ENDIF |
---|
753 | ! Open the NetCDF file |
---|
754 | ! ============= |
---|
755 | ! do we have some free file identifier? |
---|
756 | IF( MINVAL(iom_file(:)%nfid) /= 0 ) & |
---|
757 | & CALL ctl_stop( TRIM(clinfo), 'No more free file identifier', 'increase jpmax_files in iom_def' ) |
---|
758 | ! if no file was found... |
---|
759 | IF( .NOT. llok ) THEN |
---|
760 | IF( .NOT. llwrt ) THEN ! we are in read mode |
---|
761 | IF( llstop ) THEN ; CALL ctl_stop( TRIM(clinfo), 'File '//TRIM(cltmpn)//'* not found' ) |
---|
762 | ELSE ; istop = nstop + 1 ! make sure that istop /= nstop so we don't open the file |
---|
763 | ENDIF |
---|
764 | ELSE ! we are in write mode so we |
---|
765 | clname = cltmpn ! get back the file name without the cpu number |
---|
766 | ENDIF |
---|
767 | ELSE |
---|
768 | IF( llwrt .AND. .NOT. ln_clobber ) THEN ! we stop as we want to write in a new file |
---|
769 | CALL ctl_stop( TRIM(clinfo), 'We want to write in a new file but '//TRIM(clname)//' already exists...' ) |
---|
770 | istop = nstop + 1 ! make sure that istop /= nstop so we don't open the file |
---|
771 | ELSEIF( llwrt ) THEN ! the file exists and we are in write mode with permission to |
---|
772 | clname = cltmpn ! overwrite so get back the file name without the cpu number |
---|
773 | ENDIF |
---|
774 | ENDIF |
---|
775 | IF( istop == nstop ) THEN ! no error within this routine |
---|
776 | CALL iom_nf90_open( clname, kiomid, llwrt, llok, kdlev = kdlev, cdcomp = cdcomp ) |
---|
777 | ENDIF |
---|
778 | ! |
---|
779 | END SUBROUTINE iom_open |
---|
780 | |
---|
781 | |
---|
782 | SUBROUTINE iom_close( kiomid ) |
---|
783 | !!-------------------------------------------------------------------- |
---|
784 | !! *** SUBROUTINE iom_close *** |
---|
785 | !! |
---|
786 | !! ** Purpose : close an input file, or all files opened by iom |
---|
787 | !!-------------------------------------------------------------------- |
---|
788 | INTEGER, INTENT(inout), OPTIONAL :: kiomid ! iom identifier of the file to be closed |
---|
789 | ! ! return 0 when file is properly closed |
---|
790 | ! ! No argument: all files opened by iom are closed |
---|
791 | |
---|
792 | INTEGER :: jf ! dummy loop indices |
---|
793 | INTEGER :: i_s, i_e ! temporary integer |
---|
794 | CHARACTER(LEN=100) :: clinfo ! info character |
---|
795 | !--------------------------------------------------------------------- |
---|
796 | ! |
---|
797 | IF( iom_open_init == 0 ) RETURN ! avoid to use iom_file(jf)%nfid that us not yet initialized |
---|
798 | ! |
---|
799 | clinfo = ' iom_close ~~~ ' |
---|
800 | IF( PRESENT(kiomid) ) THEN |
---|
801 | i_s = kiomid |
---|
802 | i_e = kiomid |
---|
803 | ELSE |
---|
804 | i_s = 1 |
---|
805 | i_e = jpmax_files |
---|
806 | ENDIF |
---|
807 | |
---|
808 | IF( i_s > 0 ) THEN |
---|
809 | DO jf = i_s, i_e |
---|
810 | IF( iom_file(jf)%nfid > 0 ) THEN |
---|
811 | CALL iom_nf90_close( jf ) |
---|
812 | iom_file(jf)%nfid = 0 ! free the id |
---|
813 | IF( PRESENT(kiomid) ) kiomid = 0 ! return 0 as id to specify that the file was closed |
---|
814 | IF(lwp) WRITE(numout,*) TRIM(clinfo)//' close file: '//TRIM(iom_file(jf)%name)//' ok' |
---|
815 | ELSEIF( PRESENT(kiomid) ) THEN |
---|
816 | WRITE(ctmp1,*) '--->', kiomid |
---|
817 | CALL ctl_stop( TRIM(clinfo)//' Invalid file identifier', ctmp1 ) |
---|
818 | ENDIF |
---|
819 | END DO |
---|
820 | ENDIF |
---|
821 | ! |
---|
822 | END SUBROUTINE iom_close |
---|
823 | |
---|
824 | |
---|
825 | FUNCTION iom_varid ( kiomid, cdvar, kdimsz, kndims, lduld, ldstop ) |
---|
826 | !!----------------------------------------------------------------------- |
---|
827 | !! *** FUNCTION iom_varid *** |
---|
828 | !! |
---|
829 | !! ** Purpose : get the id of a variable in a file (return 0 if not found) |
---|
830 | !!----------------------------------------------------------------------- |
---|
831 | INTEGER , INTENT(in ) :: kiomid ! file Identifier |
---|
832 | CHARACTER(len=*) , INTENT(in ) :: cdvar ! name of the variable |
---|
833 | INTEGER, DIMENSION(:), INTENT( out), OPTIONAL :: kdimsz ! size of each dimension |
---|
834 | INTEGER , INTENT( out), OPTIONAL :: kndims ! number of dimensions |
---|
835 | LOGICAL , INTENT( out), OPTIONAL :: lduld ! true if the last dimension is unlimited (time) |
---|
836 | LOGICAL , INTENT(in ), OPTIONAL :: ldstop ! stop if looking for non-existing variable (default = .TRUE.) |
---|
837 | ! |
---|
838 | INTEGER :: iom_varid, iiv, i_nvd |
---|
839 | LOGICAL :: ll_fnd |
---|
840 | CHARACTER(LEN=100) :: clinfo ! info character |
---|
841 | LOGICAL :: llstop ! local definition of ldstop |
---|
842 | !!----------------------------------------------------------------------- |
---|
843 | iom_varid = 0 ! default definition |
---|
844 | ! do we call ctl_stop if we look for non-existing variable? |
---|
845 | IF( PRESENT(ldstop) ) THEN ; llstop = ldstop |
---|
846 | ELSE ; llstop = .TRUE. |
---|
847 | ENDIF |
---|
848 | ! |
---|
849 | IF( kiomid > 0 ) THEN |
---|
850 | clinfo = 'iom_varid, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(cdvar) |
---|
851 | IF( iom_file(kiomid)%nfid == 0 ) THEN |
---|
852 | CALL ctl_stop( trim(clinfo), 'the file is not open' ) |
---|
853 | ELSE |
---|
854 | ll_fnd = .FALSE. |
---|
855 | iiv = 0 |
---|
856 | ! |
---|
857 | DO WHILE ( .NOT.ll_fnd .AND. iiv < iom_file(kiomid)%nvars ) |
---|
858 | iiv = iiv + 1 |
---|
859 | ll_fnd = ( TRIM(cdvar) == TRIM(iom_file(kiomid)%cn_var(iiv)) ) |
---|
860 | END DO |
---|
861 | ! |
---|
862 | IF( .NOT.ll_fnd ) THEN |
---|
863 | iiv = iiv + 1 |
---|
864 | IF( iiv <= jpmax_vars ) THEN |
---|
865 | iom_varid = iom_nf90_varid( kiomid, cdvar, iiv, kdimsz, kndims, lduld ) |
---|
866 | ELSE |
---|
867 | CALL ctl_stop( trim(clinfo), 'Too many variables in the file '//iom_file(kiomid)%name, & |
---|
868 | & 'increase the parameter jpmax_vars') |
---|
869 | ENDIF |
---|
870 | IF( llstop .AND. iom_varid == -1 ) CALL ctl_stop( TRIM(clinfo)//' not found' ) |
---|
871 | ELSE |
---|
872 | iom_varid = iiv |
---|
873 | IF( PRESENT(kdimsz) ) THEN |
---|
874 | i_nvd = iom_file(kiomid)%ndims(iiv) |
---|
875 | IF( i_nvd <= size(kdimsz) ) THEN |
---|
876 | kdimsz(1:i_nvd) = iom_file(kiomid)%dimsz(1:i_nvd,iiv) |
---|
877 | ELSE |
---|
878 | WRITE(ctmp1,*) i_nvd, size(kdimsz) |
---|
879 | CALL ctl_stop( trim(clinfo), 'error in kdimsz size'//trim(ctmp1) ) |
---|
880 | ENDIF |
---|
881 | ENDIF |
---|
882 | IF( PRESENT(kndims) ) kndims = iom_file(kiomid)%ndims(iiv) |
---|
883 | IF( PRESENT( lduld) ) lduld = iom_file(kiomid)%luld( iiv) |
---|
884 | ENDIF |
---|
885 | ENDIF |
---|
886 | ENDIF |
---|
887 | ! |
---|
888 | END FUNCTION iom_varid |
---|
889 | |
---|
890 | |
---|
891 | !!---------------------------------------------------------------------- |
---|
892 | !! INTERFACE iom_get |
---|
893 | !!---------------------------------------------------------------------- |
---|
894 | SUBROUTINE iom_g0d_sp( kiomid, cdvar, pvar, ktime, ldxios ) |
---|
895 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
896 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
897 | REAL(sp) , INTENT( out) :: pvar ! read field |
---|
898 | REAL(dp) :: ztmp_pvar ! tmp var to read field |
---|
899 | INTEGER , INTENT(in ), OPTIONAL :: ktime ! record number |
---|
900 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! use xios to read restart |
---|
901 | ! |
---|
902 | INTEGER :: idvar ! variable id |
---|
903 | INTEGER :: idmspc ! number of spatial dimensions |
---|
904 | INTEGER , DIMENSION(1) :: itime ! record number |
---|
905 | CHARACTER(LEN=100) :: clinfo ! info character |
---|
906 | CHARACTER(LEN=100) :: clname ! file name |
---|
907 | CHARACTER(LEN=1) :: cldmspc ! |
---|
908 | LOGICAL :: llxios |
---|
909 | ! |
---|
910 | llxios = .FALSE. |
---|
911 | IF( PRESENT(ldxios) ) llxios = ldxios |
---|
912 | |
---|
913 | IF(.NOT.llxios) THEN ! read data using default library |
---|
914 | itime = 1 |
---|
915 | IF( PRESENT(ktime) ) itime = ktime |
---|
916 | ! |
---|
917 | clname = iom_file(kiomid)%name |
---|
918 | clinfo = ' iom_g0d, file: '//trim(clname)//', var: '//trim(cdvar) |
---|
919 | ! |
---|
920 | IF( kiomid > 0 ) THEN |
---|
921 | idvar = iom_varid( kiomid, cdvar ) |
---|
922 | IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN |
---|
923 | idmspc = iom_file ( kiomid )%ndims( idvar ) |
---|
924 | IF( iom_file(kiomid)%luld(idvar) ) idmspc = idmspc - 1 |
---|
925 | WRITE(cldmspc , fmt='(i1)') idmspc |
---|
926 | IF( idmspc > 0 ) CALL ctl_stop( TRIM(clinfo), 'When reading to a 0D array, we do not accept data', & |
---|
927 | & 'with 1 or more spatial dimensions: '//cldmspc//' were found.' , & |
---|
928 | & 'Use ncwa -a to suppress the unnecessary dimensions' ) |
---|
929 | CALL iom_nf90_get( kiomid, idvar, ztmp_pvar, itime ) |
---|
930 | pvar = ztmp_pvar |
---|
931 | ENDIF |
---|
932 | ENDIF |
---|
933 | ELSE |
---|
934 | #if defined key_iomput |
---|
935 | IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) |
---|
936 | CALL iom_swap( TRIM(crxios_context) ) |
---|
937 | CALL xios_recv_field( trim(cdvar), pvar) |
---|
938 | CALL iom_swap( TRIM(cxios_context) ) |
---|
939 | #else |
---|
940 | WRITE(ctmp1,*) 'Can not use XIOS in iom_g0d, file: '//trim(clname)//', var:'//trim(cdvar) |
---|
941 | CALL ctl_stop( 'iom_g0d', ctmp1 ) |
---|
942 | #endif |
---|
943 | ENDIF |
---|
944 | END SUBROUTINE iom_g0d_sp |
---|
945 | |
---|
946 | SUBROUTINE iom_g0d_dp( kiomid, cdvar, pvar, ktime, ldxios ) |
---|
947 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
948 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
949 | REAL(dp) , INTENT( out) :: pvar ! read field |
---|
950 | INTEGER , INTENT(in ), OPTIONAL :: ktime ! record number |
---|
951 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! use xios to read restart |
---|
952 | ! |
---|
953 | INTEGER :: idvar ! variable id |
---|
954 | INTEGER :: idmspc ! number of spatial dimensions |
---|
955 | INTEGER , DIMENSION(1) :: itime ! record number |
---|
956 | CHARACTER(LEN=100) :: clinfo ! info character |
---|
957 | CHARACTER(LEN=100) :: clname ! file name |
---|
958 | CHARACTER(LEN=1) :: cldmspc ! |
---|
959 | LOGICAL :: llxios |
---|
960 | ! |
---|
961 | llxios = .FALSE. |
---|
962 | IF( PRESENT(ldxios) ) llxios = ldxios |
---|
963 | |
---|
964 | IF(.NOT.llxios) THEN ! read data using default library |
---|
965 | itime = 1 |
---|
966 | IF( PRESENT(ktime) ) itime = ktime |
---|
967 | ! |
---|
968 | clname = iom_file(kiomid)%name |
---|
969 | clinfo = ' iom_g0d, file: '//trim(clname)//', var: '//trim(cdvar) |
---|
970 | ! |
---|
971 | IF( kiomid > 0 ) THEN |
---|
972 | idvar = iom_varid( kiomid, cdvar ) |
---|
973 | IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN |
---|
974 | idmspc = iom_file ( kiomid )%ndims( idvar ) |
---|
975 | IF( iom_file(kiomid)%luld(idvar) ) idmspc = idmspc - 1 |
---|
976 | WRITE(cldmspc , fmt='(i1)') idmspc |
---|
977 | IF( idmspc > 0 ) CALL ctl_stop( TRIM(clinfo), 'When reading to a 0D array, we do not accept data', & |
---|
978 | & 'with 1 or more spatial dimensions: '//cldmspc//' were found.' , & |
---|
979 | & 'Use ncwa -a to suppress the unnecessary dimensions' ) |
---|
980 | CALL iom_nf90_get( kiomid, idvar, pvar, itime ) |
---|
981 | ENDIF |
---|
982 | ENDIF |
---|
983 | ELSE |
---|
984 | #if defined key_iomput |
---|
985 | IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) |
---|
986 | CALL iom_swap( TRIM(crxios_context) ) |
---|
987 | CALL xios_recv_field( trim(cdvar), pvar) |
---|
988 | CALL iom_swap( TRIM(cxios_context) ) |
---|
989 | #else |
---|
990 | WRITE(ctmp1,*) 'Can not use XIOS in iom_g0d, file: '//trim(clname)//', var:'//trim(cdvar) |
---|
991 | CALL ctl_stop( 'iom_g0d', ctmp1 ) |
---|
992 | #endif |
---|
993 | ENDIF |
---|
994 | END SUBROUTINE iom_g0d_dp |
---|
995 | |
---|
996 | SUBROUTINE iom_g1d_sp( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, ldxios ) |
---|
997 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
998 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
999 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1000 | REAL(sp) , INTENT( out), DIMENSION(:) :: pvar ! read field |
---|
1001 | REAL(dp) , ALLOCATABLE , DIMENSION(:) :: ztmp_pvar ! tmp var to read field |
---|
1002 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1003 | INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kstart ! start axis position of the reading |
---|
1004 | INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kcount ! number of points in each axis |
---|
1005 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1006 | ! |
---|
1007 | IF( kiomid > 0 ) THEN |
---|
1008 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1009 | ALLOCATE(ztmp_pvar(size(pvar,1))) |
---|
1010 | CALL iom_get_123d( kiomid, kdom , cdvar , pv_r1d=ztmp_pvar, & |
---|
1011 | & ktime=ktime, kstart=kstart, kcount=kcount, & |
---|
1012 | & ldxios=ldxios ) |
---|
1013 | pvar = ztmp_pvar |
---|
1014 | DEALLOCATE(ztmp_pvar) |
---|
1015 | END IF |
---|
1016 | ENDIF |
---|
1017 | END SUBROUTINE iom_g1d_sp |
---|
1018 | |
---|
1019 | |
---|
1020 | SUBROUTINE iom_g1d_dp( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, ldxios ) |
---|
1021 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1022 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1023 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1024 | REAL(dp) , INTENT( out), DIMENSION(:) :: pvar ! read field |
---|
1025 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1026 | INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kstart ! start axis position of the reading |
---|
1027 | INTEGER , INTENT(in ), DIMENSION(1), OPTIONAL :: kcount ! number of points in each axis |
---|
1028 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1029 | ! |
---|
1030 | IF( kiomid > 0 ) THEN |
---|
1031 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom , cdvar , pv_r1d=pvar, & |
---|
1032 | & ktime=ktime, kstart=kstart, kcount=kcount, & |
---|
1033 | & ldxios=ldxios ) |
---|
1034 | ENDIF |
---|
1035 | END SUBROUTINE iom_g1d_dp |
---|
1036 | |
---|
1037 | SUBROUTINE iom_g2d_sp( kiomid, kdom, cdvar, pvar, ktime, cd_type, psgn, kfill, kstart, kcount, ldxios) |
---|
1038 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1039 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1040 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1041 | REAL(sp) , INTENT( out), DIMENSION(:,:) :: pvar ! read field |
---|
1042 | REAL(dp) , ALLOCATABLE , DIMENSION(:,:) :: ztmp_pvar ! tmp var to read field |
---|
1043 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1044 | CHARACTER(len=1), INTENT(in ) , OPTIONAL :: cd_type ! nature of grid-points (T, U, V, F, W) |
---|
1045 | REAL(dp) , INTENT(in ) , OPTIONAL :: psgn ! -1.(1.): (not) change sign across the north fold |
---|
1046 | INTEGER , INTENT(in ) , OPTIONAL :: kfill ! value of kfillmode in lbc_lbk |
---|
1047 | INTEGER , INTENT(in ), DIMENSION(2), OPTIONAL :: kstart ! start axis position of the reading |
---|
1048 | INTEGER , INTENT(in ), DIMENSION(2), OPTIONAL :: kcount ! number of points in each axis |
---|
1049 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1050 | ! |
---|
1051 | IF( kiomid > 0 ) THEN |
---|
1052 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1053 | ALLOCATE(ztmp_pvar(size(pvar,1), size(pvar,2))) |
---|
1054 | CALL iom_get_123d( kiomid, kdom, cdvar , pv_r2d = ztmp_pvar , ktime = ktime, & |
---|
1055 | & cd_type = cd_type, psgn = psgn , kfill = kfill, & |
---|
1056 | & kstart = kstart , kcount = kcount, ldxios=ldxios ) |
---|
1057 | pvar = ztmp_pvar |
---|
1058 | DEALLOCATE(ztmp_pvar) |
---|
1059 | ENDIF |
---|
1060 | ENDIF |
---|
1061 | END SUBROUTINE iom_g2d_sp |
---|
1062 | |
---|
1063 | SUBROUTINE iom_g2d_dp( kiomid, kdom, cdvar, pvar, ktime, cd_type, psgn, kfill, kstart, kcount, ldxios) |
---|
1064 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1065 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1066 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1067 | REAL(dp) , INTENT( out), DIMENSION(:,:) :: pvar ! read field |
---|
1068 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1069 | CHARACTER(len=1), INTENT(in ) , OPTIONAL :: cd_type ! nature of grid-points (T, U, V, F, W) |
---|
1070 | REAL(dp) , INTENT(in ) , OPTIONAL :: psgn ! -1.(1.): (not) change sign across the north fold |
---|
1071 | INTEGER , INTENT(in ) , OPTIONAL :: kfill ! value of kfillmode in lbc_lbk |
---|
1072 | INTEGER , INTENT(in ), DIMENSION(2), OPTIONAL :: kstart ! start axis position of the reading |
---|
1073 | INTEGER , INTENT(in ), DIMENSION(2), OPTIONAL :: kcount ! number of points in each axis |
---|
1074 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1075 | ! |
---|
1076 | IF( kiomid > 0 ) THEN |
---|
1077 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom, cdvar , pv_r2d = pvar , ktime = ktime, & |
---|
1078 | & cd_type = cd_type, psgn = psgn , kfill = kfill, & |
---|
1079 | & kstart = kstart , kcount = kcount, ldxios=ldxios ) |
---|
1080 | ENDIF |
---|
1081 | END SUBROUTINE iom_g2d_dp |
---|
1082 | |
---|
1083 | SUBROUTINE iom_g3d_sp( kiomid, kdom, cdvar, pvar, ktime, cd_type, psgn, kfill, kstart, kcount, ldxios ) |
---|
1084 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1085 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1086 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1087 | REAL(sp) , INTENT( out), DIMENSION(:,:,:) :: pvar ! read field |
---|
1088 | REAL(dp) , ALLOCATABLE , DIMENSION(:,:,:) :: ztmp_pvar ! tmp var to read field |
---|
1089 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1090 | CHARACTER(len=1), INTENT(in ) , OPTIONAL :: cd_type ! nature of grid-points (T, U, V, F, W) |
---|
1091 | REAL(dp) , INTENT(in ) , OPTIONAL :: psgn ! -1.(1.) : (not) change sign across the north fold |
---|
1092 | INTEGER , INTENT(in ) , OPTIONAL :: kfill ! value of kfillmode in lbc_lbk |
---|
1093 | INTEGER , INTENT(in ), DIMENSION(3), OPTIONAL :: kstart ! start axis position of the reading |
---|
1094 | INTEGER , INTENT(in ), DIMENSION(3), OPTIONAL :: kcount ! number of points in each axis |
---|
1095 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1096 | ! |
---|
1097 | IF( kiomid > 0 ) THEN |
---|
1098 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1099 | ALLOCATE(ztmp_pvar(size(pvar,1), size(pvar,2), size(pvar,3))) |
---|
1100 | CALL iom_get_123d( kiomid, kdom, cdvar , pv_r3d = ztmp_pvar , ktime = ktime, & |
---|
1101 | & cd_type = cd_type, psgn = psgn , kfill = kfill, & |
---|
1102 | & kstart = kstart , kcount = kcount, ldxios=ldxios ) |
---|
1103 | pvar = ztmp_pvar |
---|
1104 | DEALLOCATE(ztmp_pvar) |
---|
1105 | END IF |
---|
1106 | ENDIF |
---|
1107 | END SUBROUTINE iom_g3d_sp |
---|
1108 | |
---|
1109 | SUBROUTINE iom_g3d_dp( kiomid, kdom, cdvar, pvar, ktime, cd_type, psgn, kfill, kstart, kcount, ldxios ) |
---|
1110 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1111 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1112 | CHARACTER(len=*), INTENT(in ) :: cdvar ! Name of the variable |
---|
1113 | REAL(dp) , INTENT( out), DIMENSION(:,:,:) :: pvar ! read field |
---|
1114 | INTEGER , INTENT(in ) , OPTIONAL :: ktime ! record number |
---|
1115 | CHARACTER(len=1), INTENT(in ) , OPTIONAL :: cd_type ! nature of grid-points (T, U, V, F, W) |
---|
1116 | REAL(dp) , INTENT(in ) , OPTIONAL :: psgn ! -1.(1.) : (not) change sign across the north fold |
---|
1117 | INTEGER , INTENT(in ) , OPTIONAL :: kfill ! value of kfillmode in lbc_lbk |
---|
1118 | INTEGER , INTENT(in ), DIMENSION(3), OPTIONAL :: kstart ! start axis position of the reading |
---|
1119 | INTEGER , INTENT(in ), DIMENSION(3), OPTIONAL :: kcount ! number of points in each axis |
---|
1120 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! read data using XIOS |
---|
1121 | ! |
---|
1122 | IF( kiomid > 0 ) THEN |
---|
1123 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1124 | CALL iom_get_123d( kiomid, kdom, cdvar , pv_r3d = pvar , ktime = ktime, & |
---|
1125 | & cd_type = cd_type, psgn = psgn , kfill = kfill, & |
---|
1126 | & kstart = kstart , kcount = kcount, ldxios=ldxios ) |
---|
1127 | END IF |
---|
1128 | ENDIF |
---|
1129 | END SUBROUTINE iom_g3d_dp |
---|
1130 | |
---|
1131 | !!---------------------------------------------------------------------- |
---|
1132 | |
---|
1133 | SUBROUTINE iom_get_123d( kiomid , kdom, cdvar, pv_r1d, pv_r2d, pv_r3d, ktime , & |
---|
1134 | & cd_type, psgn, kfill, kstart, kcount, ldxios ) |
---|
1135 | !!----------------------------------------------------------------------- |
---|
1136 | !! *** ROUTINE iom_get_123d *** |
---|
1137 | !! |
---|
1138 | !! ** Purpose : read a 1D/2D/3D variable |
---|
1139 | !! |
---|
1140 | !! ** Method : read ONE record at each CALL |
---|
1141 | !!----------------------------------------------------------------------- |
---|
1142 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1143 | INTEGER , INTENT(in ) :: kdom ! Type of domain to be read |
---|
1144 | CHARACTER(len=*) , INTENT(in ) :: cdvar ! Name of the variable |
---|
1145 | REAL(dp), DIMENSION(:) , INTENT( out), OPTIONAL :: pv_r1d ! read field (1D case) |
---|
1146 | REAL(dp), DIMENSION(:,:) , INTENT( out), OPTIONAL :: pv_r2d ! read field (2D case) |
---|
1147 | REAL(dp), DIMENSION(:,:,:) , INTENT( out), OPTIONAL :: pv_r3d ! read field (3D case) |
---|
1148 | INTEGER , INTENT(in ), OPTIONAL :: ktime ! record number |
---|
1149 | CHARACTER(len=1) , INTENT(in ), OPTIONAL :: cd_type ! nature of grid-points (T, U, V, F, W) |
---|
1150 | REAL(dp) , INTENT(in ), OPTIONAL :: psgn ! -1.(1.) : (not) change sign across the north fold |
---|
1151 | INTEGER , INTENT(in ), OPTIONAL :: kfill ! value of kfillmode in lbc_lbk |
---|
1152 | INTEGER , DIMENSION(:) , INTENT(in ), OPTIONAL :: kstart ! start position of the reading in each axis |
---|
1153 | INTEGER , DIMENSION(:) , INTENT(in ), OPTIONAL :: kcount ! number of points to be read in each axis |
---|
1154 | LOGICAL , INTENT(in ), OPTIONAL :: ldxios ! use XIOS to read restart |
---|
1155 | ! |
---|
1156 | LOGICAL :: llok ! true if ok! |
---|
1157 | LOGICAL :: llxios ! local definition for XIOS read |
---|
1158 | INTEGER :: jl ! loop on number of dimension |
---|
1159 | INTEGER :: idom ! type of domain |
---|
1160 | INTEGER :: idvar ! id of the variable |
---|
1161 | INTEGER :: inbdim ! number of dimensions of the variable |
---|
1162 | INTEGER :: idmspc ! number of spatial dimensions |
---|
1163 | INTEGER :: itime ! record number |
---|
1164 | INTEGER :: istop ! temporary value of nstop |
---|
1165 | INTEGER :: ix1, ix2, iy1, iy2 ! subdomain indexes |
---|
1166 | INTEGER :: ji, jj ! loop counters |
---|
1167 | INTEGER :: irankpv ! |
---|
1168 | INTEGER :: ind1, ind2 ! substring index |
---|
1169 | INTEGER, DIMENSION(jpmax_dims) :: istart ! starting point to read for each axis |
---|
1170 | INTEGER, DIMENSION(jpmax_dims) :: icnt ! number of value to read along each axis |
---|
1171 | INTEGER, DIMENSION(jpmax_dims) :: idimsz ! size of the dimensions of the variable |
---|
1172 | INTEGER, DIMENSION(jpmax_dims) :: ishape ! size of the dimensions of the variable |
---|
1173 | REAL(dp) :: zscf, zofs ! sacle_factor and add_offset |
---|
1174 | REAL(wp) :: zsgn ! local value of psgn |
---|
1175 | INTEGER :: itmp ! temporary integer |
---|
1176 | CHARACTER(LEN=256) :: clinfo ! info character |
---|
1177 | CHARACTER(LEN=256) :: clname ! file name |
---|
1178 | CHARACTER(LEN=1) :: clrankpv, cldmspc ! |
---|
1179 | CHARACTER(LEN=1) :: cl_type ! local value of cd_type |
---|
1180 | LOGICAL :: ll_only3rd ! T => if kstart, kcount present then *only* use values for 3rd spatial dimension. |
---|
1181 | INTEGER :: inlev ! number of levels for 3D data |
---|
1182 | REAL(dp) :: gma, gmi |
---|
1183 | !--------------------------------------------------------------------- |
---|
1184 | ! |
---|
1185 | inlev = -1 |
---|
1186 | IF( PRESENT(pv_r3d) ) inlev = SIZE(pv_r3d, 3) |
---|
1187 | ! |
---|
1188 | llxios = .FALSE. |
---|
1189 | IF( PRESENT(ldxios) ) llxios = ldxios |
---|
1190 | ! |
---|
1191 | idom = kdom |
---|
1192 | istop = nstop |
---|
1193 | ! |
---|
1194 | IF(.NOT.llxios) THEN |
---|
1195 | clname = iom_file(kiomid)%name ! esier to read |
---|
1196 | clinfo = ' iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) |
---|
1197 | ! check kcount and kstart optionals parameters... |
---|
1198 | IF( PRESENT(kcount) .AND. .NOT. PRESENT(kstart) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') |
---|
1199 | IF( PRESENT(kstart) .AND. .NOT. PRESENT(kcount) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') |
---|
1200 | IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND. idom /= jpdom_auto_xy ) & |
---|
1201 | & CALL ctl_stop(TRIM(clinfo), 'kstart present needs idom = jpdom_unknown or idom = jpdom_auto_xy') |
---|
1202 | IF( idom == jpdom_auto_xy .AND. .NOT. PRESENT(kstart) ) & |
---|
1203 | & CALL ctl_stop(TRIM(clinfo), 'idom = jpdom_auto_xy requires kstart to be present') |
---|
1204 | ! |
---|
1205 | ! Search for the variable in the data base (eventually actualize data) |
---|
1206 | ! |
---|
1207 | idvar = iom_varid( kiomid, cdvar ) |
---|
1208 | IF( idvar > 0 ) THEN |
---|
1209 | ! |
---|
1210 | idimsz(:) = iom_file(kiomid)%dimsz(:, idvar) ! to write iom_file(kiomid)%dimsz in a shorter way |
---|
1211 | inbdim = iom_file(kiomid)%ndims(idvar) ! number of dimensions in the file |
---|
1212 | idmspc = inbdim ! number of spatial dimensions in the file |
---|
1213 | IF( iom_file(kiomid)%luld(idvar) ) idmspc = inbdim - 1 |
---|
1214 | IF( idmspc > 3 ) CALL ctl_stop(trim(clinfo), 'the file has more than 3 spatial dimensions this case is not coded...') |
---|
1215 | ! |
---|
1216 | ! Identify the domain in case of jpdom_auto definition |
---|
1217 | IF( idom == jpdom_auto .OR. idom == jpdom_auto_xy ) THEN |
---|
1218 | idom = jpdom_global ! default |
---|
1219 | ! else: if the file name finishes with _xxxx.nc with xxxx any number |
---|
1220 | ind1 = INDEX( clname, '_', back = .TRUE. ) + 1 |
---|
1221 | ind2 = INDEX( clname, '.', back = .TRUE. ) - 1 |
---|
1222 | IF( ind2 > ind1 ) THEN ; IF( VERIFY( clname(ind1:ind2), '0123456789' ) == 0 ) idom = jpdom_local ; ENDIF |
---|
1223 | ENDIF |
---|
1224 | ! |
---|
1225 | ! check the consistency between input array and data rank in the file |
---|
1226 | ! |
---|
1227 | ! initializations |
---|
1228 | itime = 1 |
---|
1229 | IF( PRESENT(ktime) ) itime = ktime |
---|
1230 | ! |
---|
1231 | irankpv = 1 * COUNT( (/PRESENT(pv_r1d)/) ) + 2 * COUNT( (/PRESENT(pv_r2d)/) ) + 3 * COUNT( (/PRESENT(pv_r3d)/) ) |
---|
1232 | WRITE(clrankpv, fmt='(i1)') irankpv |
---|
1233 | WRITE(cldmspc , fmt='(i1)') idmspc |
---|
1234 | ! |
---|
1235 | IF( idmspc < irankpv ) THEN ! it seems we want to read more than we can... |
---|
1236 | IF( irankpv == 3 .AND. idmspc == 2 ) THEN ! 3D input array from 2D spatial data in the file: |
---|
1237 | llok = inlev == 1 ! -> 3rd dimension must be equal to 1 |
---|
1238 | ELSEIF( irankpv == 3 .AND. idmspc == 1 ) THEN ! 3D input array from 1D spatial data in the file: |
---|
1239 | llok = inlev == 1 .AND. SIZE(pv_r3d, 2) == 1 ! -> 2nd and 3rd dimensions must be equal to 1 |
---|
1240 | ELSEIF( irankpv == 2 .AND. idmspc == 2 ) THEN ! 2D input array from 1D spatial data in the file: |
---|
1241 | llok = SIZE(pv_r2d, 2) == 1 ! -> 2nd dimension must be equal to 1 |
---|
1242 | ELSE |
---|
1243 | llok = .FALSE. |
---|
1244 | ENDIF |
---|
1245 | IF( .NOT. llok ) CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension', & |
---|
1246 | & '=> cannot read a true '//clrankpv//'D array from this file...' ) |
---|
1247 | ELSEIF( idmspc == irankpv ) THEN |
---|
1248 | IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown ) & |
---|
1249 | & CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' ) |
---|
1250 | ELSEIF( idmspc > irankpv ) THEN ! it seems we want to read less than we should... |
---|
1251 | IF( PRESENT(pv_r2d) .AND. itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN |
---|
1252 | CALL ctl_warn( trim(clinfo), '2D array input but 3 spatial dimensions in the file...' , & |
---|
1253 | & 'As the size of the z dimension is 1 and as we try to read the first record, ', & |
---|
1254 | & 'we accept this case, even if there is a possible mix-up between z and time dimension' ) |
---|
1255 | idmspc = idmspc - 1 |
---|
1256 | !!GS: possibility to read 3D ABL atmopsheric forcing and use 1st level to force BULK simulation |
---|
1257 | !ELSE |
---|
1258 | ! CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,', & |
---|
1259 | ! & 'we do not accept data with '//cldmspc//' spatial dimensions' , & |
---|
1260 | ! & 'Use ncwa -a to suppress the unnecessary dimensions' ) |
---|
1261 | ENDIF |
---|
1262 | ENDIF |
---|
1263 | ! |
---|
1264 | ! definition of istart and icnt |
---|
1265 | ! |
---|
1266 | icnt (:) = 1 ! default definition (simple way to deal with special cases listed above) |
---|
1267 | istart(:) = 1 ! default definition (simple way to deal with special cases listed above) |
---|
1268 | istart(idmspc+1) = itime ! temporal dimenstion |
---|
1269 | ! |
---|
1270 | IF( idom == jpdom_unknown ) THEN |
---|
1271 | IF( PRESENT(kstart) .AND. idom /= jpdom_auto_xy ) THEN |
---|
1272 | istart(1:idmspc) = kstart(1:idmspc) |
---|
1273 | icnt (1:idmspc) = kcount(1:idmspc) |
---|
1274 | ELSE |
---|
1275 | icnt (1:idmspc) = idimsz(1:idmspc) |
---|
1276 | ENDIF |
---|
1277 | ELSE ! not a 1D array as pv_r1d requires jpdom_unknown |
---|
1278 | ! we do not read the overlap and the extra-halos -> from Nis0 to Nie0 and from Njs0 to Nje0 |
---|
1279 | IF( idom == jpdom_global ) istart(1:2) = (/ mig0(Nis0), mjg0(Njs0) /) |
---|
1280 | icnt(1:2) = (/ Ni_0, Nj_0 /) |
---|
1281 | IF( PRESENT(pv_r3d) ) THEN |
---|
1282 | IF( idom == jpdom_auto_xy ) THEN |
---|
1283 | istart(3) = kstart(3) |
---|
1284 | icnt (3) = kcount(3) |
---|
1285 | ELSE |
---|
1286 | icnt (3) = inlev |
---|
1287 | ENDIF |
---|
1288 | ENDIF |
---|
1289 | ENDIF |
---|
1290 | ! |
---|
1291 | ! check that istart and icnt can be used with this file |
---|
1292 | !- |
---|
1293 | DO jl = 1, jpmax_dims |
---|
1294 | itmp = istart(jl)+icnt(jl)-1 |
---|
1295 | IF( itmp > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN |
---|
1296 | WRITE( ctmp1, FMT="('(istart(', i1, ') + icnt(', i1, ') - 1) = ', i5)" ) jl, jl, itmp |
---|
1297 | WRITE( ctmp2, FMT="(' is larger than idimsz(', i1,') = ', i5)" ) jl, idimsz(jl) |
---|
1298 | CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 ) |
---|
1299 | ENDIF |
---|
1300 | END DO |
---|
1301 | ! |
---|
1302 | ! check that icnt matches the input array |
---|
1303 | !- |
---|
1304 | IF( idom == jpdom_unknown ) THEN |
---|
1305 | IF( irankpv == 1 ) ishape(1:1) = SHAPE(pv_r1d) |
---|
1306 | IF( irankpv == 2 ) ishape(1:2) = SHAPE(pv_r2d) |
---|
1307 | IF( irankpv == 3 ) ishape(1:3) = SHAPE(pv_r3d) |
---|
1308 | ctmp1 = 'd' |
---|
1309 | ELSE |
---|
1310 | IF( irankpv == 2 ) THEN |
---|
1311 | ishape(1:2) = SHAPE(pv_r2d(Nis0:Nie0,Njs0:Nje0 )) ; ctmp1 = 'd(Nis0:Nie0,Njs0:Nje0)' |
---|
1312 | ENDIF |
---|
1313 | IF( irankpv == 3 ) THEN |
---|
1314 | ishape(1:3) = SHAPE(pv_r3d(Nis0:Nie0,Njs0:Nje0,:)) ; ctmp1 = 'd(Nis0:Nie0,Njs0:Nje0,:)' |
---|
1315 | ENDIF |
---|
1316 | ENDIF |
---|
1317 | DO jl = 1, irankpv |
---|
1318 | WRITE( ctmp2, FMT="(', ', i1,'): ', i5,' /= icnt(', i1,'):', i5)" ) jl, ishape(jl), jl, icnt(jl) |
---|
1319 | IF( ishape(jl) /= icnt(jl) ) CALL ctl_stop( TRIM(clinfo), 'size(pv_r'//clrankpv//TRIM(ctmp1)//TRIM(ctmp2) ) |
---|
1320 | END DO |
---|
1321 | |
---|
1322 | ENDIF |
---|
1323 | |
---|
1324 | ! read the data |
---|
1325 | !- |
---|
1326 | IF( idvar > 0 .AND. istop == nstop ) THEN ! no additional errors until this point... |
---|
1327 | ! |
---|
1328 | ! find the right index of the array to be read |
---|
1329 | IF( idom /= jpdom_unknown ) THEN ; ix1 = Nis0 ; ix2 = Nie0 ; iy1 = Njs0 ; iy2 = Nje0 |
---|
1330 | ELSE ; ix1 = 1 ; ix2 = icnt(1) ; iy1 = 1 ; iy2 = icnt(2) |
---|
1331 | ENDIF |
---|
1332 | |
---|
1333 | CALL iom_nf90_get( kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2, pv_r1d, pv_r2d, pv_r3d ) |
---|
1334 | |
---|
1335 | IF( istop == nstop ) THEN ! no additional errors until this point... |
---|
1336 | IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i6,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name) |
---|
1337 | |
---|
1338 | cl_type = 'T' |
---|
1339 | IF( PRESENT(cd_type) ) cl_type = cd_type |
---|
1340 | zsgn = 1._wp |
---|
1341 | IF( PRESENT(psgn ) ) zsgn = psgn |
---|
1342 | !--- overlap areas and extra hallows (mpp) |
---|
1343 | IF( PRESENT(pv_r2d) .AND. idom /= jpdom_unknown .AND. cl_type /= 'Z' ) THEN |
---|
1344 | CALL lbc_lnk( 'iom', pv_r2d, cl_type, zsgn, kfillmode = kfill ) |
---|
1345 | ELSEIF( PRESENT(pv_r3d) .AND. idom /= jpdom_unknown .AND. cl_type /= 'Z' ) THEN |
---|
1346 | CALL lbc_lnk( 'iom', pv_r3d, cl_type, zsgn, kfillmode = kfill ) |
---|
1347 | ENDIF |
---|
1348 | ! |
---|
1349 | ELSE |
---|
1350 | ! return if istop == nstop is false |
---|
1351 | RETURN |
---|
1352 | ENDIF |
---|
1353 | ELSE |
---|
1354 | ! return if statment idvar > 0 .AND. istop == nstop is false |
---|
1355 | RETURN |
---|
1356 | ENDIF |
---|
1357 | ! |
---|
1358 | ELSE ! read using XIOS. Only if KEY_IOMPUT is defined |
---|
1359 | #if defined key_iomput |
---|
1360 | !would be good to be able to check which context is active and swap only if current is not restart |
---|
1361 | CALL iom_swap( TRIM(crxios_context) ) |
---|
1362 | IF( PRESENT(pv_r3d) ) THEN |
---|
1363 | IF(lwp) WRITE(numout,*) 'XIOS RST READ (3D): ',TRIM(cdvar) |
---|
1364 | CALL xios_recv_field( trim(cdvar), pv_r3d) |
---|
1365 | IF(idom /= jpdom_unknown ) CALL lbc_lnk( 'iom', pv_r3d,'Z', -999., kfillmode = jpfillnothing) |
---|
1366 | ELSEIF( PRESENT(pv_r2d) ) THEN |
---|
1367 | IF(lwp) WRITE(numout,*) 'XIOS RST READ (2D): ', TRIM(cdvar) |
---|
1368 | CALL xios_recv_field( trim(cdvar), pv_r2d) |
---|
1369 | IF(idom /= jpdom_unknown ) CALL lbc_lnk('iom', pv_r2d,'Z',-999., kfillmode = jpfillnothing) |
---|
1370 | ELSEIF( PRESENT(pv_r1d) ) THEN |
---|
1371 | IF(lwp) WRITE(numout,*) 'XIOS RST READ (1D): ', TRIM(cdvar) |
---|
1372 | CALL xios_recv_field( trim(cdvar), pv_r1d) |
---|
1373 | ENDIF |
---|
1374 | CALL iom_swap( TRIM(cxios_context) ) |
---|
1375 | #else |
---|
1376 | istop = istop + 1 |
---|
1377 | clinfo = 'Can not use XIOS in iom_get_123d, file: '//trim(clname)//', var:'//trim(cdvar) |
---|
1378 | #endif |
---|
1379 | ENDIF |
---|
1380 | !some final adjustments |
---|
1381 | ! C1D case : always call lbc_lnk to replicate the central value over the whole 3X3 domain |
---|
1382 | IF( lk_c1d .AND. PRESENT(pv_r2d) ) CALL lbc_lnk( 'iom', pv_r2d,'Z',1.0_wp ) |
---|
1383 | IF( lk_c1d .AND. PRESENT(pv_r3d) ) CALL lbc_lnk( 'iom', pv_r3d,'Z',1.0_wp ) |
---|
1384 | |
---|
1385 | !--- Apply scale_factor and offset |
---|
1386 | zscf = iom_file(kiomid)%scf(idvar) ! scale factor |
---|
1387 | zofs = iom_file(kiomid)%ofs(idvar) ! offset |
---|
1388 | IF( PRESENT(pv_r1d) ) THEN |
---|
1389 | IF( zscf /= 1. ) pv_r1d(:) = pv_r1d(:) * zscf |
---|
1390 | IF( zofs /= 0. ) pv_r1d(:) = pv_r1d(:) + zofs |
---|
1391 | ELSEIF( PRESENT(pv_r2d) ) THEN |
---|
1392 | IF( zscf /= 1.) pv_r2d(:,:) = pv_r2d(:,:) * zscf |
---|
1393 | IF( zofs /= 0.) pv_r2d(:,:) = pv_r2d(:,:) + zofs |
---|
1394 | ELSEIF( PRESENT(pv_r3d) ) THEN |
---|
1395 | IF( zscf /= 1.) pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf |
---|
1396 | IF( zofs /= 0.) pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs |
---|
1397 | ENDIF |
---|
1398 | ! |
---|
1399 | END SUBROUTINE iom_get_123d |
---|
1400 | |
---|
1401 | SUBROUTINE iom_get_var( cdname, z2d) |
---|
1402 | CHARACTER(LEN=*), INTENT(in ) :: cdname |
---|
1403 | REAL(wp), DIMENSION(jpi,jpj) :: z2d |
---|
1404 | #if defined key_iomput |
---|
1405 | IF( xios_field_is_active( cdname, at_current_timestep_arg = .TRUE. ) ) THEN |
---|
1406 | z2d(:,:) = 0._wp |
---|
1407 | CALL xios_recv_field( cdname, z2d) |
---|
1408 | ENDIF |
---|
1409 | #else |
---|
1410 | IF( .FALSE. ) WRITE(numout,*) cdname, z2d ! useless test to avoid compilation warnings |
---|
1411 | #endif |
---|
1412 | END SUBROUTINE iom_get_var |
---|
1413 | |
---|
1414 | |
---|
1415 | FUNCTION iom_getszuld ( kiomid ) |
---|
1416 | !!----------------------------------------------------------------------- |
---|
1417 | !! *** FUNCTION iom_getszuld *** |
---|
1418 | !! |
---|
1419 | !! ** Purpose : get the size of the unlimited dimension in a file |
---|
1420 | !! (return -1 if not found) |
---|
1421 | !!----------------------------------------------------------------------- |
---|
1422 | INTEGER, INTENT(in ) :: kiomid ! file Identifier |
---|
1423 | ! |
---|
1424 | INTEGER :: iom_getszuld |
---|
1425 | !!----------------------------------------------------------------------- |
---|
1426 | iom_getszuld = -1 |
---|
1427 | IF( kiomid > 0 ) THEN |
---|
1428 | IF( iom_file(kiomid)%iduld > 0 ) iom_getszuld = iom_file(kiomid)%lenuld |
---|
1429 | ENDIF |
---|
1430 | END FUNCTION iom_getszuld |
---|
1431 | |
---|
1432 | |
---|
1433 | !!---------------------------------------------------------------------- |
---|
1434 | !! INTERFACE iom_chkatt |
---|
1435 | !!---------------------------------------------------------------------- |
---|
1436 | SUBROUTINE iom_chkatt( kiomid, cdatt, llok, ksize, cdvar ) |
---|
1437 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1438 | CHARACTER(len=*), INTENT(in ) :: cdatt ! Name of the attribute |
---|
1439 | LOGICAL , INTENT( out) :: llok ! Error code |
---|
1440 | INTEGER , INTENT( out), OPTIONAL :: ksize ! Size of the attribute array |
---|
1441 | CHARACTER(len=*), INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1442 | ! |
---|
1443 | IF( kiomid > 0 ) THEN |
---|
1444 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_chkatt( kiomid, cdatt, llok, ksize=ksize, cdvar=cdvar ) |
---|
1445 | ENDIF |
---|
1446 | ! |
---|
1447 | END SUBROUTINE iom_chkatt |
---|
1448 | |
---|
1449 | !!---------------------------------------------------------------------- |
---|
1450 | !! INTERFACE iom_getatt |
---|
1451 | !!---------------------------------------------------------------------- |
---|
1452 | SUBROUTINE iom_g0d_iatt( kiomid, cdatt, katt0d, cdvar ) |
---|
1453 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1454 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1455 | INTEGER , INTENT( out) :: katt0d ! read field |
---|
1456 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1457 | ! |
---|
1458 | IF( kiomid > 0 ) THEN |
---|
1459 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_getatt( kiomid, cdatt, katt0d = katt0d, cdvar=cdvar ) |
---|
1460 | ENDIF |
---|
1461 | END SUBROUTINE iom_g0d_iatt |
---|
1462 | |
---|
1463 | SUBROUTINE iom_g1d_iatt( kiomid, cdatt, katt1d, cdvar ) |
---|
1464 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1465 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1466 | INTEGER, DIMENSION(:) , INTENT( out) :: katt1d ! read field |
---|
1467 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1468 | ! |
---|
1469 | IF( kiomid > 0 ) THEN |
---|
1470 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_getatt( kiomid, cdatt, katt1d = katt1d, cdvar=cdvar ) |
---|
1471 | ENDIF |
---|
1472 | END SUBROUTINE iom_g1d_iatt |
---|
1473 | |
---|
1474 | SUBROUTINE iom_g0d_ratt( kiomid, cdatt, patt0d, cdvar ) |
---|
1475 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1476 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1477 | REAL(wp) , INTENT( out) :: patt0d ! read field |
---|
1478 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1479 | ! |
---|
1480 | IF( kiomid > 0 ) THEN |
---|
1481 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_getatt( kiomid, cdatt, patt0d = patt0d, cdvar=cdvar ) |
---|
1482 | ENDIF |
---|
1483 | END SUBROUTINE iom_g0d_ratt |
---|
1484 | |
---|
1485 | SUBROUTINE iom_g1d_ratt( kiomid, cdatt, patt1d, cdvar ) |
---|
1486 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1487 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1488 | REAL(wp), DIMENSION(:), INTENT( out) :: patt1d ! read field |
---|
1489 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1490 | ! |
---|
1491 | IF( kiomid > 0 ) THEN |
---|
1492 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_getatt( kiomid, cdatt, patt1d = patt1d, cdvar=cdvar ) |
---|
1493 | ENDIF |
---|
1494 | END SUBROUTINE iom_g1d_ratt |
---|
1495 | |
---|
1496 | SUBROUTINE iom_g0d_catt( kiomid, cdatt, cdatt0d, cdvar ) |
---|
1497 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1498 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1499 | CHARACTER(len=*) , INTENT( out) :: cdatt0d ! read field |
---|
1500 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1501 | ! |
---|
1502 | IF( kiomid > 0 ) THEN |
---|
1503 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_getatt( kiomid, cdatt, cdatt0d = cdatt0d, cdvar=cdvar ) |
---|
1504 | ENDIF |
---|
1505 | END SUBROUTINE iom_g0d_catt |
---|
1506 | |
---|
1507 | |
---|
1508 | !!---------------------------------------------------------------------- |
---|
1509 | !! INTERFACE iom_putatt |
---|
1510 | !!---------------------------------------------------------------------- |
---|
1511 | SUBROUTINE iom_p0d_iatt( kiomid, cdatt, katt0d, cdvar ) |
---|
1512 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1513 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1514 | INTEGER , INTENT(in ) :: katt0d ! written field |
---|
1515 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1516 | ! |
---|
1517 | IF( kiomid > 0 ) THEN |
---|
1518 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_putatt( kiomid, cdatt, katt0d = katt0d, cdvar=cdvar ) |
---|
1519 | ENDIF |
---|
1520 | END SUBROUTINE iom_p0d_iatt |
---|
1521 | |
---|
1522 | SUBROUTINE iom_p1d_iatt( kiomid, cdatt, katt1d, cdvar ) |
---|
1523 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1524 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1525 | INTEGER, DIMENSION(:) , INTENT(in ) :: katt1d ! written field |
---|
1526 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1527 | ! |
---|
1528 | IF( kiomid > 0 ) THEN |
---|
1529 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_putatt( kiomid, cdatt, katt1d = katt1d, cdvar=cdvar ) |
---|
1530 | ENDIF |
---|
1531 | END SUBROUTINE iom_p1d_iatt |
---|
1532 | |
---|
1533 | SUBROUTINE iom_p0d_ratt( kiomid, cdatt, patt0d, cdvar ) |
---|
1534 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1535 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1536 | REAL(wp) , INTENT(in ) :: patt0d ! written field |
---|
1537 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1538 | ! |
---|
1539 | IF( kiomid > 0 ) THEN |
---|
1540 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_putatt( kiomid, cdatt, patt0d = patt0d, cdvar=cdvar ) |
---|
1541 | ENDIF |
---|
1542 | END SUBROUTINE iom_p0d_ratt |
---|
1543 | |
---|
1544 | SUBROUTINE iom_p1d_ratt( kiomid, cdatt, patt1d, cdvar ) |
---|
1545 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1546 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1547 | REAL(wp), DIMENSION(:), INTENT(in ) :: patt1d ! written field |
---|
1548 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1549 | ! |
---|
1550 | IF( kiomid > 0 ) THEN |
---|
1551 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_putatt( kiomid, cdatt, patt1d = patt1d, cdvar=cdvar ) |
---|
1552 | ENDIF |
---|
1553 | END SUBROUTINE iom_p1d_ratt |
---|
1554 | |
---|
1555 | SUBROUTINE iom_p0d_catt( kiomid, cdatt, cdatt0d, cdvar ) |
---|
1556 | INTEGER , INTENT(in ) :: kiomid ! Identifier of the file |
---|
1557 | CHARACTER(len=*) , INTENT(in ) :: cdatt ! Name of the attribute |
---|
1558 | CHARACTER(len=*) , INTENT(in ) :: cdatt0d ! written field |
---|
1559 | CHARACTER(len=*) , INTENT(in ), OPTIONAL :: cdvar ! Name of the variable |
---|
1560 | ! |
---|
1561 | IF( kiomid > 0 ) THEN |
---|
1562 | IF( iom_file(kiomid)%nfid > 0 ) CALL iom_nf90_putatt( kiomid, cdatt, cdatt0d = cdatt0d, cdvar=cdvar ) |
---|
1563 | ENDIF |
---|
1564 | END SUBROUTINE iom_p0d_catt |
---|
1565 | |
---|
1566 | |
---|
1567 | !!---------------------------------------------------------------------- |
---|
1568 | !! INTERFACE iom_rstput |
---|
1569 | !!---------------------------------------------------------------------- |
---|
1570 | SUBROUTINE iom_rp0d_sp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1571 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1572 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1573 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1574 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1575 | REAL(sp) , INTENT(in) :: pvar ! written field |
---|
1576 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1577 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1578 | LOGICAL :: llx ! local xios write flag |
---|
1579 | INTEGER :: ivid ! variable id |
---|
1580 | |
---|
1581 | llx = .FALSE. |
---|
1582 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1583 | IF( llx ) THEN |
---|
1584 | #ifdef key_iomput |
---|
1585 | IF( kt == kwrite ) THEN |
---|
1586 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 0D) ',trim(cdvar) |
---|
1587 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1588 | ENDIF |
---|
1589 | #endif |
---|
1590 | ELSE |
---|
1591 | IF( kiomid > 0 ) THEN |
---|
1592 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1593 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1594 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = real(pvar, dp) ) |
---|
1595 | ENDIF |
---|
1596 | ENDIF |
---|
1597 | ENDIF |
---|
1598 | END SUBROUTINE iom_rp0d_sp |
---|
1599 | |
---|
1600 | SUBROUTINE iom_rp0d_dp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1601 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1602 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1603 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1604 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1605 | REAL(dp) , INTENT(in) :: pvar ! written field |
---|
1606 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1607 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1608 | LOGICAL :: llx ! local xios write flag |
---|
1609 | INTEGER :: ivid ! variable id |
---|
1610 | |
---|
1611 | llx = .FALSE. |
---|
1612 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1613 | IF( llx ) THEN |
---|
1614 | #ifdef key_iomput |
---|
1615 | IF( kt == kwrite ) THEN |
---|
1616 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 0D) ',trim(cdvar) |
---|
1617 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1618 | ENDIF |
---|
1619 | #endif |
---|
1620 | ELSE |
---|
1621 | IF( kiomid > 0 ) THEN |
---|
1622 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1623 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1624 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) |
---|
1625 | ENDIF |
---|
1626 | ENDIF |
---|
1627 | ENDIF |
---|
1628 | END SUBROUTINE iom_rp0d_dp |
---|
1629 | |
---|
1630 | |
---|
1631 | SUBROUTINE iom_rp1d_sp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1632 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1633 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1634 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1635 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1636 | REAL(sp) , INTENT(in), DIMENSION( :) :: pvar ! written field |
---|
1637 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1638 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1639 | LOGICAL :: llx ! local xios write flag |
---|
1640 | INTEGER :: ivid ! variable id |
---|
1641 | |
---|
1642 | llx = .FALSE. |
---|
1643 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1644 | IF( llx ) THEN |
---|
1645 | #ifdef key_iomput |
---|
1646 | IF( kt == kwrite ) THEN |
---|
1647 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 1D) ',trim(cdvar) |
---|
1648 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1649 | ENDIF |
---|
1650 | #endif |
---|
1651 | ELSE |
---|
1652 | IF( kiomid > 0 ) THEN |
---|
1653 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1654 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1655 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = real(pvar, dp) ) |
---|
1656 | ENDIF |
---|
1657 | ENDIF |
---|
1658 | ENDIF |
---|
1659 | END SUBROUTINE iom_rp1d_sp |
---|
1660 | |
---|
1661 | SUBROUTINE iom_rp1d_dp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1662 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1663 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1664 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1665 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1666 | REAL(dp) , INTENT(in), DIMENSION( :) :: pvar ! written field |
---|
1667 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1668 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1669 | LOGICAL :: llx ! local xios write flag |
---|
1670 | INTEGER :: ivid ! variable id |
---|
1671 | |
---|
1672 | llx = .FALSE. |
---|
1673 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1674 | IF( llx ) THEN |
---|
1675 | #ifdef key_iomput |
---|
1676 | IF( kt == kwrite ) THEN |
---|
1677 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 1D) ',trim(cdvar) |
---|
1678 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1679 | ENDIF |
---|
1680 | #endif |
---|
1681 | ELSE |
---|
1682 | IF( kiomid > 0 ) THEN |
---|
1683 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1684 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1685 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) |
---|
1686 | ENDIF |
---|
1687 | ENDIF |
---|
1688 | ENDIF |
---|
1689 | END SUBROUTINE iom_rp1d_dp |
---|
1690 | |
---|
1691 | |
---|
1692 | SUBROUTINE iom_rp2d_sp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1693 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1694 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1695 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1696 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1697 | REAL(sp) , INTENT(in), DIMENSION(:, : ) :: pvar ! written field |
---|
1698 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1699 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1700 | LOGICAL :: llx |
---|
1701 | INTEGER :: ivid ! variable id |
---|
1702 | |
---|
1703 | llx = .FALSE. |
---|
1704 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1705 | IF( llx ) THEN |
---|
1706 | #ifdef key_iomput |
---|
1707 | IF( kt == kwrite ) THEN |
---|
1708 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 2D) ',trim(cdvar) |
---|
1709 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1710 | ENDIF |
---|
1711 | #endif |
---|
1712 | ELSE |
---|
1713 | IF( kiomid > 0 ) THEN |
---|
1714 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1715 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1716 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = real(pvar, dp) ) |
---|
1717 | ENDIF |
---|
1718 | ENDIF |
---|
1719 | ENDIF |
---|
1720 | END SUBROUTINE iom_rp2d_sp |
---|
1721 | |
---|
1722 | SUBROUTINE iom_rp2d_dp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1723 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1724 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1725 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1726 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1727 | REAL(dp) , INTENT(in), DIMENSION(:, : ) :: pvar ! written field |
---|
1728 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1729 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1730 | LOGICAL :: llx |
---|
1731 | INTEGER :: ivid ! variable id |
---|
1732 | |
---|
1733 | llx = .FALSE. |
---|
1734 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1735 | IF( llx ) THEN |
---|
1736 | #ifdef key_iomput |
---|
1737 | IF( kt == kwrite ) THEN |
---|
1738 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 2D) ',trim(cdvar) |
---|
1739 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1740 | ENDIF |
---|
1741 | #endif |
---|
1742 | ELSE |
---|
1743 | IF( kiomid > 0 ) THEN |
---|
1744 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1745 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1746 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) |
---|
1747 | ENDIF |
---|
1748 | ENDIF |
---|
1749 | ENDIF |
---|
1750 | END SUBROUTINE iom_rp2d_dp |
---|
1751 | |
---|
1752 | |
---|
1753 | SUBROUTINE iom_rp3d_sp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1754 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1755 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1756 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1757 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1758 | REAL(sp) , INTENT(in), DIMENSION(:,:,:) :: pvar ! written field |
---|
1759 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1760 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1761 | LOGICAL :: llx ! local xios write flag |
---|
1762 | INTEGER :: ivid ! variable id |
---|
1763 | |
---|
1764 | llx = .FALSE. |
---|
1765 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1766 | IF( llx ) THEN |
---|
1767 | #ifdef key_iomput |
---|
1768 | IF( kt == kwrite ) THEN |
---|
1769 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 3D) ',trim(cdvar) |
---|
1770 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1771 | ENDIF |
---|
1772 | #endif |
---|
1773 | ELSE |
---|
1774 | IF( kiomid > 0 ) THEN |
---|
1775 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1776 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1777 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = real(pvar, dp) ) |
---|
1778 | ENDIF |
---|
1779 | ENDIF |
---|
1780 | ENDIF |
---|
1781 | END SUBROUTINE iom_rp3d_sp |
---|
1782 | |
---|
1783 | SUBROUTINE iom_rp3d_dp( kt, kwrite, kiomid, cdvar, pvar, ktype, ldxios ) |
---|
1784 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
1785 | INTEGER , INTENT(in) :: kwrite ! writing time-step |
---|
1786 | INTEGER , INTENT(in) :: kiomid ! Identifier of the file |
---|
1787 | CHARACTER(len=*), INTENT(in) :: cdvar ! time axis name |
---|
1788 | REAL(dp) , INTENT(in), DIMENSION(:,:,:) :: pvar ! written field |
---|
1789 | INTEGER , INTENT(in), OPTIONAL :: ktype ! variable external type |
---|
1790 | LOGICAL, OPTIONAL :: ldxios ! xios write flag |
---|
1791 | LOGICAL :: llx ! local xios write flag |
---|
1792 | INTEGER :: ivid ! variable id |
---|
1793 | |
---|
1794 | llx = .FALSE. |
---|
1795 | IF(PRESENT(ldxios)) llx = ldxios |
---|
1796 | IF( llx ) THEN |
---|
1797 | #ifdef key_iomput |
---|
1798 | IF( kt == kwrite ) THEN |
---|
1799 | IF(lwp) write(numout,*) 'RESTART: write (XIOS 3D) ',trim(cdvar) |
---|
1800 | CALL xios_send_field(trim(cdvar), pvar) |
---|
1801 | ENDIF |
---|
1802 | #endif |
---|
1803 | ELSE |
---|
1804 | IF( kiomid > 0 ) THEN |
---|
1805 | IF( iom_file(kiomid)%nfid > 0 ) THEN |
---|
1806 | ivid = iom_varid( kiomid, cdvar, ldstop = .FALSE. ) |
---|
1807 | CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) |
---|
1808 | ENDIF |
---|
1809 | ENDIF |
---|
1810 | ENDIF |
---|
1811 | END SUBROUTINE iom_rp3d_dp |
---|
1812 | |
---|
1813 | |
---|
1814 | |
---|
1815 | SUBROUTINE iom_delay_rst( cdaction, cdcpnt, kncid ) |
---|
1816 | !!--------------------------------------------------------------------- |
---|
1817 | !! Routine iom_delay_rst: used read/write restart related to mpp_delay |
---|
1818 | !! |
---|
1819 | !!--------------------------------------------------------------------- |
---|
1820 | CHARACTER(len=*), INTENT(in ) :: cdaction ! |
---|
1821 | CHARACTER(len=*), INTENT(in ) :: cdcpnt |
---|
1822 | INTEGER , INTENT(in ) :: kncid |
---|
1823 | ! |
---|
1824 | INTEGER :: ji |
---|
1825 | INTEGER :: indim |
---|
1826 | LOGICAL :: llattexist |
---|
1827 | REAL(wp), ALLOCATABLE, DIMENSION(:) :: zreal1d |
---|
1828 | !!--------------------------------------------------------------------- |
---|
1829 | ! |
---|
1830 | ! =================================== |
---|
1831 | IF( TRIM(cdaction) == 'READ' ) THEN ! read restart related to mpp_delay ! |
---|
1832 | ! =================================== |
---|
1833 | DO ji = 1, nbdelay |
---|
1834 | IF ( c_delaycpnt(ji) == cdcpnt ) THEN |
---|
1835 | CALL iom_chkatt( kncid, 'DELAY_'//c_delaylist(ji), llattexist, indim ) |
---|
1836 | IF( llattexist ) THEN |
---|
1837 | ALLOCATE( todelay(ji)%z1d(indim) ) |
---|
1838 | CALL iom_getatt( kncid, 'DELAY_'//c_delaylist(ji), todelay(ji)%z1d(:) ) |
---|
1839 | ndelayid(ji) = 0 ! set to 0 to specify that the value was read in the restart |
---|
1840 | ENDIF |
---|
1841 | ENDIF |
---|
1842 | END DO |
---|
1843 | ! ==================================== |
---|
1844 | ELSE ! write restart related to mpp_delay ! |
---|
1845 | ! ==================================== |
---|
1846 | DO ji = 1, nbdelay ! save only ocean delayed global communication variables |
---|
1847 | IF ( c_delaycpnt(ji) == cdcpnt ) THEN |
---|
1848 | IF( ASSOCIATED(todelay(ji)%z1d) ) THEN |
---|
1849 | CALL mpp_delay_rcv(ji) ! make sure %z1d is received |
---|
1850 | CALL iom_putatt( kncid, 'DELAY_'//c_delaylist(ji), todelay(ji)%z1d(:) ) |
---|
1851 | ENDIF |
---|
1852 | ENDIF |
---|
1853 | END DO |
---|
1854 | ! |
---|
1855 | ENDIF |
---|
1856 | |
---|
1857 | END SUBROUTINE iom_delay_rst |
---|
1858 | |
---|
1859 | |
---|
1860 | |
---|
1861 | !!---------------------------------------------------------------------- |
---|
1862 | !! INTERFACE iom_put |
---|
1863 | !!---------------------------------------------------------------------- |
---|
1864 | SUBROUTINE iom_p0d_sp( cdname, pfield0d ) |
---|
1865 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
1866 | REAL(sp) , INTENT(in) :: pfield0d |
---|
1867 | !! REAL(wp) , DIMENSION(jpi,jpj) :: zz ! masson |
---|
1868 | #if defined key_iomput |
---|
1869 | !!clem zz(:,:)=pfield0d |
---|
1870 | !!clem CALL xios_send_field(cdname, zz) |
---|
1871 | CALL xios_send_field(cdname, (/pfield0d/)) |
---|
1872 | #else |
---|
1873 | IF( .FALSE. ) WRITE(numout,*) cdname, pfield0d ! useless test to avoid compilation warnings |
---|
1874 | #endif |
---|
1875 | END SUBROUTINE iom_p0d_sp |
---|
1876 | |
---|
1877 | SUBROUTINE iom_p0d_dp( cdname, pfield0d ) |
---|
1878 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
1879 | REAL(dp) , INTENT(in) :: pfield0d |
---|
1880 | !! REAL(wp) , DIMENSION(jpi,jpj) :: zz ! masson |
---|
1881 | #if defined key_iomput |
---|
1882 | !!clem zz(:,:)=pfield0d |
---|
1883 | !!clem CALL xios_send_field(cdname, zz) |
---|
1884 | CALL xios_send_field(cdname, (/pfield0d/)) |
---|
1885 | #else |
---|
1886 | IF( .FALSE. ) WRITE(numout,*) cdname, pfield0d ! useless test to avoid compilation warnings |
---|
1887 | #endif |
---|
1888 | END SUBROUTINE iom_p0d_dp |
---|
1889 | |
---|
1890 | |
---|
1891 | SUBROUTINE iom_p1d_sp( cdname, pfield1d ) |
---|
1892 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1893 | REAL(sp), DIMENSION(:), INTENT(in) :: pfield1d |
---|
1894 | #if defined key_iomput |
---|
1895 | CALL xios_send_field( cdname, RESHAPE( (/pfield1d/), (/1,1,SIZE(pfield1d)/) ) ) |
---|
1896 | #else |
---|
1897 | IF( .FALSE. ) WRITE(numout,*) cdname, pfield1d ! useless test to avoid compilation warnings |
---|
1898 | #endif |
---|
1899 | END SUBROUTINE iom_p1d_sp |
---|
1900 | |
---|
1901 | SUBROUTINE iom_p1d_dp( cdname, pfield1d ) |
---|
1902 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1903 | REAL(dp), DIMENSION(:), INTENT(in) :: pfield1d |
---|
1904 | #if defined key_iomput |
---|
1905 | CALL xios_send_field( cdname, RESHAPE( (/pfield1d/), (/1,1,SIZE(pfield1d)/) ) ) |
---|
1906 | #else |
---|
1907 | IF( .FALSE. ) WRITE(numout,*) cdname, pfield1d ! useless test to avoid compilation warnings |
---|
1908 | #endif |
---|
1909 | END SUBROUTINE iom_p1d_dp |
---|
1910 | |
---|
1911 | SUBROUTINE iom_p2d_sp( cdname, pfield2d ) |
---|
1912 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1913 | REAL(sp), DIMENSION(:,:), INTENT(in) :: pfield2d |
---|
1914 | IF( iom_use(cdname) ) THEN |
---|
1915 | #if defined key_iomput |
---|
1916 | CALL xios_send_field( cdname, pfield2d ) |
---|
1917 | #else |
---|
1918 | WRITE(numout,*) pfield2d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1919 | #endif |
---|
1920 | ENDIF |
---|
1921 | END SUBROUTINE iom_p2d_sp |
---|
1922 | |
---|
1923 | SUBROUTINE iom_p2d_dp( cdname, pfield2d ) |
---|
1924 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1925 | REAL(dp), DIMENSION(:,:), INTENT(in) :: pfield2d |
---|
1926 | IF( iom_use(cdname) ) THEN |
---|
1927 | #if defined key_iomput |
---|
1928 | CALL xios_send_field( cdname, pfield2d ) |
---|
1929 | #else |
---|
1930 | WRITE(numout,*) pfield2d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1931 | #endif |
---|
1932 | ENDIF |
---|
1933 | END SUBROUTINE iom_p2d_dp |
---|
1934 | |
---|
1935 | SUBROUTINE iom_p3d_sp( cdname, pfield3d ) |
---|
1936 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1937 | REAL(sp), DIMENSION(:,:,:), INTENT(in) :: pfield3d |
---|
1938 | IF( iom_use(cdname) ) THEN |
---|
1939 | #if defined key_iomput |
---|
1940 | CALL xios_send_field( cdname, pfield3d ) |
---|
1941 | #else |
---|
1942 | WRITE(numout,*) pfield3d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1943 | #endif |
---|
1944 | ENDIF |
---|
1945 | END SUBROUTINE iom_p3d_sp |
---|
1946 | |
---|
1947 | SUBROUTINE iom_p3d_dp( cdname, pfield3d ) |
---|
1948 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1949 | REAL(dp), DIMENSION(:,:,:), INTENT(in) :: pfield3d |
---|
1950 | IF( iom_use(cdname) ) THEN |
---|
1951 | #if defined key_iomput |
---|
1952 | CALL xios_send_field( cdname, pfield3d ) |
---|
1953 | #else |
---|
1954 | WRITE(numout,*) pfield3d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1955 | #endif |
---|
1956 | ENDIF |
---|
1957 | END SUBROUTINE iom_p3d_dp |
---|
1958 | |
---|
1959 | SUBROUTINE iom_p4d_sp( cdname, pfield4d ) |
---|
1960 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1961 | REAL(sp), DIMENSION(:,:,:,:), INTENT(in) :: pfield4d |
---|
1962 | IF( iom_use(cdname) ) THEN |
---|
1963 | #if defined key_iomput |
---|
1964 | CALL xios_send_field (cdname, pfield4d ) |
---|
1965 | #else |
---|
1966 | WRITE(numout,*) pfield4d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1967 | #endif |
---|
1968 | ENDIF |
---|
1969 | END SUBROUTINE iom_p4d_sp |
---|
1970 | |
---|
1971 | SUBROUTINE iom_p4d_dp( cdname, pfield4d ) |
---|
1972 | CHARACTER(LEN=*) , INTENT(in) :: cdname |
---|
1973 | REAL(dp), DIMENSION(:,:,:,:), INTENT(in) :: pfield4d |
---|
1974 | IF( iom_use(cdname) ) THEN |
---|
1975 | #if defined key_iomput |
---|
1976 | CALL xios_send_field (cdname, pfield4d ) |
---|
1977 | #else |
---|
1978 | WRITE(numout,*) pfield4d ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings |
---|
1979 | #endif |
---|
1980 | ENDIF |
---|
1981 | END SUBROUTINE iom_p4d_dp |
---|
1982 | |
---|
1983 | #if defined key_iomput |
---|
1984 | !!---------------------------------------------------------------------- |
---|
1985 | !! 'key_iomput' XIOS interface |
---|
1986 | !!---------------------------------------------------------------------- |
---|
1987 | |
---|
1988 | SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, & |
---|
1989 | & data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask, & |
---|
1990 | & nvertex, bounds_lon, bounds_lat, area ) |
---|
1991 | !!---------------------------------------------------------------------- |
---|
1992 | !!---------------------------------------------------------------------- |
---|
1993 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
1994 | INTEGER , OPTIONAL, INTENT(in) :: ni_glo, nj_glo, ibegin, jbegin, ni, nj |
---|
1995 | INTEGER , OPTIONAL, INTENT(in) :: data_dim, data_ibegin, data_ni, data_jbegin, data_nj |
---|
1996 | INTEGER , OPTIONAL, INTENT(in) :: nvertex |
---|
1997 | REAL(dp), DIMENSION(:) , OPTIONAL, INTENT(in) :: lonvalue, latvalue |
---|
1998 | REAL(dp), DIMENSION(:,:), OPTIONAL, INTENT(in) :: bounds_lon, bounds_lat, area |
---|
1999 | LOGICAL , DIMENSION(:) , OPTIONAL, INTENT(in) :: mask |
---|
2000 | !!---------------------------------------------------------------------- |
---|
2001 | ! |
---|
2002 | IF( xios_is_valid_domain (cdid) ) THEN |
---|
2003 | CALL xios_set_domain_attr ( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj, & |
---|
2004 | & data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj , & |
---|
2005 | & lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon, & |
---|
2006 | & bounds_lat_1D=bounds_lat, area=area, type='curvilinear') |
---|
2007 | ENDIF |
---|
2008 | IF( xios_is_valid_domaingroup(cdid) ) THEN |
---|
2009 | CALL xios_set_domaingroup_attr( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj, & |
---|
2010 | & data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj , & |
---|
2011 | & lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon, & |
---|
2012 | & bounds_lat_1D=bounds_lat, area=area, type='curvilinear' ) |
---|
2013 | ENDIF |
---|
2014 | ! |
---|
2015 | CALL xios_solve_inheritance() |
---|
2016 | ! |
---|
2017 | END SUBROUTINE iom_set_domain_attr |
---|
2018 | |
---|
2019 | |
---|
2020 | SUBROUTINE iom_set_zoom_domain_attr( cdid, ibegin, jbegin, ni, nj ) |
---|
2021 | !!---------------------------------------------------------------------- |
---|
2022 | !!---------------------------------------------------------------------- |
---|
2023 | CHARACTER(LEN=*), INTENT(in) :: cdid |
---|
2024 | INTEGER , INTENT(in) :: ibegin, jbegin, ni, nj |
---|
2025 | ! |
---|
2026 | TYPE(xios_gridgroup) :: gridgroup_hdl |
---|
2027 | TYPE(xios_grid) :: grid_hdl |
---|
2028 | TYPE(xios_domain) :: domain_hdl |
---|
2029 | TYPE(xios_axis) :: axis_hdl |
---|
2030 | CHARACTER(LEN=64) :: cldomrefid ! domain_ref name |
---|
2031 | CHARACTER(len=1) :: cl1 ! last character of this name |
---|
2032 | !!---------------------------------------------------------------------- |
---|
2033 | ! |
---|
2034 | IF( xios_is_valid_zoom_domain(cdid) ) THEN |
---|
2035 | ! define the zoom_domain attributs |
---|
2036 | CALL xios_set_zoom_domain_attr( cdid, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj ) |
---|
2037 | ! define a new 2D grid with this new domain |
---|
2038 | CALL xios_get_handle("grid_definition", gridgroup_hdl ) |
---|
2039 | CALL xios_add_child(gridgroup_hdl, grid_hdl, TRIM(cdid)//'_2D' ) ! add a new 2D grid to grid_definition |
---|
2040 | CALL xios_add_child(grid_hdl, domain_hdl, TRIM(cdid) ) ! add its domain |
---|
2041 | ! define a new 3D grid with this new domain |
---|
2042 | CALL xios_add_child(gridgroup_hdl, grid_hdl, TRIM(cdid)//'_3D' ) ! add a new 3D grid to grid_definition |
---|
2043 | CALL xios_add_child(grid_hdl, domain_hdl, TRIM(cdid) ) ! add its domain |
---|
2044 | ! vertical axis |
---|
2045 | cl1 = cdid(LEN_TRIM(cdid):) ! last letter of cdid |
---|
2046 | cl1 = CHAR(ICHAR(cl1)+32) ! from upper to lower case |
---|
2047 | CALL xios_add_child(grid_hdl, axis_hdl, 'depth'//cl1) ! add its axis |
---|
2048 | ENDIF |
---|
2049 | ! |
---|
2050 | END SUBROUTINE iom_set_zoom_domain_attr |
---|
2051 | |
---|
2052 | |
---|
2053 | SUBROUTINE iom_set_axis_attr( cdid, paxis, bounds ) |
---|
2054 | !!---------------------------------------------------------------------- |
---|
2055 | !!---------------------------------------------------------------------- |
---|
2056 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
2057 | REAL(wp), DIMENSION(:) , OPTIONAL, INTENT(in) :: paxis |
---|
2058 | REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) :: bounds |
---|
2059 | !!---------------------------------------------------------------------- |
---|
2060 | IF( PRESENT(paxis) ) THEN |
---|
2061 | IF( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid, n_glo=SIZE(paxis), value=real(paxis, dp) ) |
---|
2062 | IF( xios_is_valid_axisgroup(cdid) ) CALL xios_set_axisgroup_attr( cdid, n_glo=SIZE(paxis), value=real(paxis, dp) ) |
---|
2063 | ENDIF |
---|
2064 | IF( PRESENT(bounds) ) THEN |
---|
2065 | IF( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid, bounds=real(bounds, dp) ) |
---|
2066 | IF( xios_is_valid_axisgroup(cdid) ) CALL xios_set_axisgroup_attr( cdid, bounds=real(bounds, dp) ) |
---|
2067 | ELSE |
---|
2068 | IF( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid) |
---|
2069 | IF( xios_is_valid_axisgroup(cdid) ) CALL xios_set_axisgroup_attr( cdid) |
---|
2070 | END IF |
---|
2071 | CALL xios_solve_inheritance() |
---|
2072 | END SUBROUTINE iom_set_axis_attr |
---|
2073 | |
---|
2074 | |
---|
2075 | SUBROUTINE iom_set_field_attr( cdid, freq_op, freq_offset ) |
---|
2076 | !!---------------------------------------------------------------------- |
---|
2077 | !!---------------------------------------------------------------------- |
---|
2078 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
2079 | TYPE(xios_duration), OPTIONAL, INTENT(in) :: freq_op |
---|
2080 | TYPE(xios_duration), OPTIONAL, INTENT(in) :: freq_offset |
---|
2081 | !!---------------------------------------------------------------------- |
---|
2082 | IF( xios_is_valid_field (cdid) ) CALL xios_set_field_attr ( cdid, freq_op=freq_op, freq_offset=freq_offset ) |
---|
2083 | IF( xios_is_valid_fieldgroup(cdid) ) CALL xios_set_fieldgroup_attr( cdid, freq_op=freq_op, freq_offset=freq_offset ) |
---|
2084 | CALL xios_solve_inheritance() |
---|
2085 | END SUBROUTINE iom_set_field_attr |
---|
2086 | |
---|
2087 | |
---|
2088 | SUBROUTINE iom_set_file_attr( cdid, name, name_suffix ) |
---|
2089 | !!---------------------------------------------------------------------- |
---|
2090 | !!---------------------------------------------------------------------- |
---|
2091 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
2092 | CHARACTER(LEN=*),OPTIONAL , INTENT(in) :: name, name_suffix |
---|
2093 | !!---------------------------------------------------------------------- |
---|
2094 | IF( xios_is_valid_file (cdid) ) CALL xios_set_file_attr ( cdid, name=name, name_suffix=name_suffix ) |
---|
2095 | IF( xios_is_valid_filegroup(cdid) ) CALL xios_set_filegroup_attr( cdid, name=name, name_suffix=name_suffix ) |
---|
2096 | CALL xios_solve_inheritance() |
---|
2097 | END SUBROUTINE iom_set_file_attr |
---|
2098 | |
---|
2099 | |
---|
2100 | SUBROUTINE iom_get_file_attr( cdid, name, name_suffix, output_freq ) |
---|
2101 | !!---------------------------------------------------------------------- |
---|
2102 | !!---------------------------------------------------------------------- |
---|
2103 | CHARACTER(LEN=*) , INTENT(in ) :: cdid |
---|
2104 | CHARACTER(LEN=*),OPTIONAL , INTENT(out) :: name, name_suffix |
---|
2105 | TYPE(xios_duration), OPTIONAL , INTENT(out) :: output_freq |
---|
2106 | LOGICAL :: llexist1,llexist2,llexist3 |
---|
2107 | !--------------------------------------------------------------------- |
---|
2108 | IF( PRESENT( name ) ) name = '' ! default values |
---|
2109 | IF( PRESENT( name_suffix ) ) name_suffix = '' |
---|
2110 | IF( PRESENT( output_freq ) ) output_freq = xios_duration(0,0,0,0,0,0) |
---|
2111 | IF( xios_is_valid_file (cdid) ) THEN |
---|
2112 | CALL xios_solve_inheritance() |
---|
2113 | CALL xios_is_defined_file_attr ( cdid, name = llexist1, name_suffix = llexist2, output_freq = llexist3) |
---|
2114 | IF(llexist1) CALL xios_get_file_attr ( cdid, name = name ) |
---|
2115 | IF(llexist2) CALL xios_get_file_attr ( cdid, name_suffix = name_suffix ) |
---|
2116 | IF(llexist3) CALL xios_get_file_attr ( cdid, output_freq = output_freq ) |
---|
2117 | ENDIF |
---|
2118 | IF( xios_is_valid_filegroup(cdid) ) THEN |
---|
2119 | CALL xios_solve_inheritance() |
---|
2120 | CALL xios_is_defined_filegroup_attr( cdid, name = llexist1, name_suffix = llexist2, output_freq = llexist3) |
---|
2121 | IF(llexist1) CALL xios_get_filegroup_attr( cdid, name = name ) |
---|
2122 | IF(llexist2) CALL xios_get_filegroup_attr( cdid, name_suffix = name_suffix ) |
---|
2123 | IF(llexist3) CALL xios_get_filegroup_attr( cdid, output_freq = output_freq ) |
---|
2124 | ENDIF |
---|
2125 | END SUBROUTINE iom_get_file_attr |
---|
2126 | |
---|
2127 | |
---|
2128 | SUBROUTINE iom_set_grid_attr( cdid, mask ) |
---|
2129 | !!---------------------------------------------------------------------- |
---|
2130 | !!---------------------------------------------------------------------- |
---|
2131 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
2132 | LOGICAL, DIMENSION(:,:,:), OPTIONAL, INTENT(in) :: mask |
---|
2133 | !!---------------------------------------------------------------------- |
---|
2134 | IF( xios_is_valid_grid (cdid) ) CALL xios_set_grid_attr ( cdid, mask_3D=mask ) |
---|
2135 | IF( xios_is_valid_gridgroup(cdid) ) CALL xios_set_gridgroup_attr( cdid, mask_3D=mask ) |
---|
2136 | CALL xios_solve_inheritance() |
---|
2137 | END SUBROUTINE iom_set_grid_attr |
---|
2138 | |
---|
2139 | SUBROUTINE iom_setkt( kt, cdname ) |
---|
2140 | !!---------------------------------------------------------------------- |
---|
2141 | !!---------------------------------------------------------------------- |
---|
2142 | INTEGER , INTENT(in) :: kt |
---|
2143 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
2144 | !!---------------------------------------------------------------------- |
---|
2145 | CALL iom_swap( cdname ) ! swap to cdname context |
---|
2146 | CALL xios_update_calendar(kt) |
---|
2147 | IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) ) ! return back to nemo context |
---|
2148 | END SUBROUTINE iom_setkt |
---|
2149 | |
---|
2150 | SUBROUTINE iom_context_finalize( cdname ) |
---|
2151 | !!---------------------------------------------------------------------- |
---|
2152 | !!---------------------------------------------------------------------- |
---|
2153 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
2154 | CHARACTER(LEN=120) :: clname |
---|
2155 | !!---------------------------------------------------------------------- |
---|
2156 | clname = cdname |
---|
2157 | IF( TRIM(Agrif_CFixed()) .NE. '0' ) clname = TRIM(Agrif_CFixed())//"_"//clname |
---|
2158 | IF( xios_is_valid_context(clname) ) THEN |
---|
2159 | CALL iom_swap( cdname ) ! swap to cdname context |
---|
2160 | CALL xios_context_finalize() ! finalize the context |
---|
2161 | IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) ) ! return back to nemo context |
---|
2162 | ENDIF |
---|
2163 | ! |
---|
2164 | END SUBROUTINE iom_context_finalize |
---|
2165 | |
---|
2166 | |
---|
2167 | SUBROUTINE set_grid( cdgrd, plon, plat, ldxios, ldrxios ) |
---|
2168 | !!---------------------------------------------------------------------- |
---|
2169 | !! *** ROUTINE set_grid *** |
---|
2170 | !! |
---|
2171 | !! ** Purpose : define horizontal grids |
---|
2172 | !!---------------------------------------------------------------------- |
---|
2173 | CHARACTER(LEN=1) , INTENT(in) :: cdgrd |
---|
2174 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plon |
---|
2175 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plat |
---|
2176 | ! |
---|
2177 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: zmask |
---|
2178 | LOGICAL, INTENT(IN) :: ldxios, ldrxios |
---|
2179 | !!---------------------------------------------------------------------- |
---|
2180 | ! |
---|
2181 | CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=Ni0glo,nj_glo=Nj0glo,ibegin=mig0(Nis0)-1,jbegin=mjg0(Njs0)-1,ni=Ni_0,nj=Nj_0) |
---|
2182 | CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = -nn_hls, data_ni = jpi, data_jbegin = -nn_hls, data_nj = jpj) |
---|
2183 | !don't define lon and lat for restart reading context. |
---|
2184 | IF ( .NOT.ldrxios ) & |
---|
2185 | CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = real(RESHAPE(plon(Nis0:Nie0, Njs0:Nje0),(/ Ni_0*Nj_0 /)),dp), & |
---|
2186 | & latvalue = real(RESHAPE(plat(Nis0:Nie0, Njs0:Nje0),(/ Ni_0*Nj_0 /)),dp )) |
---|
2187 | ! |
---|
2188 | IF ( ln_mskland .AND. (.NOT.ldxios) ) THEN |
---|
2189 | ! mask land points, keep values on coast line -> specific mask for U, V and W points |
---|
2190 | SELECT CASE ( cdgrd ) |
---|
2191 | CASE('T') ; zmask(:,:,:) = tmask(:,:,:) |
---|
2192 | CASE('U') ; zmask(2:jpim1,:,:) = tmask(2:jpim1,:,:) + tmask(3:jpi,:,:) |
---|
2193 | CASE('V') ; zmask(:,2:jpjm1,:) = tmask(:,2:jpjm1,:) + tmask(:,3:jpj,:) |
---|
2194 | CASE('W') ; zmask(:,:,2:jpk ) = tmask(:,:,1:jpkm1) + tmask(:,:,2:jpk) ; zmask(:,:,1) = tmask(:,:,1) |
---|
2195 | END SELECT |
---|
2196 | ! |
---|
2197 | CALL iom_set_domain_attr( "grid_"//cdgrd , mask = RESHAPE(zmask(Nis0:Nie0,Njs0:Nje0,1),(/Ni_0*Nj_0 /)) /= 0. ) |
---|
2198 | CALL iom_set_grid_attr ( "grid_"//cdgrd//"_3D", mask = RESHAPE(zmask(Nis0:Nie0,Njs0:Nje0,:),(/Ni_0,Nj_0,jpk/)) /= 0. ) |
---|
2199 | ENDIF |
---|
2200 | ! |
---|
2201 | END SUBROUTINE set_grid |
---|
2202 | |
---|
2203 | SUBROUTINE set_grid_bounds( cdgrd, plon_cnr, plat_cnr, plon_pnt, plat_pnt ) |
---|
2204 | !!---------------------------------------------------------------------- |
---|
2205 | !! *** ROUTINE set_grid_bounds *** |
---|
2206 | !! |
---|
2207 | !! ** Purpose : define horizontal grid corners |
---|
2208 | !! |
---|
2209 | !!---------------------------------------------------------------------- |
---|
2210 | CHARACTER(LEN=1) , INTENT(in) :: cdgrd |
---|
2211 | REAL(wp), DIMENSION(jpi,jpj) , INTENT(in) :: plon_cnr, plat_cnr ! Lat/lon coord. of a contiguous vertex of cell (i,j) |
---|
2212 | REAL(wp), DIMENSION(jpi,jpj), OPTIONAL, INTENT(in) :: plon_pnt, plat_pnt ! Lat/lon coord. of the point of cell (i,j) |
---|
2213 | ! |
---|
2214 | INTEGER :: ji, jj, jn |
---|
2215 | INTEGER :: icnr, jcnr ! Offset such that the vertex coordinate (i+icnr,j+jcnr) |
---|
2216 | ! ! represents the |
---|
2217 | ! bottom-left corner of |
---|
2218 | ! cell (i,j) |
---|
2219 | REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z_bnds ! Lat/lon coordinates of the vertices of cell (i,j) |
---|
2220 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_fld ! Working array to determine where to rotate cells |
---|
2221 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_rot ! Lat/lon working array for rotation of cells |
---|
2222 | !!---------------------------------------------------------------------- |
---|
2223 | ! |
---|
2224 | ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2) ) |
---|
2225 | ! |
---|
2226 | ! Offset of coordinate representing bottom-left corner |
---|
2227 | SELECT CASE ( TRIM(cdgrd) ) |
---|
2228 | CASE ('T', 'W') ; icnr = -1 ; jcnr = -1 |
---|
2229 | CASE ('U') ; icnr = 0 ; jcnr = -1 |
---|
2230 | CASE ('V') ; icnr = -1 ; jcnr = 0 |
---|
2231 | END SELECT |
---|
2232 | ! |
---|
2233 | z_fld(:,:) = 1._wp |
---|
2234 | CALL lbc_lnk( 'iom', z_fld, cdgrd, -1.0_wp ) ! Working array for location of northfold |
---|
2235 | ! |
---|
2236 | ! Cell vertices that can be defined |
---|
2237 | DO_2D( 0, 0, 0, 0 ) |
---|
2238 | z_bnds(1,ji,jj,1) = plat_cnr(ji+icnr, jj+jcnr ) ! Bottom-left |
---|
2239 | z_bnds(2,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr ) ! Bottom-right |
---|
2240 | z_bnds(3,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right |
---|
2241 | z_bnds(4,ji,jj,1) = plat_cnr(ji+icnr, jj+jcnr+1) ! Top-left |
---|
2242 | z_bnds(1,ji,jj,2) = plon_cnr(ji+icnr, jj+jcnr ) ! Bottom-left |
---|
2243 | z_bnds(2,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr ) ! Bottom-right |
---|
2244 | z_bnds(3,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right |
---|
2245 | z_bnds(4,ji,jj,2) = plon_cnr(ji+icnr, jj+jcnr+1) ! Top-left |
---|
2246 | END_2D |
---|
2247 | ! |
---|
2248 | DO_2D( 0, 0, 0, 0 ) |
---|
2249 | IF( z_fld(ji,jj) == -1. ) THEN |
---|
2250 | z_rot(1,:) = z_bnds(3,ji,jj,:) ; z_rot(2,:) = z_bnds(4,ji,jj,:) |
---|
2251 | z_rot(3,:) = z_bnds(1,ji,jj,:) ; z_rot(4,:) = z_bnds(2,ji,jj,:) |
---|
2252 | z_bnds(:,ji,jj,:) = z_rot(:,:) |
---|
2253 | ENDIF |
---|
2254 | END_2D |
---|
2255 | ! |
---|
2256 | CALL iom_set_domain_attr("grid_"//cdgrd, bounds_lat = real(RESHAPE(z_bnds(:,Nis0:Nie0,Njs0:Nje0,1),(/ 4,Ni_0*Nj_0 /)), dp), & |
---|
2257 | & bounds_lon = real(RESHAPE(z_bnds(:,Nis0:Nie0,Njs0:Nje0,2),(/ 4,Ni_0*Nj_0 /)), dp), nvertex=4 ) |
---|
2258 | ! |
---|
2259 | DEALLOCATE( z_bnds, z_fld, z_rot ) |
---|
2260 | ! |
---|
2261 | END SUBROUTINE set_grid_bounds |
---|
2262 | |
---|
2263 | SUBROUTINE set_grid_znl( plat ) |
---|
2264 | !!---------------------------------------------------------------------- |
---|
2265 | !! *** ROUTINE set_grid_znl *** |
---|
2266 | !! |
---|
2267 | !! ** Purpose : define grids for zonal mean |
---|
2268 | !! |
---|
2269 | !!---------------------------------------------------------------------- |
---|
2270 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plat |
---|
2271 | ! |
---|
2272 | INTEGER :: ix, iy |
---|
2273 | REAL(wp), DIMENSION(:), ALLOCATABLE :: zlon |
---|
2274 | !!---------------------------------------------------------------------- |
---|
2275 | ! |
---|
2276 | ALLOCATE( zlon(Ni_0*Nj_0) ) ; zlon(:) = 0._wp |
---|
2277 | ! |
---|
2278 | ! CALL dom_ngb( -168.53_wp, 65.03_wp, ix, iy, 'T' ) ! i-line that passes through Bering Strait: Reference latitude (used in plots) |
---|
2279 | CALL dom_ngb( 180.0_wp, 90.0_wp, ix, iy, 'T' ) ! i-line that passes near the North Pole : Reference latitude (used in plots) |
---|
2280 | CALL iom_set_domain_attr("gznl", ni_glo=Ni0glo, nj_glo=Nj0glo, ibegin=mig0(Nis0)-1, jbegin=mjg0(Njs0)-1, ni=Ni_0, nj=Nj_0) |
---|
2281 | CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = -nn_hls, data_ni = jpi, data_jbegin = -nn_hls, data_nj = jpj) |
---|
2282 | CALL iom_set_domain_attr("gznl", lonvalue = real(zlon, dp), & |
---|
2283 | & latvalue = real(RESHAPE(plat(Nis0:Nie0, Njs0:Nje0),(/ Ni_0*Nj_0 /)),dp)) |
---|
2284 | CALL iom_set_zoom_domain_attr("ptr", ibegin=ix-1, jbegin=0, ni=1, nj=Nj0glo) |
---|
2285 | ! |
---|
2286 | CALL iom_update_file_name('ptr') |
---|
2287 | ! |
---|
2288 | END SUBROUTINE set_grid_znl |
---|
2289 | |
---|
2290 | |
---|
2291 | SUBROUTINE set_scalar |
---|
2292 | !!---------------------------------------------------------------------- |
---|
2293 | !! *** ROUTINE set_scalar *** |
---|
2294 | !! |
---|
2295 | !! ** Purpose : define fake grids for scalar point |
---|
2296 | !! |
---|
2297 | !!---------------------------------------------------------------------- |
---|
2298 | REAL(dp), DIMENSION(1) :: zz = 1. |
---|
2299 | !!---------------------------------------------------------------------- |
---|
2300 | ! |
---|
2301 | CALL iom_set_domain_attr('scalarpoint', ni_glo=jpnij, nj_glo=1, ibegin=narea-1, jbegin=0, ni=1, nj=1) |
---|
2302 | CALL iom_set_domain_attr('scalarpoint', data_dim=2, data_ibegin = 1, data_ni = 1, data_jbegin = 1, data_nj = 1) |
---|
2303 | ! |
---|
2304 | zz = REAL( narea, wp ) |
---|
2305 | CALL iom_set_domain_attr('scalarpoint', lonvalue=zz, latvalue=zz) |
---|
2306 | ! |
---|
2307 | END SUBROUTINE set_scalar |
---|
2308 | |
---|
2309 | |
---|
2310 | SUBROUTINE set_xmlatt |
---|
2311 | !!---------------------------------------------------------------------- |
---|
2312 | !! *** ROUTINE set_xmlatt *** |
---|
2313 | !! |
---|
2314 | !! ** Purpose : automatic definitions of some of the xml attributs... |
---|
2315 | !! |
---|
2316 | !!---------------------------------------------------------------------- |
---|
2317 | CHARACTER(len=1),DIMENSION( 3) :: clgrd ! suffix name |
---|
2318 | CHARACTER(len=256) :: clsuff ! suffix name |
---|
2319 | CHARACTER(len=1) :: cl1 ! 1 character |
---|
2320 | CHARACTER(len=2) :: cl2 ! 2 characters |
---|
2321 | CHARACTER(len=3) :: cl3 ! 3 characters |
---|
2322 | INTEGER :: ji, jg ! loop counters |
---|
2323 | INTEGER :: ix, iy ! i-,j- index |
---|
2324 | REAL(wp) ,DIMENSION(11) :: zlontao ! longitudes of tao moorings |
---|
2325 | REAL(wp) ,DIMENSION( 7) :: zlattao ! latitudes of tao moorings |
---|
2326 | REAL(wp) ,DIMENSION( 4) :: zlonrama ! longitudes of rama moorings |
---|
2327 | REAL(wp) ,DIMENSION(11) :: zlatrama ! latitudes of rama moorings |
---|
2328 | REAL(wp) ,DIMENSION( 3) :: zlonpira ! longitudes of pirata moorings |
---|
2329 | REAL(wp) ,DIMENSION( 9) :: zlatpira ! latitudes of pirata moorings |
---|
2330 | TYPE(xios_duration) :: f_op, f_of |
---|
2331 | !!---------------------------------------------------------------------- |
---|
2332 | ! |
---|
2333 | ! frequency of the call of iom_put (attribut: freq_op) |
---|
2334 | f_op%timestep = 1 ; f_of%timestep = 0 ; CALL iom_set_field_attr('field_definition', freq_op=f_op, freq_offset=f_of) |
---|
2335 | f_op%timestep = 2 ; f_of%timestep = 0 ; CALL iom_set_field_attr('trendT_even' , freq_op=f_op, freq_offset=f_of) |
---|
2336 | f_op%timestep = 2 ; f_of%timestep = -1 ; CALL iom_set_field_attr('trendT_odd' , freq_op=f_op, freq_offset=f_of) |
---|
2337 | f_op%timestep = nn_fsbc ; f_of%timestep = 0 ; CALL iom_set_field_attr('SBC' , freq_op=f_op, freq_offset=f_of) |
---|
2338 | f_op%timestep = nn_fsbc ; f_of%timestep = 0 ; CALL iom_set_field_attr('SBC_scalar' , freq_op=f_op, freq_offset=f_of) |
---|
2339 | f_op%timestep = nn_fsbc ; f_of%timestep = 0 ; CALL iom_set_field_attr('ABL' , freq_op=f_op, freq_offset=f_of) |
---|
2340 | |
---|
2341 | ! output file names (attribut: name) |
---|
2342 | DO ji = 1, 9 |
---|
2343 | WRITE(cl1,'(i1)') ji |
---|
2344 | CALL iom_update_file_name('file'//cl1) |
---|
2345 | END DO |
---|
2346 | DO ji = 1, 99 |
---|
2347 | WRITE(cl2,'(i2.2)') ji |
---|
2348 | CALL iom_update_file_name('file'//cl2) |
---|
2349 | END DO |
---|
2350 | DO ji = 1, 999 |
---|
2351 | WRITE(cl3,'(i3.3)') ji |
---|
2352 | CALL iom_update_file_name('file'//cl3) |
---|
2353 | END DO |
---|
2354 | |
---|
2355 | ! Zooms... |
---|
2356 | clgrd = (/ 'T', 'U', 'W' /) |
---|
2357 | DO jg = 1, SIZE(clgrd) ! grid type |
---|
2358 | cl1 = clgrd(jg) |
---|
2359 | ! Equatorial section (attributs: jbegin, ni, name_suffix) |
---|
2360 | CALL dom_ngb( 0.0_wp, 0.0_wp, ix, iy, cl1 ) |
---|
2361 | CALL iom_set_zoom_domain_attr('Eq'//cl1, ibegin=0, jbegin=iy-1, ni=Ni0glo, nj=1 ) |
---|
2362 | CALL iom_get_file_attr ('Eq'//cl1, name_suffix = clsuff ) |
---|
2363 | CALL iom_set_file_attr ('Eq'//cl1, name_suffix = TRIM(clsuff)//'_Eq') |
---|
2364 | CALL iom_update_file_name('Eq'//cl1) |
---|
2365 | END DO |
---|
2366 | ! TAO moorings (attributs: ibegin, jbegin, name_suffix) |
---|
2367 | zlontao = (/ 137.0, 147.0, 156.0, 165.0, -180.0, -170.0, -155.0, -140.0, -125.0, -110.0, -95.0 /) |
---|
2368 | zlattao = (/ -8.0, -5.0, -2.0, 0.0, 2.0, 5.0, 8.0 /) |
---|
2369 | CALL set_mooring( zlontao, zlattao ) |
---|
2370 | ! RAMA moorings (attributs: ibegin, jbegin, name_suffix) |
---|
2371 | zlonrama = (/ 55.0, 67.0, 80.5, 90.0 /) |
---|
2372 | zlatrama = (/ -16.0, -12.0, -8.0, -4.0, -1.5, 0.0, 1.5, 4.0, 8.0, 12.0, 15.0 /) |
---|
2373 | CALL set_mooring( zlonrama, zlatrama ) |
---|
2374 | ! PIRATA moorings (attributs: ibegin, jbegin, name_suffix) |
---|
2375 | zlonpira = (/ -38.0, -23.0, -10.0 /) |
---|
2376 | zlatpira = (/ -19.0, -14.0, -8.0, 0.0, 4.0, 8.0, 12.0, 15.0, 20.0 /) |
---|
2377 | CALL set_mooring( zlonpira, zlatpira ) |
---|
2378 | ! |
---|
2379 | END SUBROUTINE set_xmlatt |
---|
2380 | |
---|
2381 | |
---|
2382 | SUBROUTINE set_mooring( plon, plat ) |
---|
2383 | !!---------------------------------------------------------------------- |
---|
2384 | !! *** ROUTINE set_mooring *** |
---|
2385 | !! |
---|
2386 | !! ** Purpose : automatic definitions of moorings xml attributs... |
---|
2387 | !! |
---|
2388 | !!---------------------------------------------------------------------- |
---|
2389 | REAL(wp), DIMENSION(:), INTENT(in) :: plon, plat ! longitudes/latitudes oft the mooring |
---|
2390 | ! |
---|
2391 | !!$ CHARACTER(len=1),DIMENSION(4) :: clgrd = (/ 'T', 'U', 'V', 'W' /) ! suffix name |
---|
2392 | CHARACTER(len=1),DIMENSION(1) :: clgrd = (/ 'T' /) ! suffix name |
---|
2393 | CHARACTER(len=256) :: clname ! file name |
---|
2394 | CHARACTER(len=256) :: clsuff ! suffix name |
---|
2395 | CHARACTER(len=1) :: cl1 ! 1 character |
---|
2396 | CHARACTER(len=6) :: clon,clat ! name of longitude, latitude |
---|
2397 | INTEGER :: ji, jj, jg ! loop counters |
---|
2398 | INTEGER :: ix, iy ! i-,j- index |
---|
2399 | REAL(wp) :: zlon, zlat |
---|
2400 | !!---------------------------------------------------------------------- |
---|
2401 | DO jg = 1, SIZE(clgrd) |
---|
2402 | cl1 = clgrd(jg) |
---|
2403 | DO ji = 1, SIZE(plon) |
---|
2404 | DO jj = 1, SIZE(plat) |
---|
2405 | zlon = plon(ji) |
---|
2406 | zlat = plat(jj) |
---|
2407 | ! modifications for RAMA moorings |
---|
2408 | IF( zlon == 67. .AND. zlat == 15. ) zlon = 65. |
---|
2409 | IF( zlon == 90. .AND. zlat <= -4. ) zlon = 95. |
---|
2410 | IF( zlon == 95. .AND. zlat == -4. ) zlat = -5. |
---|
2411 | ! modifications for PIRATA moorings |
---|
2412 | IF( zlon == -38. .AND. zlat == -19. ) zlon = -34. |
---|
2413 | IF( zlon == -38. .AND. zlat == -14. ) zlon = -32. |
---|
2414 | IF( zlon == -38. .AND. zlat == -8. ) zlon = -30. |
---|
2415 | IF( zlon == -38. .AND. zlat == 0. ) zlon = -35. |
---|
2416 | IF( zlon == -23. .AND. zlat == 20. ) zlat = 21. |
---|
2417 | IF( zlon == -10. .AND. zlat == -14. ) zlat = -10. |
---|
2418 | IF( zlon == -10. .AND. zlat == -8. ) zlat = -6. |
---|
2419 | IF( zlon == -10. .AND. zlat == 4. ) THEN ; zlon = 0. ; zlat = 0. ; ENDIF |
---|
2420 | CALL dom_ngb( zlon, zlat, ix, iy, cl1 ) |
---|
2421 | IF( zlon >= 0. ) THEN |
---|
2422 | IF( zlon == REAL(NINT(zlon), wp) ) THEN ; WRITE(clon, '(i3, a)') NINT( zlon), 'e' |
---|
2423 | ELSE ; WRITE(clon, '(f5.1,a)') zlon , 'e' |
---|
2424 | ENDIF |
---|
2425 | ELSE |
---|
2426 | IF( zlon == REAL(NINT(zlon), wp) ) THEN ; WRITE(clon, '(i3, a)') NINT(-zlon), 'w' |
---|
2427 | ELSE ; WRITE(clon, '(f5.1,a)') -zlon , 'w' |
---|
2428 | ENDIF |
---|
2429 | ENDIF |
---|
2430 | IF( zlat >= 0. ) THEN |
---|
2431 | IF( zlat == REAL(NINT(zlat), wp) ) THEN ; WRITE(clat, '(i2, a)') NINT( zlat), 'n' |
---|
2432 | ELSE ; WRITE(clat, '(f4.1,a)') zlat , 'n' |
---|
2433 | ENDIF |
---|
2434 | ELSE |
---|
2435 | IF( zlat == REAL(NINT(zlat), wp) ) THEN ; WRITE(clat, '(i2, a)') NINT(-zlat), 's' |
---|
2436 | ELSE ; WRITE(clat, '(f4.1,a)') -zlat , 's' |
---|
2437 | ENDIF |
---|
2438 | ENDIF |
---|
2439 | clname = TRIM(ADJUSTL(clat))//TRIM(ADJUSTL(clon)) |
---|
2440 | CALL iom_set_zoom_domain_attr(TRIM(clname)//cl1, ibegin= ix-1, jbegin= iy-1, ni=1, nj=1) |
---|
2441 | |
---|
2442 | CALL iom_get_file_attr (TRIM(clname)//cl1, name_suffix = clsuff ) |
---|
2443 | CALL iom_set_file_attr (TRIM(clname)//cl1, name_suffix = TRIM(clsuff)//'_'//TRIM(clname)) |
---|
2444 | CALL iom_update_file_name(TRIM(clname)//cl1) |
---|
2445 | END DO |
---|
2446 | END DO |
---|
2447 | END DO |
---|
2448 | |
---|
2449 | END SUBROUTINE set_mooring |
---|
2450 | |
---|
2451 | |
---|
2452 | SUBROUTINE iom_update_file_name( cdid ) |
---|
2453 | !!---------------------------------------------------------------------- |
---|
2454 | !! *** ROUTINE iom_update_file_name *** |
---|
2455 | !! |
---|
2456 | !! ** Purpose : |
---|
2457 | !! |
---|
2458 | !!---------------------------------------------------------------------- |
---|
2459 | CHARACTER(LEN=*) , INTENT(in) :: cdid |
---|
2460 | ! |
---|
2461 | CHARACTER(LEN=256) :: clname |
---|
2462 | CHARACTER(LEN=20) :: clfreq |
---|
2463 | CHARACTER(LEN=20) :: cldate |
---|
2464 | INTEGER :: idx |
---|
2465 | INTEGER :: jn |
---|
2466 | INTEGER :: itrlen |
---|
2467 | INTEGER :: iyear, imonth, iday, isec |
---|
2468 | REAL(wp) :: zsec |
---|
2469 | LOGICAL :: llexist |
---|
2470 | TYPE(xios_duration) :: output_freq |
---|
2471 | !!---------------------------------------------------------------------- |
---|
2472 | ! |
---|
2473 | DO jn = 1, 2 |
---|
2474 | ! |
---|
2475 | output_freq = xios_duration(0,0,0,0,0,0) |
---|
2476 | IF( jn == 1 ) CALL iom_get_file_attr( cdid, name = clname, output_freq = output_freq ) |
---|
2477 | IF( jn == 2 ) CALL iom_get_file_attr( cdid, name_suffix = clname ) |
---|
2478 | ! |
---|
2479 | IF ( TRIM(clname) /= '' ) THEN |
---|
2480 | ! |
---|
2481 | idx = INDEX(clname,'@expname@') + INDEX(clname,'@EXPNAME@') |
---|
2482 | DO WHILE ( idx /= 0 ) |
---|
2483 | clname = clname(1:idx-1)//TRIM(cexper)//clname(idx+9:LEN_TRIM(clname)) |
---|
2484 | idx = INDEX(clname,'@expname@') + INDEX(clname,'@EXPNAME@') |
---|
2485 | END DO |
---|
2486 | ! |
---|
2487 | idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') |
---|
2488 | DO WHILE ( idx /= 0 ) |
---|
2489 | IF ( output_freq%timestep /= 0) THEN |
---|
2490 | WRITE(clfreq,'(I18,A2)')INT(output_freq%timestep),'ts' |
---|
2491 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2492 | ELSE IF ( output_freq%second /= 0 ) THEN |
---|
2493 | WRITE(clfreq,'(I19,A1)')INT(output_freq%second),'s' |
---|
2494 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2495 | ELSE IF ( output_freq%minute /= 0 ) THEN |
---|
2496 | WRITE(clfreq,'(I18,A2)')INT(output_freq%minute),'mi' |
---|
2497 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2498 | ELSE IF ( output_freq%hour /= 0 ) THEN |
---|
2499 | WRITE(clfreq,'(I19,A1)')INT(output_freq%hour),'h' |
---|
2500 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2501 | ELSE IF ( output_freq%day /= 0 ) THEN |
---|
2502 | WRITE(clfreq,'(I19,A1)')INT(output_freq%day),'d' |
---|
2503 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2504 | ELSE IF ( output_freq%month /= 0 ) THEN |
---|
2505 | WRITE(clfreq,'(I19,A1)')INT(output_freq%month),'m' |
---|
2506 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2507 | ELSE IF ( output_freq%year /= 0 ) THEN |
---|
2508 | WRITE(clfreq,'(I19,A1)')INT(output_freq%year),'y' |
---|
2509 | itrlen = LEN_TRIM(ADJUSTL(clfreq)) |
---|
2510 | ELSE |
---|
2511 | CALL ctl_stop('error in the name of file id '//TRIM(cdid), & |
---|
2512 | & ' attribute output_freq is undefined -> cannot replace @freq@ in '//TRIM(clname) ) |
---|
2513 | ENDIF |
---|
2514 | clname = clname(1:idx-1)//TRIM(ADJUSTL(clfreq))//clname(idx+6:LEN_TRIM(clname)) |
---|
2515 | idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@') |
---|
2516 | END DO |
---|
2517 | ! |
---|
2518 | idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') |
---|
2519 | DO WHILE ( idx /= 0 ) |
---|
2520 | cldate = iom_sdate( fjulday - rn_Dt / rday ) |
---|
2521 | clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+11:LEN_TRIM(clname)) |
---|
2522 | idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@') |
---|
2523 | END DO |
---|
2524 | ! |
---|
2525 | idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') |
---|
2526 | DO WHILE ( idx /= 0 ) |
---|
2527 | cldate = iom_sdate( fjulday - rn_Dt / rday, ldfull = .TRUE. ) |
---|
2528 | clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+15:LEN_TRIM(clname)) |
---|
2529 | idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@') |
---|
2530 | END DO |
---|
2531 | ! |
---|
2532 | idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') |
---|
2533 | DO WHILE ( idx /= 0 ) |
---|
2534 | cldate = iom_sdate( fjulday + rn_Dt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. ) |
---|
2535 | clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+9:LEN_TRIM(clname)) |
---|
2536 | idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@') |
---|
2537 | END DO |
---|
2538 | ! |
---|
2539 | idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') |
---|
2540 | DO WHILE ( idx /= 0 ) |
---|
2541 | cldate = iom_sdate( fjulday + rn_Dt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. ) |
---|
2542 | clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+13:LEN_TRIM(clname)) |
---|
2543 | idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@') |
---|
2544 | END DO |
---|
2545 | ! |
---|
2546 | IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) |
---|
2547 | IF( jn == 1 ) CALL iom_set_file_attr( cdid, name = clname ) |
---|
2548 | IF( jn == 2 ) CALL iom_set_file_attr( cdid, name_suffix = clname ) |
---|
2549 | ! |
---|
2550 | ENDIF |
---|
2551 | ! |
---|
2552 | END DO |
---|
2553 | ! |
---|
2554 | END SUBROUTINE iom_update_file_name |
---|
2555 | |
---|
2556 | |
---|
2557 | FUNCTION iom_sdate( pjday, ld24, ldfull ) |
---|
2558 | !!---------------------------------------------------------------------- |
---|
2559 | !! *** ROUTINE iom_sdate *** |
---|
2560 | !! |
---|
2561 | !! ** Purpose : send back the date corresponding to the given julian day |
---|
2562 | !!---------------------------------------------------------------------- |
---|
2563 | REAL(wp), INTENT(in ) :: pjday ! julian day |
---|
2564 | LOGICAL , INTENT(in ), OPTIONAL :: ld24 ! true to force 24:00 instead of 00:00 |
---|
2565 | LOGICAL , INTENT(in ), OPTIONAL :: ldfull ! true to get the compleate date: yyyymmdd_hh:mm:ss |
---|
2566 | ! |
---|
2567 | CHARACTER(LEN=20) :: iom_sdate |
---|
2568 | CHARACTER(LEN=50) :: clfmt ! format used to write the date |
---|
2569 | INTEGER :: iyear, imonth, iday, ihour, iminute, isec |
---|
2570 | REAL(wp) :: zsec |
---|
2571 | LOGICAL :: ll24, llfull |
---|
2572 | !!---------------------------------------------------------------------- |
---|
2573 | ! |
---|
2574 | IF( PRESENT(ld24) ) THEN ; ll24 = ld24 |
---|
2575 | ELSE ; ll24 = .FALSE. |
---|
2576 | ENDIF |
---|
2577 | ! |
---|
2578 | IF( PRESENT(ldfull) ) THEN ; llfull = ldfull |
---|
2579 | ELSE ; llfull = .FALSE. |
---|
2580 | ENDIF |
---|
2581 | ! |
---|
2582 | CALL ju2ymds( pjday, iyear, imonth, iday, zsec ) |
---|
2583 | isec = NINT(zsec) |
---|
2584 | ! |
---|
2585 | IF ( ll24 .AND. isec == 0 ) THEN ! 00:00 of the next day -> move to 24:00 of the current day |
---|
2586 | CALL ju2ymds( pjday - 1.0_wp, iyear, imonth, iday, zsec ) |
---|
2587 | isec = 86400 |
---|
2588 | ENDIF |
---|
2589 | ! |
---|
2590 | IF( iyear < 10000 ) THEN ; clfmt = "i4.4,2i2.2" ! format used to write the date |
---|
2591 | ELSE ; WRITE(clfmt, "('i',i1,',2i2.2')") INT(LOG10(REAL(iyear,wp))) + 1 |
---|
2592 | ENDIF |
---|
2593 | ! |
---|
2594 | !$AGRIF_DO_NOT_TREAT |
---|
2595 | ! needed in the conv |
---|
2596 | IF( llfull ) THEN |
---|
2597 | clfmt = TRIM(clfmt)//",'_',i2.2,':',i2.2,':',i2.2" |
---|
2598 | ihour = isec / 3600 |
---|
2599 | isec = MOD(isec, 3600) |
---|
2600 | iminute = isec / 60 |
---|
2601 | isec = MOD(isec, 60) |
---|
2602 | WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday, ihour, iminute, isec ! date of the end of run |
---|
2603 | ELSE |
---|
2604 | WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday ! date of the end of run |
---|
2605 | ENDIF |
---|
2606 | !$AGRIF_END_DO_NOT_TREAT |
---|
2607 | ! |
---|
2608 | END FUNCTION iom_sdate |
---|
2609 | |
---|
2610 | #else |
---|
2611 | !!---------------------------------------------------------------------- |
---|
2612 | !! NOT 'key_iomput' a few dummy routines |
---|
2613 | !!---------------------------------------------------------------------- |
---|
2614 | SUBROUTINE iom_setkt( kt, cdname ) |
---|
2615 | INTEGER , INTENT(in):: kt |
---|
2616 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
2617 | IF( .FALSE. ) WRITE(numout,*) kt, cdname ! useless test to avoid compilation warnings |
---|
2618 | END SUBROUTINE iom_setkt |
---|
2619 | |
---|
2620 | SUBROUTINE iom_context_finalize( cdname ) |
---|
2621 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
2622 | IF( .FALSE. ) WRITE(numout,*) cdname ! useless test to avoid compilation warnings |
---|
2623 | END SUBROUTINE iom_context_finalize |
---|
2624 | |
---|
2625 | SUBROUTINE iom_update_file_name( cdid ) |
---|
2626 | CHARACTER(LEN=*), INTENT(in) :: cdid |
---|
2627 | IF( .FALSE. ) WRITE(numout,*) cdid ! useless test to avoid compilation warnings |
---|
2628 | END SUBROUTINE iom_update_file_name |
---|
2629 | |
---|
2630 | #endif |
---|
2631 | |
---|
2632 | LOGICAL FUNCTION iom_use( cdname ) |
---|
2633 | CHARACTER(LEN=*), INTENT(in) :: cdname |
---|
2634 | #if defined key_iomput |
---|
2635 | iom_use = xios_field_is_active( cdname ) |
---|
2636 | #else |
---|
2637 | iom_use = .FALSE. |
---|
2638 | #endif |
---|
2639 | END FUNCTION iom_use |
---|
2640 | |
---|
2641 | SUBROUTINE iom_miss_val( cdname, pmiss_val ) |
---|
2642 | CHARACTER(LEN=*), INTENT(in ) :: cdname |
---|
2643 | REAL(wp) , INTENT(out) :: pmiss_val |
---|
2644 | REAL(dp) :: ztmp_pmiss_val |
---|
2645 | #if defined key_iomput |
---|
2646 | ! get missing value |
---|
2647 | CALL xios_get_field_attr( cdname, default_value = ztmp_pmiss_val ) |
---|
2648 | pmiss_val = ztmp_pmiss_val |
---|
2649 | #else |
---|
2650 | IF( .FALSE. ) WRITE(numout,*) cdname, pmiss_val ! useless test to avoid compilation warnings |
---|
2651 | IF( .FALSE. ) pmiss_val = 0._wp ! useless assignment to avoid compilation warnings |
---|
2652 | #endif |
---|
2653 | END SUBROUTINE iom_miss_val |
---|
2654 | |
---|
2655 | !!====================================================================== |
---|
2656 | END MODULE iom |
---|