New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
iom_cdf.f90 in NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/SIREN/src – NEMO

source: NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/TOOLS/SIREN/src/iom_cdf.f90 @ 10115

Last change on this file since 10115 was 10115, checked in by cbricaud, 6 years ago

phase 3.6 coarsening branch with nemo_3.6_rev9192

File size: 85.2 KB
Line 
1!----------------------------------------------------------------------
2! NEMO system team, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! MODULE: iom_cdf
6!
7! DESCRIPTION:
8!> @brief NETCDF Input/Output manager :  Library to read Netcdf input files
9!>
10!> @details
11!>    to open netcdf file:<br/>
12!> @code
13!>    CALL iom_cdf_open(td_file)
14!> @endcode
15!>       - td_file is file structure (see @ref file)
16!>
17!>    to write in netcdf file:<br/>
18!> @code
19!>    CALL  iom_cdf_write_file(td_file)
20!> @endcode
21!>
22!>    to close netcdf file:<br/>
23!> @code
24!>    CALL iom_cdf_close(tl_file)
25!> @endcode
26!>
27!>    to read one dimension in netcdf file:<br/>
28!> @code
29!>    tl_dim = iom_cdf_read_dim(tl_file, id_dimid)
30!> @endcode
31!>    or
32!> @code
33!>    tl_dim = iom_cdf_read_dim(tl_file, cd_name)
34!> @endcode
35!>       - id_dimid is dimension id<br/>
36!>       - cd_name is dimension name
37!>
38!>    to read one attribute in netcdf file:<br/>
39!> @code
40!>    tl_att = iom_cdf_read_att(tl_file, id_varid, id_attid)
41!> @endcode
42!>    or
43!> @code
44!>    tl_att = iom_cdf_read_att(tl_file, id_varid, cd_name)
45!> @endcode
46!>       - id_varid is variable id
47!>       - id_attid is attribute id<br/>
48!>       - cd_name is attribute name
49!>   
50!>    to read one variable in netcdf file:<br/>
51!> @code
52!>    tl_var = iom_cdf_read_var(td_file, id_varid, [id_start, id_count])
53!> @endcode
54!>    or
55!> @code
56!>    tl_var = iom_cdf_read_var(td_file, cd_name, [id_start, [id_count,]])
57!> @endcode
58!>       - id_varid is variabale id
59!>       - cd_name is variabale name
60!>       - id_start is a integer(4) 1D array of index from which the data
61!>          values will be read [optional]
62!>       - id_count is a integer(4) 1D array of the number of indices selected
63!>          along each dimension [optional]
64!>
65!> @author
66!> J.Paul
67! REVISION HISTORY:
68!> @date November, 2013 - Initial Version
69!
70!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
71!----------------------------------------------------------------------
72MODULE iom_cdf
73   USE netcdf                          ! nf90 library
74   USE global                          ! global parameter
75   USE kind                            ! F90 kind parameter
76   USE fct                             ! basic useful function
77   USE logger                          ! log file manager
78   USE att                             ! attribute manage
79   USE dim                             ! dimension manager
80   USE var                             ! variable manager
81   USE file                            ! file manager
82   IMPLICIT NONE
83   ! NOTE_avoid_public_variables_if_possible
84
85   ! function and subroutine
86   PUBLIC :: iom_cdf_open        !< open or create netcdf file, return file structure
87   PUBLIC :: iom_cdf_close       !< close netcdf file
88   PUBLIC :: iom_cdf_read_dim    !< read one dimension in an opened netcdf file, return dimension structure
89   PUBLIC :: iom_cdf_read_att    !< read one attribute in an opened netcdf file, return attribute structure
90   PUBLIC :: iom_cdf_read_var    !< read one variable  in an opened netcdf file, return variable  structure
91   PUBLIC :: iom_cdf_fill_var    !< fill variable value in an opened netcdf file
92   PUBLIC :: iom_cdf_write_file  !< write file structure contents in an opened netcdf file
93
94   PRIVATE :: iom_cdf__check           ! provides a simple interface to netcdf error message
95   PRIVATE :: iom_cdf__get_info        ! get global information in an opened netcdf file
96   PRIVATE :: iom_cdf__get_file_dim    ! read dimension on an opened netcdf file, and reorder it
97   PRIVATE :: iom_cdf__get_file_att    ! read global attribute on an opened netcdf file
98   PRIVATE :: iom_cdf__get_file_var    ! read information about variable on an opened netcdf file
99   PRIVATE :: iom_cdf__read_dim_id     ! read one dimension in an opened netcdf file, given dimension id.
100   PRIVATE :: iom_cdf__read_dim_name   ! read one dimension in an opened netcdf file, given dimension name.
101   PRIVATE :: iom_cdf__read_att_name   ! read variable or global attribute in an opened netcdf file, given attribute name.
102   PRIVATE :: iom_cdf__read_att_id     ! read variable or global attribute in an opened netcdf file, given attribute id.
103   PRIVATE :: iom_cdf__read_var_id     ! read variable value in an opened netcdf file, given variable id.
104   PRIVATE :: iom_cdf__read_var_name   ! read variable value in an opened netcdf file, given variable name or standard name.
105   PRIVATE :: iom_cdf__read_var_meta   ! read metadata of a variable in an opened netcdf file.
106   PRIVATE :: iom_cdf__read_var_dim    ! read variable dimension in an opened netcdf file.
107   PRIVATE :: iom_cdf__read_var_att    ! read variable attributes in an opened netcdf file.
108   PRIVATE :: iom_cdf__read_var_value  ! read variable value in an opened netcdf file.
109   PRIVATE :: iom_cdf__write_dim       ! write one dimension in an opened netcdf file in write mode.
110   PRIVATE :: iom_cdf__write_att       ! write a variable attribute in an opened netcdf file.
111   PRIVATE :: iom_cdf__write_var       ! write a variable in an opened netcdf file.
112   PRIVATE :: iom_cdf__write_var_def   ! define variable in an opened netcdf file.
113   PRIVATE :: iom_cdf__write_var_value ! put variable value in an opened netcdf file.
114   PRIVATE :: iom_cdf__fill_var_id     ! fill variable value in an opened netcdf file, given variable id
115   PRIVATE :: iom_cdf__fill_var_name   ! fill variable value in an opened netcdf file, given variable name
116   PRIVATE :: iom_cdf__fill_var_all    ! fill all variable value in an opened netcdf file
117   PRIVATE :: iom_cdf__del_coord_var   ! remove coordinate variable from an opened netcdf file
118
119   INTERFACE iom_cdf_read_var
120      MODULE PROCEDURE iom_cdf__read_var_id
121      MODULE PROCEDURE iom_cdf__read_var_name
122   END INTERFACE iom_cdf_read_var
123
124   INTERFACE iom_cdf_fill_var
125      MODULE PROCEDURE iom_cdf__fill_var_id
126      MODULE PROCEDURE iom_cdf__fill_var_name
127      MODULE PROCEDURE iom_cdf__fill_var_all
128   END INTERFACE iom_cdf_fill_var
129
130   INTERFACE iom_cdf_read_dim
131      MODULE PROCEDURE iom_cdf__read_dim_id
132      MODULE PROCEDURE iom_cdf__read_dim_name
133   END INTERFACE iom_cdf_read_dim
134
135   INTERFACE iom_cdf_read_att
136      MODULE PROCEDURE iom_cdf__read_att_id
137      MODULE PROCEDURE iom_cdf__read_att_name
138   END INTERFACE iom_cdf_read_att
139
140CONTAINS
141   !-------------------------------------------------------------------
142   !> @brief This subroutine provides a simple interface to
143   !> netcdf error message
144   !>
145   !> @author J.Paul
146   !> @date November, 2013 - Initial Version
147   !> @date May, 2015 - add optional message to netcdf error message
148   !>
149   !> @param[in] id_status error status
150   !> @param[in] cd_msg    message
151   !-------------------------------------------------------------------
152   SUBROUTINE iom_cdf__check(id_status, cd_msg)
153      IMPLICIT NONE
154      ! Argument     
155      INTEGER(i4)     , INTENT(IN)           :: id_status
156      CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: cd_msg
157      ! local variable
158      CHARACTER(LEN=lc) :: cl_msg
159      !----------------------------------------------------------------
160
161      cl_msg=""
162      IF( PRESENT(cd_msg) ) cl_msg=cd_msg
163
164      IF( id_status /= NF90_NOERR )THEN
165         CALL logger_error(TRIM(cl_msg)//TRIM(NF90_STRERROR(id_status)))
166      ENDIF
167
168   END SUBROUTINE iom_cdf__check
169   !-------------------------------------------------------------------
170   !> @brief This subroutine open a netcdf file in read or write mode.
171   !> @details
172   !> if try to open a file in write mode that did not exist, create it.<br/>
173   !> if file already exist, get information about0:<br/>
174   !> - the number of variables
175   !> - the number of dimensions
176   !> - the number of global attributes
177   !> - the ID of the unlimited dimension
178   !> - the file format
179   !> Finally it read dimensions, and 'longitude' variable to compute East-West
180   !> overlap.
181   !>
182   !> @author J.Paul
183   !> @date November, 2013 - Initial Version
184   !
185   !> @param[inout] td_file   file structure
186   !-------------------------------------------------------------------
187   SUBROUTINE iom_cdf_open(td_file)
188      IMPLICIT NONE
189      ! Argument     
190      TYPE(TFILE), INTENT(INOUT)  :: td_file
191
192      ! local variable
193      LOGICAL     :: ll_exist
194      LOGICAL     :: ll_open
195
196      INTEGER(i4) :: il_status
197      !----------------------------------------------------------------
198
199      ! check file existence
200      INQUIRE(FILE=TRIM(td_file%c_name), EXIST=ll_exist, OPENED=ll_open)
201      ! ll_open do not work for netcdf file, always return FALSE
202      IF( .NOT. ll_exist .OR. TRIM(td_file%c_type) /= 'cdf' )THEN
203
204         IF( .NOT. td_file%l_wrt )THEN
205
206            CALL logger_fatal( " IOM CDF OPEN: can not open file "//&
207            &               TRIM(td_file%c_name) )
208 
209         ELSE
210
211            CALL logger_info( " IOM CDF CREATE: file "//TRIM(td_file%c_name) )
212
213            il_status = NF90_CREATE(TRIM(td_file%c_name),&
214            &                       cmode=NF90_64BIT_OFFSET,&
215            &                       ncid=td_file%i_id)
216            CALL iom_cdf__check(il_status," IOM CDF CREATE: ")
217
218            td_file%l_def=.TRUE.
219
220         ENDIF
221
222      ELSE
223
224         IF( td_file%i_id /= 0 )THEN
225
226            CALL logger_error( " IOM CDF OPEN: file "//&
227            &               TRIM(td_file%c_name)//" already opened")
228
229         ELSE
230 
231            IF( .NOT. td_file%l_wrt )THEN
232
233               CALL logger_info( " IOM CDF OPEN: file "//&
234               &              TRIM(td_file%c_name)//" in read only mode" )
235
236               il_status = NF90_OPEN( TRIM(td_file%c_name), &
237               &                      NF90_NOWRITE,         &
238               &                      td_file%i_id)
239               CALL iom_cdf__check(il_status," IOM CDF OPEN: ")
240
241            ELSE
242
243               CALL logger_info( "IOM CDF OPEN: file "//&
244               &              TRIM(td_file%c_name)//" in write mode" )
245
246               il_status = NF90_OPEN( TRIM(td_file%c_name), &
247               &                      NF90_WRITE,           &
248               &                      td_file%i_id)
249               CALL iom_cdf__check(il_status,"IOM CDF OPEN: ")
250
251            ENDIF
252
253            ! get general information about file
254            CALL iom_cdf__get_info(td_file)
255
256            ! read dimension in file
257            CALL iom_cdf__get_file_dim(td_file) 
258
259            ! read global attribute in file
260            CALL iom_cdf__get_file_att(td_file)
261
262            ! get information about variables in file
263            CALL iom_cdf__get_file_var(td_file)
264
265            ! remove dimension variable from list of variable
266            CALL iom_cdf__del_coord_var(td_file)
267
268         ENDIF
269
270      ENDIF
271
272   END SUBROUTINE iom_cdf_open
273   !-------------------------------------------------------------------
274   !> @brief This subroutine close netcdf file.
275   !>
276   !> @author J.Paul
277   !> @date November, 2013 - Initial Version
278   !
279   !> @param[inout] td_file   file structure
280   !-------------------------------------------------------------------
281   SUBROUTINE iom_cdf_close(td_file)
282      IMPLICIT NONE
283      ! Argument     
284      TYPE(TFILE), INTENT(INOUT) :: td_file
285
286      ! local variable
287      INTEGER(i4) :: il_status
288      !----------------------------------------------------------------
289
290      ! check if file opened
291      IF( td_file%i_id == 0 )THEN
292
293         CALL logger_error( &
294         &  " IOM CDF CLOSE: no id associated to file "//TRIM(td_file%c_name))
295
296      ELSE
297         CALL logger_info( &
298         &  " IOM CDF CLOSE: file "//TRIM(td_file%c_name))
299
300         il_status = NF90_CLOSE(td_file%i_id)
301         CALL iom_cdf__check(il_status,"IOM CDF CLOSE: ")
302
303         td_file%i_id = 0
304
305      ENDIF
306
307   END SUBROUTINE iom_cdf_close
308   !-------------------------------------------------------------------
309   !> @brief This subroutine get global information in an opened netcdf
310   !> file.
311   !> @details
312   !> It gets the number of variables, the number of dimensions,
313   !> the number of global attributes, the ID of the unlimited dimension
314   !> and finally the format version and filled file strucuture with it.
315   !>
316   !> @author J.Paul
317   !> @date November, 2013 - Initial Version
318   !> @date October, 2016
319   !> - define cdf4 as cdf.
320   !
321   !> @param[inout] td_file   file structure
322   !-------------------------------------------------------------------
323   SUBROUTINE iom_cdf__get_info(td_file)
324      IMPLICIT NONE
325      ! Argument     
326      TYPE(TFILE), INTENT(INOUT) :: td_file
327
328      ! local variable
329      INTEGER(i4) :: il_fmt   ! format version
330      INTEGER(i4) :: il_status
331      !----------------------------------------------------------------
332
333      CALL logger_trace( &
334      &  " IOM CDF GET INFO: about netcdf file "//TRIM(td_file%c_name))
335
336      il_status=NF90_INQUIRE(td_file%i_id, td_file%i_ndim, &
337      &     td_file%i_nvar, td_file%i_natt, td_file%i_uldid, il_fmt)
338      CALL iom_cdf__check(il_status,"IOM CDF GET INFO: ")
339
340      SELECT CASE(il_fmt)
341         CASE(nf90_format_classic, nf90_format_64bit)
342            td_file%c_type='cdf'
343         CASE(nf90_format_netcdf4, nf90_format_netcdf4_classic)
344            !td_file%c_type='cdf4'
345            td_file%c_type='cdf'
346      END SELECT
347      CALL logger_debug("IOM CDF GET INFO: type "//TRIM(td_file%c_type)) 
348
349      ! record header infos
350      td_file%i_rhd=1
351
352   END SUBROUTINE iom_cdf__get_info
353   !-------------------------------------------------------------------
354   !> @brief This subroutine read dimension on an opened netcdf file, and
355   !> reorder dimension to ('x', 'y', 'z', 't').
356   !> The dimension structure inside file structure is then completed.
357   !>
358   !> @author J.Paul
359   !> @date November, 2013 - Initial Version
360   !> @date October, 2016
361   !> - check unknown dimension
362   !>
363   !> @param[inout] td_file   file structure
364   !-------------------------------------------------------------------
365   SUBROUTINE iom_cdf__get_file_dim(td_file)
366      IMPLICIT NONE
367      ! Argument     
368      TYPE(TFILE), INTENT(INOUT) :: td_file
369      ! local variable
370      TYPE(TDIM) :: tl_dim
371
372      ! loop indices
373      INTEGER(i4) :: ji
374      INTEGER(i4) :: ii
375      !----------------------------------------------------------------
376
377      ! clean dimension
378      DO ji=1,ip_maxdim
379         CALL dim_clean(td_file%t_dim(ji))
380      ENDDO
381
382      IF( td_file%i_ndim > 0 )THEN
383
384         ii=1
385         DO ji = 1, td_file%i_ndim
386            ! read dimension information
387            tl_dim=iom_cdf_read_dim( td_file, ji)
388            ! sname == 'u' if dimension is unknown (not to be used)
389            IF( TRIM(tl_dim%c_sname) /= 'u' )THEN
390               IF( ii > ip_maxdim )THEN
391                  CALL logger_fatal("IOM CDF OPEN: too much dimension "//&
392                  & "to be read. you could choose dimension to be used. see "//&
393                  & " configuration file")
394               ENDIF
395               td_file%t_dim(ii)=dim_copy(tl_dim)
396               ii=ii+1
397            ENDIF
398         ENDDO
399
400         ! inform unlimited dimension
401         IF( td_file%i_uldid == -1 )THEN
402            CALL logger_warn( &
403            &  " IOM CDF GET FILE DIM: there is no unlimited dimension in file "//&
404            &  TRIM(td_file%c_name))
405         !ELSE
406         !   td_file%t_dim( td_file%i_uldid )%l_uld=.TRUE.
407         ENDIF
408
409      ELSE
410
411         CALL logger_warn( &
412         &  " IOM CDF GET FILE DIM: there is no dimension in file "//&
413         &  TRIM(td_file%c_name))
414
415      ENDIF
416
417      ! reorder dimension to ('x','y','z','t')
418      CALL dim_reorder(td_file%t_dim(:))
419
420   END SUBROUTINE iom_cdf__get_file_dim
421   !-------------------------------------------------------------------
422   !> @brief This subroutine read global attribute on an opened netcdf
423   !> file.
424   !> The attribute structure inside file structure is then completed.
425   !
426   !> @author J.Paul
427   !> @date November, 2013 - Initial Version
428   !> @date September, 2014
429   !> - use attribute periodicity read from the file if present.
430   !
431   !> @param[inout] td_file   file structure
432   !-------------------------------------------------------------------
433   SUBROUTINE iom_cdf__get_file_att(td_file)
434      IMPLICIT NONE
435      ! Argument     
436      TYPE(TFILE), INTENT(INOUT) :: td_file
437
438      ! local variable
439      TYPE(TATT) :: tl_att
440
441      ! loop indices
442      INTEGER(i4) :: ji
443      INTEGER(i4) :: ii
444      !----------------------------------------------------------------
445
446      IF( td_file%i_natt > 0 )THEN
447         IF(ASSOCIATED(td_file%t_att))THEN
448            CALL att_clean(td_file%t_att(:))
449            DEALLOCATE(td_file%t_att)
450         ENDIF
451         ALLOCATE(td_file%t_att(td_file%i_natt))
452
453         ii=1
454         DO ji = 1, td_file%i_natt
455            ! read global attribute
456            tl_att=iom_cdf_read_att( td_file, NF90_GLOBAL, ji)
457            IF( .NOT. att_is_dummy(tl_att) )THEN
458               td_file%t_att(ii)=att_copy(tl_att)
459               ii=ii+1
460            ENDIF
461           
462         ENDDO
463
464      ELSE
465         CALL logger_debug( &
466         &  " IOM CDF GET FILE ATT: there is no global attribute in file "//&
467         &  TRIM(td_file%c_name))
468      ENDIF
469
470   END SUBROUTINE iom_cdf__get_file_att
471   !-------------------------------------------------------------------
472   !> @brief This subroutine read information about variable of an
473   !> opened netcdf file.
474   !> The variable structure inside file structure is then completed.
475   !> @note variable value are not read !
476   !>
477   !> @author J.Paul
478   !> @date November, 2013 - Initial Version
479   !> @date September, 2015
480   !> - manage useless (dummy) variable
481   !> @date January, 2016
482   !> - increment n3d for 4D variable
483   !> @date October, 2016
484   !> - check variable to be used (variable's dimension allowed and variable
485   !> not "dummy")
486   !>
487   !> @param[inout] td_file   file structure
488   !-------------------------------------------------------------------
489   SUBROUTINE iom_cdf__get_file_var(td_file)
490      IMPLICIT NONE
491      ! Argument     
492      TYPE(TFILE), INTENT(INOUT) :: td_file
493
494      ! local variable
495      INTEGER(i4) :: il_attid
496      INTEGER(i4) :: il_nvar
497
498      TYPE(TVAR), DIMENSION(:), ALLOCATABLE  :: tl_var
499
500      ! loop indices
501      INTEGER(i4) :: ji
502      INTEGER(i4) :: ii
503      !----------------------------------------------------------------
504
505      IF( td_file%i_nvar > 0 )THEN
506
507         IF(ASSOCIATED(td_file%t_var))THEN
508            CALL var_clean(td_file%t_var(:))
509            DEALLOCATE(td_file%t_var)
510         ENDIF
511
512         il_nvar=td_file%i_nvar
513         ALLOCATE(tl_var(il_nvar))
514         DO ji = 1, il_nvar
515           ! read variable information
516           tl_var(ji)=iom_cdf__read_var_meta( td_file, ji) 
517         ENDDO
518
519         ! update number of variable used
520         td_file%i_nvar=COUNT(tl_var(:)%l_use)
521
522         ALLOCATE(td_file%t_var(td_file%i_nvar))
523
524         ii=0
525         DO ji = 1, il_nvar
526            IF( tl_var(ji)%l_use )THEN
527               ii=ii+1
528               td_file%t_var(ii)=var_copy(tl_var(ji))
529               SELECT CASE(td_file%t_var(ii)%i_ndim)
530                  CASE(0)
531                     td_file%i_n0d=td_file%i_n0d+1
532                  CASE(1)
533                     td_file%i_n1d=td_file%i_n1d+1
534                     td_file%i_rhd=td_file%i_rhd+1
535                  CASE(2)
536                     td_file%i_n2d=td_file%i_n2d+1
537                     td_file%i_rhd=td_file%i_rhd+1
538                  CASE(3,4)
539                     td_file%i_n3d=td_file%i_n3d+1
540                     td_file%i_rhd=td_file%i_rhd+td_file%t_dim(3)%i_len
541               END SELECT
542
543               ! look for depth id
544               IF( INDEX(TRIM(fct_lower(td_file%t_var(ii)%c_name)),'depth')/=0 )THEN
545                  IF( td_file%i_depthid == 0 )THEN
546                     td_file%i_depthid=ji
547                  ELSE
548                     IF( td_file%i_depthid /= ji )THEN
549                        CALL logger_error("IOM CDF GET FILE VAR: find more"//&
550                           &  " than one depth variable in file "//&
551                           &  TRIM(td_file%c_name) )
552                     ENDIF
553                  ENDIF
554               ENDIF
555
556               ! look for time id
557               IF( INDEX(TRIM(fct_lower(td_file%t_var(ii)%c_name)),'time')/=0 )THEN
558                  IF( td_file%i_timeid == 0 )THEN
559                     td_file%i_timeid=ji
560                  ELSE
561                     IF( td_file%i_timeid /= ji )THEN
562                        CALL logger_warn("IOM CDF GET FILE VAR: find more "//&
563                        &                 "than one time variable in file "//&
564                        &                 TRIM(td_file%c_name)//". see "//&
565                        &                 "dummy.cfg configuration file to"//&
566                        &                 " not used dummy variables.")
567                     ENDIF
568                     il_attid=0
569                     IF( ASSOCIATED(td_file%t_var(ii)%t_att) )THEN
570                        il_attid=att_get_id(td_file%t_var(ii)%t_att(:),'calendar')
571                     ENDIF
572                     IF( il_attid /= 0 )THEN
573                        td_file%i_timeid=ji
574                     ENDIF
575                  ENDIF
576               ENDIF
577
578            ENDIF
579         ENDDO
580
581         CALL var_clean(tl_var(:))
582         DEALLOCATE(tl_var)
583
584      ELSE
585         CALL logger_debug( &
586         &  " IOM CDF GET FILE VAR: there is no variable in file "//&
587         &  TRIM(td_file%c_name))
588      ENDIF
589
590   END SUBROUTINE iom_cdf__get_file_var
591   !-------------------------------------------------------------------
592   !> @brief This subroutine delete coordinate variable from an
593   !> opened netcdf file if present.
594   !
595   !> @author J.Paul
596   !> @date November, 2013 - Initial Version
597   !
598   !> @param[inout] td_file   file structure
599   !-------------------------------------------------------------------
600   SUBROUTINE iom_cdf__del_coord_var(td_file)
601      IMPLICIT NONE
602      ! Argument     
603      TYPE(TFILE), INTENT(INOUT) :: td_file
604
605      ! local variable
606      CHARACTER(LEN=lc) :: cl_name
607      CHARACTER(LEN=lc) :: cl_sname
608
609      ! loop indices
610      INTEGER(i4) :: ji
611      INTEGER(i4) :: jj
612      !----------------------------------------------------------------
613      IF( td_file%i_nvar > 0 )THEN
614         DO ji=td_file%i_nvar,1,-1
615            cl_name=TRIM(td_file%t_var(ji)%c_name)
616            DO jj=1,ip_maxdim
617               IF( td_file%t_dim(jj)%l_use )THEN
618                  cl_sname=fct_upper(td_file%t_dim(jj)%c_sname)
619                  IF( TRIM(cl_name) == TRIM(cl_sname) )THEN
620                     CALL file_del_var(td_file,TRIM(cl_name))
621                     EXIT
622                  ENDIF
623               ENDIF
624            ENDDO
625         ENDDO
626      ELSE
627         CALL logger_debug( &
628         &  " IOM CDF DEL VAR DIM: there is no variable in file "//&
629         &  TRIM(td_file%c_name))
630      ENDIF
631   END SUBROUTINE iom_cdf__del_coord_var
632   !-------------------------------------------------------------------
633   !> @brief This function read one dimension in an opened netcdf file,
634   !> given dimension id.
635   !
636   !> @author J.Paul
637   !> @date November, 2013 - Initial Version
638   !> @date February, 2015 - create unused dimension, when reading dimension
639   !> of length less or equal to zero
640   !
641   !> @param[in] td_file   file structure
642   !> @param[in] id_dimid  dimension id
643   !> @return  dimension structure
644   !-------------------------------------------------------------------
645   TYPE(TDIM) FUNCTION iom_cdf__read_dim_id(td_file, id_dimid)
646      IMPLICIT NONE
647      ! Argument     
648      TYPE(TFILE), INTENT(IN) :: td_file
649      INTEGER(i4), INTENT(IN) :: id_dimid
650
651      ! local variable
652      INTEGER(i4)       :: il_status
653      INTEGER(i4)       :: il_len
654      CHARACTER(LEN=lc) :: cl_name
655      LOGICAL           :: ll_use
656      !----------------------------------------------------------------
657
658      ! check if file opened
659      IF( td_file%i_id == 0 )THEN
660
661         CALL logger_error( &
662         &  " IOM CDF READ DIM: no id associated to file "//TRIM(td_file%c_name))
663
664      ELSE
665
666         CALL logger_trace( &
667         &  " IOM CDF READ DIM: dimension "//TRIM(fct_str(id_dimid))//&
668         &  " in file "//TRIM(td_file%c_name))
669
670         il_status=NF90_INQUIRE_DIMENSION(td_file%i_id, id_dimid, &
671         &                                cl_name, il_len )
672         CALL iom_cdf__check(il_status,"IOM CDF READ DIM: ")
673
674         ll_use=.TRUE.
675         IF( il_len <= 0 )THEN
676            CALL logger_warn( &
677         &  " IOM CDF READ DIM: dimension "//TRIM(fct_str(id_dimid))//&
678         &  " in file "//TRIM(td_file%c_name)//" is less or equel to zero")
679            il_len=1
680            ll_use=.FALSE.
681         ENDIF
682         iom_cdf__read_dim_id=dim_init(cl_name, il_len, ld_use=ll_use)
683
684      ENDIF
685
686      iom_cdf__read_dim_id%i_id=id_dimid
687
688   END FUNCTION iom_cdf__read_dim_id
689   !-------------------------------------------------------------------
690   !> @brief This function read one dimension in an opened netcdf file,
691   !> given dimension name.
692   !
693   !> @author J.Paul
694   !> @date November, 2013 - Initial Version
695   !
696   !> @param[in] td_file   file structure
697   !> @param[in] cd_name   dimension name
698   !> @return  dimension structure
699   !-------------------------------------------------------------------
700   TYPE(TDIM) FUNCTION iom_cdf__read_dim_name(td_file, cd_name)
701      IMPLICIT NONE
702      ! Argument     
703      TYPE(TFILE),      INTENT(IN) :: td_file
704      CHARACTER(LEN=*), INTENT(IN) :: cd_name
705
706      ! local variable
707      INTEGER(i4) :: il_status
708      INTEGER(i4) :: il_dimid
709      !----------------------------------------------------------------
710
711      ! check if file opened
712      IF( td_file%i_id == 0 )THEN
713
714         CALL logger_error( &
715         &  " IOM CDF READ DIM: no id associated to file "//&
716         &  TRIM(td_file%c_name))
717
718      ELSE     
719
720         il_status=NF90_INQ_DIMID( td_file%i_id, TRIM(ADJUSTL(cd_name)), &
721         &                         il_dimid)
722         CALL iom_cdf__check(il_status,"IOM CDF READ DIM: ")
723
724         iom_cdf__read_dim_name=iom_cdf_read_dim(td_file, il_dimid)
725
726      ENDIF
727
728   END FUNCTION iom_cdf__read_dim_name
729   !-------------------------------------------------------------------
730   !> @brief This function read variable or global attribute in an opened
731   !> netcdf file, given attribute name.
732   !
733   !> @author J.Paul
734   !> @date November, 2013 - Initial Version
735   !> @date November 2017
736   !> - check if cl_value is not bug
737   !
738   !> @param[in] td_file   file structure
739   !> @param[in] id_varid  variable id. use NF90_GLOBAL to read global
740   !> attribute in a file
741   !> @param[in] cd_name   attribute name
742   !> @return  attribute structure
743   !-------------------------------------------------------------------
744   TYPE(TATT) FUNCTION iom_cdf__read_att_name(td_file, id_varid, cd_name)
745      IMPLICIT NONE
746      ! Argument     
747      TYPE(TFILE),      INTENT(IN) :: td_file
748      INTEGER(i4),      INTENT(IN) :: id_varid
749      CHARACTER(LEN=*), INTENT(IN) :: cd_name
750
751      ! local variable
752      CHARACTER(LEN=lc) :: cl_name
753
754      INTEGER(i4) :: il_status
755      INTEGER(i4) :: il_attid
756      INTEGER(i4) :: il_type
757      INTEGER(i4) :: il_len
758
759      CHARACTER(LEN=lc) :: cl_value
760     
761      INTEGER(i1), DIMENSION(:), ALLOCATABLE :: bl_value
762      INTEGER(i2), DIMENSION(:), ALLOCATABLE :: sl_value
763      INTEGER(i4), DIMENSION(:), ALLOCATABLE :: il_value
764      REAL(sp)   , DIMENSION(:), ALLOCATABLE :: fl_value
765      REAL(dp)   , DIMENSION(:), ALLOCATABLE :: dl_value
766      !----------------------------------------------------------------
767      ! check if file opened
768      IF( td_file%i_id == 0 )THEN
769
770         CALL logger_error( &
771         &  " IOM CDF READ ATT: no id associated to file "//TRIM(td_file%c_name))
772
773      ELSE     
774
775         cl_name=TRIM(ADJUSTL(cd_name))
776
777         ! inquire attribute
778         IF( id_varid == NF90_GLOBAL )THEN
779
780            CALL logger_trace( &
781            &  " IOM CDF READ ATT: inquire global attribute "//&
782            &  " in file "//TRIM(td_file%c_name))
783
784         ELSE
785
786            CALL logger_trace( &
787            &  " IOM CDF READ ATT: inquire attribute "//&
788            &  " of variable "//TRIM(fct_str(id_varid))//&
789            &  " in file "//TRIM(td_file%c_name))
790
791         ENDIF
792
793         il_status=NF90_INQUIRE_ATTRIBUTE(td_file%i_id, id_varid,  &
794         &                                cl_name,&
795         &                                il_type,&
796         &                                il_len, &
797         &                                il_attid )
798         CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")
799
800         !! get attribute value
801         CALL logger_debug( " IOM CDF READ ATT: get attribute "//&
802            &            TRIM(cl_name)//" in file "//TRIM(td_file%c_name))
803
804         SELECT CASE( il_type )
805
806            CASE(NF90_CHAR)
807               CALL logger_debug( " IOM CDF READ ATT: get NF90_CHAR ")
808
809               ! check string lengths
810               IF( LEN(cl_value) < il_len )THEN
811
812                  CALL logger_warn( &
813                  &  " IOM CDF READ ATT: not enough space to put "//&
814                  &  "attribute "//TRIM(cl_name) )
815
816               ELSE
817
818                  ! Read the attributes
819                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
820                  &                      cl_name, &
821                  &                      cl_value )
822                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")
823
824                  ! check cl_value
825                  IF( LLT(cl_value,'') ) cl_value = ''
826                  iom_cdf__read_att_name=att_init(cl_name, cl_value)
827
828               ENDIF
829         
830            CASE(NF90_BYTE)
831               CALL logger_debug( " IOM CDF READ ATT: get NF90_BYTE ")
832
833               ALLOCATE( bl_value( il_len), &
834               &         stat=il_status)
835               IF(il_status /= 0 )THEN
836
837                  CALL logger_error( "IOM CDF READ ATT: "//&
838                  &  "not enough space to put attribute "//TRIM(cl_name) )
839
840               ELSE
841
842                  ! Read the attributes
843                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
844                  &                      cl_name, &
845                  &                      bl_value(:))
846                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")   
847
848                  iom_cdf__read_att_name=att_init(cl_name, bl_value(:))
849
850               ENDIF
851
852               DEALLOCATE(bl_value)
853
854            CASE(NF90_SHORT)
855               CALL logger_debug( " IOM CDF READ ATT: get NF90_SHORT ")
856
857               ALLOCATE( sl_value( il_len), &
858               &         stat=il_status)
859               IF(il_status /= 0 )THEN
860
861                  CALL logger_error( &
862                  &  " IOM CDF READ ATT: not enough space to put "//&
863                  &  "attribute "//TRIM(cl_name) )
864
865               ELSE
866
867                  ! Read the attributes
868                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
869                  &                      cl_name, &
870                  &                      sl_value(:))
871                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")   
872
873                  iom_cdf__read_att_name=att_init(cl_name, sl_value(:))
874
875               ENDIF
876
877               DEALLOCATE(sl_value)
878
879            CASE(NF90_INT)
880               CALL logger_debug( " IOM CDF READ ATT: get NF90_INT ")
881
882               ALLOCATE( il_value( il_len), &
883               &         stat=il_status)
884               IF(il_status /= 0 )THEN
885
886                  CALL logger_error( &
887                  &  " IOM CDF READ ATT: not enough space to put "//&
888                  &  "attribute "//TRIM(cl_name) )
889
890               ELSE
891
892                  ! Read the attributes
893                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
894                  &                      cl_name, &
895                  &                      il_value(:))
896                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")   
897
898                  iom_cdf__read_att_name=att_init(cl_name, il_value(:))
899               ENDIF
900
901               DEALLOCATE(il_value)
902
903            CASE(NF90_FLOAT)
904               CALL logger_debug( " IOM CDF READ ATT: get NF90_FLOAT ")
905
906               ALLOCATE( fl_value( il_len), &
907               &         stat=il_status)
908               IF(il_status /= 0 )THEN
909
910                  CALL logger_error( &
911                  &  " IOM CDF READ ATT: not enough space to put "//&
912                  &  "attribute "//TRIM(cl_name) )
913
914               ELSE
915
916                  ! Read the attributes
917                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
918                  &                      cl_name, &
919                  &                      fl_value(:))
920                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")   
921
922                  iom_cdf__read_att_name=att_init(cl_name, fl_value(:))
923
924               ENDIF
925
926               DEALLOCATE(fl_value)
927
928            CASE(NF90_DOUBLE)
929               CALL logger_debug( " IOM CDF READ ATT: get NF90_DOUBLE ")
930
931               ALLOCATE( dl_value( il_len), &
932               &         stat=il_status)
933               IF(il_status /= 0 )THEN
934
935                  CALL logger_error( &
936                  &  " IOM CDF READ ATT: not enough space to put "//&
937                  &  "attribute "//TRIM(cl_name) )
938
939               ELSE
940
941                  ! Read the attributes
942                  il_status=NF90_GET_ATT(td_file%i_id, id_varid, &
943                  &                      cl_name, &
944                  &                      dl_value(:))
945                  CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")   
946
947                  iom_cdf__read_att_name=att_init(cl_name, dl_value(:))
948
949               ENDIF
950
951               DEALLOCATE(dl_value)
952
953         END SELECT
954
955         iom_cdf__read_att_name%i_id=il_attid
956
957      ENDIF
958
959   END FUNCTION iom_cdf__read_att_name
960   !-------------------------------------------------------------------
961   !> @brief This function read variable or global attribute in an opened
962   !> netcdf file, given attribute id.
963   !
964   !> @author J.Paul
965   !> @date November, 2013 - Initial Version
966   !
967   !> @param[in] td_file   file structure
968   !> @param[in] id_varid  variable id. use NF90_GLOBAL to read global
969   !> attribute in a file
970   !> @param[in] id_attid  attribute id
971   !> @return  attribute structure
972   !-------------------------------------------------------------------
973   TYPE(TATT) FUNCTION iom_cdf__read_att_id(td_file, id_varid, id_attid)
974      IMPLICIT NONE
975      ! Argument     
976      TYPE(TFILE), INTENT(IN) :: td_file
977      INTEGER(i4), INTENT(IN) :: id_varid
978      INTEGER(i4), INTENT(IN) :: id_attid
979
980      ! local variable
981      INTEGER(i4)       :: il_status
982      CHARACTER(LEN=lc) :: cl_name
983      !----------------------------------------------------------------
984      ! check if file opened
985      IF( td_file%i_id == 0 )THEN
986
987         CALL logger_error( &
988         &  "IOM CDF READ ATT: no id associated to file "//TRIM(td_file%c_name))
989
990      ELSE
991
992         ! get attribute name
993         il_status=NF90_INQ_ATTNAME(td_file%i_id, id_varid, id_attid, cl_name)
994         CALL iom_cdf__check(il_status,"IOM CDF READ ATT: ")
995
996         ! read attribute
997         iom_cdf__read_att_id=iom_cdf__read_att_name(td_file, id_varid, cl_name)
998
999      ENDIF
1000
1001   END FUNCTION iom_cdf__read_att_id
1002   !-------------------------------------------------------------------
1003   !> @brief This function read variable value in an opened
1004   !> netcdf file, given variable id.
1005   !> @details
1006   !> Optionaly, start indices and number of indices selected along each dimension
1007   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1008   !
1009   !> @author J.Paul
1010   !> @date November, 2013 - Initial Version
1011   !
1012   !> @param[in] td_file   file structure
1013   !> @param[in] id_varid  variable id
1014   !> @param[in] id_start  index in the variable from which the data values
1015   !> will be read
1016   !> @param[in] id_count  number of indices selected along each dimension
1017   !> @return  variable structure
1018   !-------------------------------------------------------------------
1019   TYPE(TVAR) FUNCTION iom_cdf__read_var_id(td_file, id_varid,&
1020   &                                        id_start, id_count)
1021      IMPLICIT NONE
1022      ! Argument     
1023      TYPE(TFILE),               INTENT(IN) :: td_file
1024      INTEGER(i4),               INTENT(IN) :: id_varid
1025      INTEGER(i4), DIMENSION(:), INTENT(IN), OPTIONAL :: id_start
1026      INTEGER(i4), DIMENSION(:), INTENT(IN), OPTIONAL :: id_count
1027
1028      ! local variable
1029      INTEGER(i4), DIMENSION(1) :: il_ind
1030      !----------------------------------------------------------------
1031      ! check if file opened
1032      IF( td_file%i_id == 0 )THEN
1033
1034         CALL logger_error( &
1035         &  " IOM CDF READ VAR: no id associated to file "//TRIM(td_file%c_name))
1036
1037      ELSE
1038
1039         ! look for variable index
1040         il_ind(:)=MINLOC(td_file%t_var(:)%i_id,mask=(td_file%t_var(:)%i_id==id_varid))
1041         IF( il_ind(1) /= 0 )THEN
1042
1043            iom_cdf__read_var_id=var_copy(td_file%t_var(il_ind(1)))
1044
1045            !!! read variable value
1046            CALL iom_cdf__read_var_value(td_file, iom_cdf__read_var_id, &
1047            &                            id_start, id_count)
1048
1049         ELSE
1050            CALL logger_error( &
1051            &  " IOM CDF READ VAR: there is no variable with id "//&
1052            &  TRIM(fct_str(id_varid))//" in file "//TRIM(td_file%c_name))
1053         ENDIF
1054
1055      ENDIF
1056   END FUNCTION iom_cdf__read_var_id
1057   !-------------------------------------------------------------------
1058   !> @brief This function read variable value in an opened
1059   !> netcdf file, given variable name or standard name.
1060   !> @details
1061   !> Optionaly, start indices and number of indices selected along each dimension
1062   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1063   !>
1064   !> look first for variable name. If it doesn't
1065   !> exist in file, look for variable standard name.<br/>
1066   !
1067   !> @author J.Paul
1068   !> @date November, 2013 - Initial Version
1069   !
1070   !> @param[in] td_file   file structure
1071   !> @param[in] cd_name   variable name or standard name.
1072   !> @param[in] id_start  index in the variable from which the data values will be read
1073   !> @param[in] id_count  number of indices selected along each dimension
1074   !> @return  variable structure
1075   !-------------------------------------------------------------------
1076   TYPE(TVAR) FUNCTION iom_cdf__read_var_name(td_file, cd_name,  &
1077   &                                          id_start, id_count )
1078      IMPLICIT NONE
1079      ! Argument     
1080      TYPE(TFILE)     ,                INTENT(IN) :: td_file
1081      CHARACTER(LEN=*),                INTENT(IN), OPTIONAL :: cd_name
1082      INTEGER(i4)     , DIMENSION(:),  INTENT(IN), OPTIONAL :: id_start
1083      INTEGER(i4)     , DIMENSION(:),  INTENT(IN), OPTIONAL :: id_count
1084
1085      ! local variable
1086      INTEGER(i4)       :: il_varid
1087      !----------------------------------------------------------------
1088      ! check if file opened
1089      IF( td_file%i_id == 0 )THEN
1090
1091         CALL logger_error( &
1092         &  " IOM CDF READ VAR: no id associated to file "//TRIM(td_file%c_name))
1093
1094      ELSE
1095
1096         IF( .NOT. PRESENT(cd_name) )THEN
1097
1098            CALL logger_error( &
1099            &  " IOM CDF READ VAR: you must specify a variable to read "//&
1100            &  " in file "//TRIM(td_file%c_name))
1101
1102         ELSE
1103
1104            il_varid=var_get_index(td_file%t_var(:), cd_name)
1105            IF( il_varid /= 0 )THEN
1106
1107               iom_cdf__read_var_name=var_copy(td_file%t_var(il_varid))
1108
1109               !!! read variable value
1110               CALL iom_cdf__read_var_value( td_file, &
1111               &                             iom_cdf__read_var_name, &
1112               &                             id_start, id_count)
1113
1114            ELSE
1115
1116               CALL logger_error( &
1117               &  " IOM CDF READ VAR: there is no variable with "//&
1118               &  " name or standard name "//TRIM(cd_name)//&
1119               &  " in file "//TRIM(td_file%c_name) )
1120            ENDIF
1121
1122         ENDIF
1123
1124      ENDIF
1125     
1126   END FUNCTION iom_cdf__read_var_name
1127   !-------------------------------------------------------------------
1128   !> @brief This subroutine fill all variable value from an opened
1129   !> netcdf file.
1130   !> @details
1131   !> Optionaly, start indices and number of indices selected along each dimension
1132   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1133   !
1134   !> @author J.Paul
1135   !> @date November, 2013 - Initial Version
1136   !
1137   !> @param[inout] td_file   file structure
1138   !> @param[in] id_start     index in the variable from which the data values
1139   !> will be read
1140   !> @param[in] id_count     number of indices selected along each dimension
1141   !-------------------------------------------------------------------
1142   SUBROUTINE iom_cdf__fill_var_all(td_file, id_start, id_count)
1143      IMPLICIT NONE
1144      ! Argument     
1145      TYPE(TFILE),               INTENT(INOUT) :: td_file
1146      INTEGER(i4), DIMENSION(:), INTENT(IN   ),  OPTIONAL :: id_start
1147      INTEGER(i4), DIMENSION(:), INTENT(IN   ),  OPTIONAL :: id_count
1148
1149      ! local variable
1150
1151      ! loop indices
1152      INTEGER(i4) :: ji
1153      !----------------------------------------------------------------
1154      ! check if file opened
1155      IF( td_file%i_id == 0 )THEN
1156
1157         CALL logger_error( &
1158         &  " IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name))
1159
1160      ELSE
1161
1162         DO ji=1,td_file%i_nvar
1163            CALL iom_cdf_fill_var(td_file, td_file%t_var(ji)%i_id, &
1164            &                     id_start, id_count)
1165         ENDDO
1166
1167      ENDIF
1168   END SUBROUTINE iom_cdf__fill_var_all
1169   !-------------------------------------------------------------------
1170   !> @brief This subroutine fill variable value in an opened
1171   !> netcdf file, given variable id.
1172   !> @details
1173   !> Optionaly, start indices and number of indices selected along each dimension
1174   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1175   !
1176   !> @author J.Paul
1177   !> @date November, 2013 - Initial Version
1178   !
1179   !> @param[inout] td_file   file structure
1180   !> @param[in] id_varid     variable id
1181   !> @param[in] id_start     index in the variable from which the data values
1182   !> will be read
1183   !> @param[in] id_count     number of indices selected along each dimension
1184   !-------------------------------------------------------------------
1185   SUBROUTINE iom_cdf__fill_var_id(td_file, id_varid, id_start, id_count)
1186      IMPLICIT NONE
1187      ! Argument     
1188      TYPE(TFILE),               INTENT(INOUT) :: td_file
1189      INTEGER(i4),               INTENT(IN)    :: id_varid
1190      INTEGER(i4), DIMENSION(:), INTENT(IN),  OPTIONAL :: id_start
1191      INTEGER(i4), DIMENSION(:), INTENT(IN),  OPTIONAL :: id_count
1192
1193      ! local variable
1194      INTEGER(i4), DIMENSION(1) :: il_varid
1195
1196      ! loop indices
1197      INTEGER(i4) :: ji
1198      !----------------------------------------------------------------
1199      ! check if file opened
1200      IF( td_file%i_id == 0 )THEN
1201
1202         CALL logger_error( &
1203         &  "IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name))
1204
1205      ELSE
1206
1207         ! look for variable id
1208         il_varid(:)=MINLOC( td_file%t_var(:)%i_id, &
1209         &                 mask=(td_file%t_var(:)%i_id==id_varid))
1210         IF( il_varid(1) /= 0 )THEN
1211
1212            !!! read variable value
1213            CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_varid(1)), &
1214            &                            id_start, id_count)
1215
1216            DO ji=1,td_file%i_nvar
1217               CALL logger_debug(" IOM CDF FILL VAR: var id "//&
1218               &     TRIM(td_file%t_var(ji)%c_name)//" "//&
1219               &     TRIM(fct_str(td_file%t_var(ji)%i_id)) )
1220            ENDDO
1221         ELSE
1222            CALL logger_error( &
1223            &  " IOM CDF FILL VAR: there is no variable with id "//&
1224            &  TRIM(fct_str(id_varid))//" in file "//TRIM(td_file%c_name))
1225         ENDIF
1226
1227      ENDIF
1228   END SUBROUTINE iom_cdf__fill_var_id
1229   !-------------------------------------------------------------------
1230   !> @brief This subroutine fill variable value in an opened
1231   !> netcdf file, given variable name or standard name.
1232   !> @details
1233   !> Optionaly, start indices and number of indices selected along each dimension
1234   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1235   !>
1236   !> look first for variable name. If it doesn't
1237   !> exist in file, look for variable standard name.<br/>
1238   !
1239   !> @author J.Paul
1240   !> @date November, 2013 - Initial Version
1241   !
1242   !> @param[inout] td_file   file structure
1243   !> @param[in] cd_name      variable name or standard name
1244   !> @param[in] id_start     index in the variable from which the data values will be read
1245   !> @param[in] id_count     number of indices selected along each dimension
1246   !-------------------------------------------------------------------
1247   SUBROUTINE iom_cdf__fill_var_name(td_file, cd_name, id_start, id_count )
1248      IMPLICIT NONE
1249      ! Argument     
1250      TYPE(TFILE),                   INTENT(INOUT) :: td_file
1251      CHARACTER(LEN=*),              INTENT(IN)    :: cd_name
1252      INTEGER(i4),     DIMENSION(:), INTENT(IN),  OPTIONAL :: id_start
1253      INTEGER(i4),     DIMENSION(:), INTENT(IN),  OPTIONAL :: id_count
1254
1255      ! local variable
1256      INTEGER(i4)       :: il_varid
1257      !----------------------------------------------------------------
1258      ! check if file opened
1259      IF( td_file%i_id == 0 )THEN
1260
1261         CALL logger_error( &
1262         &  "IOM CDF FILL VAR: no id associated to file "//TRIM(td_file%c_name))
1263
1264      ELSE
1265
1266            il_varid=var_get_index(td_file%t_var(:), cd_name)
1267            IF( il_varid /= 0 )THEN
1268
1269               !!! read variable value
1270               CALL iom_cdf__read_var_value(td_file, td_file%t_var(il_varid), &
1271               &                            id_start, id_count)
1272
1273            ELSE
1274
1275               CALL logger_error( &
1276               &  "IOM CDF FILL VAR: there is no variable with "//&
1277               &  "name or standard name"//TRIM(cd_name)//&
1278               &  " in file "//TRIM(td_file%c_name))
1279            ENDIF
1280
1281      ENDIF
1282     
1283   END SUBROUTINE iom_cdf__fill_var_name
1284   !-------------------------------------------------------------------
1285   !> @brief This function read metadata of a variable in an opened
1286   !> netcdf file.
1287   !
1288   !> @note variable value are not read
1289   !
1290   !> @author J.Paul
1291   !> @date November, 2013 - Initial Version
1292   !> @date September, 2014
1293   !> - force to use FillValue=1.e20 if no FillValue for coordinate variable.
1294   !> @date September, 2015
1295   !> - manage useless (dummy) attribute
1296   !
1297   !> @param[in] td_file   file structure
1298   !> @param[in] id_varid  variable id
1299   !> @return  variable structure
1300   !-------------------------------------------------------------------
1301   TYPE(TVAR) FUNCTION iom_cdf__read_var_meta(td_file, id_varid)
1302      IMPLICIT NONE
1303      ! Argument     
1304      TYPE(TFILE), INTENT(IN) :: td_file
1305      INTEGER(i4), INTENT(IN) :: id_varid
1306
1307      ! local variable
1308      CHARACTER(LEN=lc)                                       :: cl_name
1309
1310      INTEGER(i4)                                             :: il_status
1311      INTEGER(i4)                                             :: il_type
1312      INTEGER(i4)                                             :: il_ndim
1313      INTEGER(i4)                                             :: il_natt
1314      INTEGER(i4)                                             :: il_attid
1315      INTEGER(i4), DIMENSION(NF90_MAX_VAR_DIMS)               :: il_dimid
1316
1317      TYPE(TDIM) , DIMENSION(ip_maxdim)                       :: tl_dim
1318      TYPE(TATT)                                              :: tl_fill
1319      TYPE(TATT) , DIMENSION(:)                 , ALLOCATABLE :: tl_att
1320      TYPE(TATT) , DIMENSION(:)                 , ALLOCATABLE :: tl_tmp
1321
1322      ! loop indices
1323      INTEGER(i4) :: ji
1324      !----------------------------------------------------------------
1325      ! check if file opened
1326      IF( td_file%i_id == 0 )THEN
1327
1328         CALL logger_error( &
1329         &  " IOM CDF READ VAR META: no id associated to file "//&
1330         &   TRIM(td_file%c_name))
1331
1332      ELSE
1333
1334         ! inquire variable
1335         CALL logger_debug( &
1336         &  " IOM CDF READ VAR META: inquire variable "//&
1337         &  TRIM(fct_str(id_varid))//&
1338         &  " in file "//TRIM(td_file%c_name))
1339         
1340         il_dimid(:)=0
1341
1342         il_status=NF90_INQUIRE_VARIABLE( td_file%i_id, id_varid,        &
1343         &                                cl_name,    &
1344         &                                il_type,    &
1345         &                                il_ndim,    &
1346         &                                il_dimid(:),&
1347         &                                il_natt )
1348         CALL iom_cdf__check(il_status,"IOM CDF READ VAR META: ")
1349
1350         !!! fill variable dimension structure
1351         tl_dim(:)=iom_cdf__read_var_dim( td_file, il_ndim, cl_name, il_dimid(:) )
1352
1353         IF( il_natt /= 0 )THEN
1354            ALLOCATE( tl_att(il_natt) )
1355            !!! fill variable attribute structure
1356            tl_att(:)=iom_cdf__read_var_att(td_file, id_varid, il_natt)
1357
1358            !! look for _FillValue. if none add one
1359            il_attid=att_get_id(tl_att(:),'_FillValue')
1360            IF( il_attid == 0 )THEN
1361               CALL logger_info("IOM CDF READ VAR META: no _FillValue for variable "//&
1362               &  TRIM(cl_name)//" in file "//TRIM(td_file%c_name) )
1363
1364               il_attid=att_get_id(tl_att(:),'missing_value')
1365               IF( il_attid /= 0 )THEN
1366                  ! create attribute _FillValue
1367                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//&
1368                  &                "missing_value for variable "//TRIM(cl_name) )
1369                  tl_fill=att_init('_FillValue',tl_att(il_attid)%d_value(:), &
1370                  &                 id_type=tl_att(il_attid)%i_type)
1371               ELSE
1372                  ! create attribute _FillValue
1373                  SELECT CASE(TRIM(fct_lower(cl_name)))
1374                     CASE DEFAULT
1375                        CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//&
1376                        &                "zero for variable "//TRIM(cl_name) )
1377                        tl_fill=att_init('_FillValue',0.)
1378                     CASE('nav_lon','nav_lat', 'nav_lev', &
1379                        &  'glamt','glamu','glamv','glamf', &
1380                        &  'gphit','gphiu','gphiv','gphif')
1381                        CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//&
1382                        &                "dummy fillValue (1.e20) for variable "//TRIM(cl_name) )
1383                        tl_fill=att_init('_FillValue',1.e20)
1384                  END SELECT
1385               ENDIF
1386
1387               ALLOCATE( tl_tmp(il_natt) )
1388               ! save read attribut
1389               tl_tmp(:)=att_copy(tl_att(:))
1390               ! change number of attribute in array
1391               CALL att_clean(tl_att(:))
1392               DEALLOCATE( tl_att )
1393               ALLOCATE( tl_att(il_natt+1) )
1394               ! copy read attribut
1395               tl_att(1:il_natt)=att_copy(tl_tmp(:))
1396               ! clean
1397               CALL att_clean(tl_tmp(:))
1398               DEALLOCATE( tl_tmp )
1399
1400               ! create attribute _FillValue
1401               tl_att(il_natt+1)=att_copy(tl_fill)
1402
1403            ENDIF
1404
1405         ELSE
1406            ALLOCATE(tl_att(il_natt+1) )
1407            ! create attribute _FillValue
1408            SELECT CASE(TRIM(fct_lower(cl_name)))
1409               CASE DEFAULT
1410                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//&
1411                  &                "zero for variable "//TRIM(cl_name) )
1412                  tl_fill=att_init('_FillValue',0.)
1413               CASE('nav_lon','nav_lat', &
1414                  &  'glamt','glamu','glamv','glamf', &
1415                  &  'gphit','gphiu','gphiv','gphif')
1416                  CALL logger_info("IOM CDF READ VAR META: assume _FillValue is equal to "//&
1417                  &                "dummy fillValue (1.e20) for variable "//TRIM(cl_name) )
1418                  tl_fill=att_init('_FillValue',1.e20)
1419            END SELECT           
1420            ! create attribute _FillValue
1421            tl_att(il_natt+1)=att_copy(tl_fill)
1422         ENDIF
1423
1424         !! initialize variable
1425         iom_cdf__read_var_meta=var_init( cl_name, il_type, tl_dim(:), &
1426         &                                tl_att(:), id_id=id_varid )
1427
1428         !! look for dummy attribute
1429         DO ji=il_natt,1,-1
1430            IF( att_is_dummy(tl_att(ji)) )THEN
1431               CALL var_del_att(iom_cdf__read_var_meta, tl_att(ji))
1432            ENDIF
1433         ENDDO
1434
1435         !! check if variable is dummy
1436         IF( var_is_dummy(iom_cdf__read_var_meta) )THEN
1437            iom_cdf__read_var_meta%l_use=.FALSE.
1438         ENDIF
1439
1440         !! check if all dimensions are allowed
1441         DO ji=1,il_ndim
1442            IF( ALL(td_file%t_dim(:)%i_id /= il_dimid(ji)) )THEN
1443               iom_cdf__read_var_meta%l_use=.FALSE.
1444            ENDIF
1445         ENDDO
1446
1447         ! clean
1448         CALL dim_clean(tl_dim(:))
1449         CALL att_clean(tl_fill)
1450         CALL att_clean(tl_att(:))
1451         DEALLOCATE( tl_att )
1452
1453      ENDIF
1454
1455   END FUNCTION iom_cdf__read_var_meta
1456   !-------------------------------------------------------------------
1457   !> @brief This subroutine read variable dimension
1458   !> in an opened netcdf file.
1459   !>
1460   !> @details
1461   !> the number of dimension can't exceed 4,
1462   !> and should be 'x', 'y', 'z', 't' (whatever their order).<br/>
1463   !> If the number of dimension read is less than 4, the array of dimension
1464   !> strucure is filled with unused dimension.<br/>
1465   !> So the array of dimension structure of a variable is always compose of 4
1466   !> dimension (use or not).
1467   !>
1468   !> @warn dummy dimension are not used.
1469   !>
1470   !> @author J.Paul
1471   !> @date November, 2013 - Initial Version
1472   !> @date July, 2015
1473   !> - Bug fix: use order to disorder table (see dim_init)
1474   !> @date September, 2015
1475   !> - check dummy dimension
1476   !>
1477   !> @param[in] td_file   file structure
1478   !> @param[in] id_ndim   number of dimension
1479   !> @param[in] cd_name   variable name
1480   !> @param[in] id_dimid  array of dimension id
1481   !> @return array dimension structure
1482   !-------------------------------------------------------------------
1483   FUNCTION iom_cdf__read_var_dim(td_file, id_ndim, cd_name, id_dimid)
1484      IMPLICIT NONE
1485      ! Argument     
1486      TYPE(TFILE),               INTENT(IN) :: td_file
1487      INTEGER(i4),               INTENT(IN) :: id_ndim
1488      CHARACTER(LEN=*)         , INTENT(IN) :: cd_name
1489      INTEGER(i4), DIMENSION(:), INTENT(IN) :: id_dimid
1490
1491      ! function
1492      TYPE(TDIM), DIMENSION(ip_maxdim) :: iom_cdf__read_var_dim
1493
1494      ! local variable
1495      INTEGER(i4), DIMENSION(ip_maxdim) :: il_xyzt2
1496
1497      TYPE(TDIM) , DIMENSION(ip_maxdim) :: tl_dim
1498
1499      ! loop indices
1500      INTEGER(i4) :: ji
1501      INTEGER(i4) :: ii
1502      !----------------------------------------------------------------
1503
1504      IF( id_ndim == 0 )THEN
1505
1506         tl_dim(:)%l_use=.FALSE.
1507
1508         ! reorder dimension to ('x','y','z','t')
1509         CALL dim_reorder(tl_dim(:))
1510
1511         iom_cdf__read_var_dim(:)=dim_copy(tl_dim(:))
1512
1513         ! clean
1514         CALL dim_clean(tl_dim(:))
1515
1516      ELSE IF( id_ndim > 0 )THEN
1517
1518         ii=1
1519         DO ji = 1, id_ndim
1520
1521            ! check if dimension to be used, is allowed
1522            IF( ANY(td_file%t_dim(:)%i_id == id_dimid(ji)) )THEN
1523               IF( ii > ip_maxdim )THEN
1524                  CALL logger_error(" IOM CDF READ VAR DIM: "//&
1525                  &  "too much dimensions for variable "//&
1526                  &  TRIM(cd_name)//". check dummy configuration file.")
1527               ENDIF
1528
1529               CALL logger_debug( " IOM CDF READ VAR DIM: get variable "//&
1530                  &  "dimension "//TRIM(fct_str(ji)) )
1531
1532               il_xyzt2(ii)=td_file%t_dim(id_dimid(ji))%i_xyzt2
1533
1534               ! read dimension information
1535               tl_dim(ii) = dim_init( td_file%t_dim(il_xyzt2(ii))%c_name, &
1536               &                      td_file%t_dim(il_xyzt2(ii))%i_len )
1537
1538               ii=ii+1
1539            ELSE
1540               CALL logger_debug( " IOM CDF READ VAR DIM: dummy variable "//&
1541               &  "dimension "//TRIM(fct_str(ji))//" not used." )
1542            ENDIF
1543         ENDDO
1544
1545         ! reorder dimension to ('x','y','z','t')
1546         CALL dim_reorder(tl_dim(:))
1547 
1548         iom_cdf__read_var_dim(:)=dim_copy(tl_dim(:))
1549
1550         ! clean
1551         CALL dim_clean(tl_dim(:))
1552
1553      ENDIF
1554
1555   END FUNCTION iom_cdf__read_var_dim
1556   !-------------------------------------------------------------------
1557   !> @brief This subroutine read variable attributes
1558   !> in an opened netcdf file.
1559   !
1560   !> @author J.Paul
1561   !> @date November, 2013 - Initial Version
1562   !
1563   !> @param[in] td_file   file structure
1564   !> @param[in] id_varid  variable id
1565   !> @param[in] id_natt   number of attributes
1566   !> @return array of attribute structure
1567   !-------------------------------------------------------------------
1568   FUNCTION iom_cdf__read_var_att(td_file, id_varid, id_natt)
1569      IMPLICIT NONE
1570      ! Argument     
1571      TYPE(TFILE), INTENT(IN) :: td_file
1572      INTEGER(i4), INTENT(IN) :: id_varid
1573      INTEGER(i4), INTENT(IN) :: id_natt     
1574
1575      ! function
1576      TYPE(TATT), DIMENSION(id_natt) :: iom_cdf__read_var_att
1577
1578      ! local variable
1579
1580      ! loop indices
1581      INTEGER(i4) :: ji
1582      !----------------------------------------------------------------
1583
1584      IF( id_natt > 0 )THEN
1585     
1586         ! read attributes
1587         DO ji = 1, id_natt
1588            CALL logger_trace( " IOM CDF READ VAR ATT: get attribute "//&
1589            &               TRIM(fct_str(ji)) )
1590
1591            iom_cdf__read_var_att(ji)=iom_cdf_read_att(td_file, id_varid, ji)
1592
1593         ENDDO
1594
1595      ELSE
1596
1597         CALL logger_debug( " IOM CDF READ VAR ATT: no attribute for variable " )
1598
1599      ENDIF
1600
1601   END FUNCTION iom_cdf__read_var_att
1602   !-------------------------------------------------------------------
1603   !> @brief This subroutine read variable value
1604   !> in an opened netcdf file.
1605   !> @details
1606   !> Optionaly, start indices and number of indices selected along each dimension
1607   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
1608   !
1609   !> @author J.Paul
1610   !> @date November, 2013 - Initial Version
1611   !> @date June, 2015
1612   !> - use scale factor and offset, as soon as read variable value
1613   !
1614   !> @param[in] td_file   file structure
1615   !> @param[inout] td_var variable structure
1616   !> @param[in] id_start  index in the variable from which the data values will be read
1617   !> @param[in] id_count  number of indices selected along each dimension
1618   !> @return variable structure completed
1619   !-------------------------------------------------------------------
1620   SUBROUTINE iom_cdf__read_var_value(td_file, td_var, &
1621   &                                  id_start, id_count )
1622      IMPLICIT NONE
1623      ! Argument     
1624      TYPE(TFILE),               INTENT(IN)    :: td_file
1625      TYPE(TVAR) ,               INTENT(INOUT) :: td_var
1626      INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_start
1627      INTEGER(i4), DIMENSION(:), INTENT(IN),   OPTIONAL :: id_count
1628
1629      ! local variable
1630      INTEGER(i4)                                    :: il_status
1631      INTEGER(i4)                                    :: il_tmp1
1632      INTEGER(i4)                                    :: il_tmp2
1633      INTEGER(i4)                                    :: il_varid
1634      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_start
1635      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_count
1636      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_start_ord
1637      INTEGER(i4), DIMENSION(ip_maxdim)              :: il_count_ord
1638
1639      REAL(dp)   , DIMENSION(:,:,:,:)  , ALLOCATABLE :: dl_value
1640      REAL(dp)   , DIMENSION(:,:,:,:)  , ALLOCATABLE :: dl_tmp
1641
1642      ! loop indices
1643      INTEGER(i4) :: ji
1644      !----------------------------------------------------------------
1645
1646      ! check if variable in file structure
1647      il_varid=var_get_id(td_file%t_var(:),TRIM(td_var%c_name))
1648      IF( il_varid /= 0 )THEN
1649
1650         ! check id_count and id_start optionals parameters...
1651         IF( (       PRESENT(id_start)  .AND. (.NOT. PRESENT(id_count))) .OR. &
1652             ((.NOT. PRESENT(id_start)) .AND.        PRESENT(id_count) ) )THEN
1653            CALL logger_warn( "IOM CDF READ VAR VALUE: id_start and id_count"//&
1654               & " should be both specify")
1655         ENDIF
1656         IF( PRESENT(id_start).AND.PRESENT(id_count) )THEN
1657
1658            IF( SIZE(id_start(:)) /= ip_maxdim .OR. &
1659            &   SIZE(id_count(:)) /= ip_maxdim )THEN
1660               CALL logger_error("IOM CDF READ VAR: dimension of array start"//&
1661                  &  " or count are invalid to read variable "//&
1662                  &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name) )
1663            ENDIF
1664
1665            ! change dimension order from ('x','y','z','t')
1666            il_start(:)=dim_reorder_xyzt2(td_var%t_dim, id_start(:))
1667            il_count(:)=dim_reorder_xyzt2(td_var%t_dim, id_count(:))
1668
1669            ! keep ordered array ('x','y','z','t')
1670            il_start_ord(:)=id_start(:)
1671            il_count_ord(:)=id_count(:)
1672
1673         ELSE
1674
1675            ! change dimension order from ('x','y','z','t')
1676            il_start(:)=(/1,1,1,1/)
1677            il_count(:)=dim_reorder_xyzt2(td_var%t_dim(:),td_var%t_dim(:)%i_len)
1678
1679            ! keep ordered array ('x','y','z','t')
1680            il_start_ord(:)=(/1,1,1,1/)
1681            il_count_ord(:)=td_var%t_dim(:)%i_len
1682
1683         ENDIF
1684
1685         ! check dimension
1686         IF( .NOT. ALL(il_start_ord(:)>=(/1,1,1,1/)) )THEN
1687
1688            CALL logger_error( "IOM CDF READ VAR VALUE: start indices should"//&
1689            &  " be greater than or equal to 1")
1690
1691         ENDIF
1692
1693         IF(.NOT.ALL(il_start_ord(:)+il_count_ord(:)-1 <= &
1694            &  (/td_var%t_dim( 1 )%i_len,&
1695            &    td_var%t_dim( 2 )%i_len,&
1696            &    td_var%t_dim( 3 )%i_len,&
1697            &    td_var%t_dim( 4 )%i_len &
1698            &                                            /)) )THEN
1699
1700            DO ji = 1, ip_maxdim
1701               il_tmp1=il_start_ord(ji)+il_count_ord(ji)-1
1702               il_tmp2=td_var%t_dim(ji)%i_len
1703               CALL logger_debug( "IOM CDF READ VAR VALUE: start + count -1:"//&
1704               &  TRIM(fct_str(il_tmp1))//" variable dimension"//&
1705               &  TRIM(fct_str(il_tmp2)))
1706            ENDDO
1707            CALL logger_error( "IOM CDF READ VAR VALUE: start + count exceed "//&
1708            &  "variable dimension for "//TRIM(td_var%c_name) )
1709
1710         ELSE
1711
1712            ! Allocate space to hold variable value (disorder)
1713            ALLOCATE(dl_value( il_count(1), &
1714               &               il_count(2), &
1715               &               il_count(3), &
1716               &               il_count(4)),&
1717               &               stat=il_status)
1718            IF( il_status /= 0 )THEN
1719
1720              CALL logger_error( &
1721               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//&
1722               &  TRIM(td_var%c_name))
1723
1724            ENDIF
1725
1726            ! read values
1727            CALL logger_debug( &
1728            &  "IOM CDF READ VAR VALUE: get variable "//TRIM(td_var%c_name)//&
1729            &  " in file "//TRIM(td_file%c_name))
1730
1731            il_status = NF90_GET_VAR( td_file%i_id, il_varid,           &
1732            &                                       dl_value(:,:,:,:),  &
1733            &                                       start = il_start(:),&
1734            &                                       count = il_count(:) )
1735            CALL iom_cdf__check(il_status,"IOM CDF READ VAR VALUE: ")
1736
1737            ! Allocate space to hold variable value in structure
1738            IF( ASSOCIATED(td_var%d_value) )THEN
1739               DEALLOCATE(td_var%d_value)   
1740            ENDIF
1741 
1742            ! new dimension length
1743            td_var%t_dim(:)%i_len=il_count_ord(:)
1744
1745!>   dummy patch for pgf95
1746            ALLOCATE( dl_tmp( td_var%t_dim(1)%i_len, &
1747            &                 td_var%t_dim(2)%i_len, &
1748            &                 td_var%t_dim(3)%i_len, &
1749            &                 td_var%t_dim(4)%i_len),&
1750            &        stat=il_status)
1751            IF(il_status /= 0 )THEN
1752
1753               CALL logger_error( &
1754               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//&
1755               &  TRIM(td_var%c_name)//&
1756               &  " in variable structure")
1757            ENDIF
1758            dl_tmp(:,:,:,:)=td_var%d_fill
1759
1760            ! reshape values to be ordered as ('x','y','z','t')
1761            dl_tmp(:,:,:,:)=dim_reshape_2xyzt(td_var%t_dim(:), &
1762            &                                 dl_value(:,:,:,:))
1763
1764            DEALLOCATE(dl_value)
1765
1766            ALLOCATE(td_var%d_value( td_var%t_dim(1)%i_len, &
1767            &                        td_var%t_dim(2)%i_len, &
1768            &                        td_var%t_dim(3)%i_len, &
1769            &                        td_var%t_dim(4)%i_len),&
1770            &        stat=il_status)
1771            IF(il_status /= 0 )THEN
1772
1773               CALL logger_error( &
1774               &  "IOM CDF READ VAR VALUE: not enough space to put variable "//&
1775               &  TRIM(td_var%c_name)//&
1776               &  " in variable structure")
1777
1778            ENDIF
1779!            ! FillValue by default
1780!            td_var%d_value(:,:,:,:)=td_var%d_fill
1781!
1782!            ! reshape values to be ordered as ('x','y','z','t')
1783!            td_var%d_value(:,:,:,:)=dim_reshape_2xyzt(td_var%t_dim(:), &
1784!            &                                         dl_value(:,:,:,:))
1785!
1786!            DEALLOCATE(dl_value)
1787
1788            td_var%d_value(:,:,:,:)=dl_tmp(:,:,:,:)
1789            DEALLOCATE(dl_tmp)
1790!<   dummy patch for pgf95
1791
1792            ! force to change _FillValue to avoid mistake
1793            ! with dummy zero _FillValue
1794            IF( td_var%d_fill == 0._dp )THEN
1795               CALL var_chg_FillValue(td_var)
1796            ENDIF
1797
1798            ! use scale factor and offset
1799            WHERE( td_var%d_value(:,:,:,:) /= td_var%d_fill )
1800               td_var%d_value(:,:,:,:) = &
1801               &  td_var%d_value(:,:,:,:)*td_var%d_scf + td_var%d_ofs
1802            END WHERE
1803
1804         ENDIF
1805      ELSE
1806         CALL logger_error( &
1807         &  "IOM CDF READ VAR VALUE: no variable "//TRIM(td_var%c_name)//&
1808         &  " in file structure "//TRIM(td_file%c_name))
1809      ENDIF
1810
1811   END SUBROUTINE iom_cdf__read_var_value
1812   !-------------------------------------------------------------------
1813   !> @brief This subroutine write file structure in an opened netcdf file.
1814   !>
1815   !> @details
1816   !> optionally, you could specify dimension order (default 'xyzt')
1817   !>
1818   !> @author J.Paul
1819   !> @date November, 2013 - Initial Version
1820   !> @date July, 2015
1821   !> - add dimension order option
1822   !
1823   !> @param[inout] td_file   file structure
1824   !-------------------------------------------------------------------
1825   SUBROUTINE iom_cdf_write_file(td_file, cd_dimorder)
1826      IMPLICIT NONE
1827      ! Argument     
1828      TYPE(TFILE)     , INTENT(INOUT) :: td_file
1829      CHARACTER(LEN=*), INTENT(IN   ), OPTIONAL :: cd_dimorder
1830
1831      ! local variable
1832      INTEGER(i4), DIMENSION(:), ALLOCATABLE :: il_value
1833
1834      CHARACTER(LEN=lc)                      :: cl_dimorder
1835
1836      TYPE(TVAR)                             :: tl_var
1837
1838      TYPE(TDIM), DIMENSION(ip_maxdim)       :: tl_dim
1839
1840      ! loop indices
1841      INTEGER(i4) :: ji
1842      INTEGER(i4) :: jj
1843      INTEGER(i4) :: jvar
1844      !----------------------------------------------------------------
1845
1846      cl_dimorder='xyzt'
1847      IF( PRESENT(cd_dimorder) ) cl_dimorder=TRIM(cd_dimorder)
1848
1849      ! check if file opened
1850      IF( td_file%i_id == 0 )THEN
1851
1852         CALL logger_error( &
1853         &  " IOM CDF WRITE FILE: no id associated to file "//TRIM(td_file%c_name))
1854
1855      ELSE
1856         IF( td_file%l_wrt )THEN
1857
1858            ! remove dummy variable
1859            CALL file_del_var(td_file,'no0d')
1860            CALL file_del_var(td_file,'no1d')
1861            CALL file_del_var(td_file,'no2d')
1862            CALL file_del_var(td_file,'no3d')
1863
1864            DO ji = 1, td_file%i_nvar
1865               CALL var_check_dim( td_file%t_var(ji) )
1866            ENDDO
1867
1868            ! save usefull dimension
1869            IF( ASSOCIATED(td_file%t_var) )THEN
1870               tl_dim(:)=var_max_dim(td_file%t_var(:))
1871
1872               DO ji=1,ip_maxdim
1873                  IF( tl_dim(ji)%l_use ) CALL file_move_dim(td_file, tl_dim(ji))
1874               ENDDO
1875               ! clean
1876               CALL dim_clean(tl_dim(:))
1877            ENDIF
1878
1879            ! change dimension order
1880            IF( TRIM(cl_dimorder) /= 'xyzt' )THEN
1881               CALL dim_reorder(td_file%t_dim(:),TRIM(cl_dimorder))
1882               DO jvar=1,td_file%i_nvar
1883                  CALL logger_debug("VAR REORDER: "//TRIM(td_file%t_var(jvar)%c_name))
1884                  CALL var_reorder(td_file%t_var(jvar),TRIM(cl_dimorder))
1885               ENDDO
1886            ENDIF
1887
1888            ! write dimension in file
1889            DO ji = 1, ip_maxdim
1890               IF( td_file%t_dim(ji)%l_use )THEN
1891                  CALL iom_cdf__write_dim(td_file, td_file%t_dim(ji))
1892
1893                  ! write dimension variable
1894                  ALLOCATE(il_value(td_file%t_dim(ji)%i_len))
1895                  il_value(:)=(/(jj,jj=1,td_file%t_dim(ji)%i_len)/)
1896
1897                  tl_var=var_init( fct_upper(td_file%t_dim(ji)%c_sname), &
1898                  &                il_value(:),                          &
1899                  &                td_dim=td_file%t_dim(ji) )
1900
1901                  DEALLOCATE(il_value)
1902
1903                  ! do not use FillValue for dimension variable
1904                  CALL var_del_att(tl_var, "_FillValue")
1905                   
1906                  CALL iom_cdf__write_var(td_file,tl_var)
1907                  ! clean
1908                  CALL var_clean(tl_var)
1909
1910               ENDIF
1911            ENDDO
1912
1913            ! write global attibute in file
1914            DO ji = 1, td_file%i_natt
1915               CALL iom_cdf__write_att(td_file, NF90_GLOBAL, td_file%t_att(ji))
1916            ENDDO
1917
1918            ! write variable in file
1919            DO ji = 1, td_file%i_nvar
1920               CALL iom_cdf__write_var(td_file, td_file%t_var(ji)) 
1921            ENDDO
1922
1923         ELSE
1924
1925            CALL logger_error( &
1926            &  "IOM CDF WRITE FILE: try to write in file "//TRIM(td_file%c_name)//&
1927            &  ", not opened in write mode")
1928
1929         ENDIF
1930      ENDIF
1931
1932   END SUBROUTINE iom_cdf_write_file
1933   !-------------------------------------------------------------------
1934   !> @brief This subroutine write one dimension in an opened netcdf
1935   !> file in write mode.
1936   !
1937   !> @author J.Paul
1938   !> @date November, 2013 - Initial Version
1939   !
1940   !> @param[inout] td_file   file structure
1941   !> @param[inout] td_dim    dimension structure
1942   !-------------------------------------------------------------------
1943   SUBROUTINE iom_cdf__write_dim(td_file, td_dim)
1944      IMPLICIT NONE
1945      ! Argument     
1946      TYPE(TFILE), INTENT(INOUT) :: td_file
1947      TYPE(TDIM),  INTENT(INOUT) :: td_dim
1948
1949      ! local variable
1950      INTEGER(i4) :: il_status
1951      !----------------------------------------------------------------
1952
1953      IF( .NOT. td_file%l_def )THEN
1954
1955         CALL logger_trace( &
1956         &  " IOM CDF WRITE FILE DIM: Enter define mode, file "//TRIM(td_file%c_name))
1957
1958         ! Enter define mode
1959         il_status=NF90_REDEF(td_file%i_id)
1960         CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ")
1961
1962         td_file%l_def=.TRUE.
1963
1964      ENDIF
1965
1966      IF( td_dim%l_use )THEN
1967         IF( td_dim%l_uld )THEN
1968            ! write unlimited dimension
1969            CALL logger_trace( &
1970            &  "IOM CDF WRITE FILE DIM: write unlimited dimension "//&
1971            &  TRIM(td_dim%c_name)//" in file "//TRIM(td_file%c_name))
1972
1973            il_status=NF90_DEF_DIM(td_file%i_id, fct_upper(td_dim%c_sname), &
1974            &                      NF90_UNLIMITED, td_dim%i_id)
1975            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ")
1976
1977         ELSE
1978            ! write not unlimited dimension
1979            CALL logger_debug( &
1980            &  "IOM CDF WRITE FILE DIM: write dimension "//TRIM(td_dim%c_name)//&
1981            &  " in file "//TRIM(td_file%c_name))
1982           
1983            il_status=NF90_DEF_DIM(td_file%i_id, fct_upper(td_dim%c_sname), &
1984            &                      td_dim%i_len, td_dim%i_id)
1985            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE DIM: ")
1986
1987         ENDIF
1988      ENDIF
1989
1990   END SUBROUTINE iom_cdf__write_dim
1991   !-------------------------------------------------------------------
1992   !> @brief This subroutine write a variable attribute in
1993   !> an opened netcdf file.
1994   !
1995   !> @author J.Paul
1996   !> @date November, 2013 - Initial Version
1997   !
1998   !> @param[inout] td_file   file structure
1999   !> @param[in] id_varid     variable id. use NF90_GLOBAL to write
2000   !> global attribute in a file
2001   !> @param[in] td_att       attribute structure
2002   !-------------------------------------------------------------------
2003   SUBROUTINE iom_cdf__write_att(td_file, id_varid, td_att)
2004      IMPLICIT NONE
2005      ! Argument     
2006      TYPE(TFILE), INTENT(INOUT) :: td_file
2007      INTEGER(i4), INTENT(IN)    :: id_varid
2008      TYPE(TATT),  INTENT(IN)    :: td_att
2009
2010      ! local variable
2011      INTEGER(i4) :: il_status
2012      !----------------------------------------------------------------
2013
2014      IF( .NOT. td_file%l_def )THEN
2015
2016         CALL logger_trace( &
2017         &  "IOM CDF WRITE FILE ATT: Enter define mode, file "//TRIM(td_file%c_name))
2018
2019         ! Enter define mode
2020         il_status=NF90_REDEF(td_file%i_id)
2021         CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ")
2022
2023         td_file%l_def=.TRUE.
2024
2025      ENDIF
2026
2027      !! put attribute value
2028      CALL logger_trace( &
2029      &  "IOM CDF WRITE FILE ATT: write attribute "//TRIM(td_att%c_name)//&
2030      &  " of variable "//TRIM(fct_str(id_varid))//&
2031      &  " in file "//TRIM(td_file%c_name))
2032      SELECT CASE( td_att%i_type )
2033
2034         CASE(NF90_CHAR)
2035            ! put the attribute
2036            il_status = NF90_PUT_ATT(td_file%i_id, id_varid, &
2037            &  td_att%c_name, td_att%c_value )
2038            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ")
2039
2040         CASE(NF90_BYTE, NF90_SHORT, NF90_INT, NF90_FLOAT, NF90_DOUBLE)
2041            ! put the attribute
2042            il_status = NF90_PUT_ATT(td_file%i_id, id_varid, &
2043            &  td_att%c_name, td_att%d_value )
2044            CALL iom_cdf__check(il_status,"IOM CDF WRITE FILE ATT: ")
2045
2046      END SELECT
2047
2048   END SUBROUTINE iom_cdf__write_att
2049   !-------------------------------------------------------------------
2050   !> @brief This subroutine write a variable in an opened netcdf file.
2051   !
2052   !> @author J.Paul
2053   !> @date November, 2013 - Initial Version
2054   !> @date September, 2015
2055   !> - do not force to use zero as FillValue for any meshmask variable
2056   !
2057   !> @param[inout] td_file   file structure
2058   !> @param[inout] td_var    variable structure
2059   !-------------------------------------------------------------------
2060   SUBROUTINE iom_cdf__write_var(td_file, td_var)
2061      IMPLICIT NONE
2062      ! Argument     
2063      TYPE(TFILE), INTENT(INOUT) :: td_file
2064      TYPE(TVAR),  INTENT(INOUT) :: td_var
2065
2066      ! local variable
2067      INTEGER(i4) :: il_status
2068      LOGICAL     :: ll_chg
2069      ! loop indices
2070      INTEGER(i4) :: ji
2071      !----------------------------------------------------------------
2072
2073      IF( .NOT. td_file%l_def )THEN
2074
2075         CALL logger_trace( &
2076         &  " IOM CDF WRITE VAR: Enter define mode, file "//&
2077         &  TRIM(td_file%c_name))
2078
2079         ! Enter define mode
2080         il_status=NF90_REDEF(td_file%i_id)
2081         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR: ")
2082
2083         td_file%l_def=.TRUE.
2084
2085      ENDIF
2086 
2087      ! check if file and variable dimension conform
2088      IF( file_check_var_dim(td_file, td_var) )THEN
2089
2090         ll_chg=.TRUE.
2091         DO ji=1,ip_maxdim
2092            IF( TRIM(fct_lower(cp_dimorder(ji:ji))) == &
2093            &   TRIM(fct_lower(td_var%c_name)) )THEN
2094               ll_chg=.FALSE.
2095               CALL logger_trace(TRIM(fct_lower(td_var%c_name))//' is var dimension')
2096               EXIT
2097            ENDIF
2098         ENDDO
2099         ! ugly patch until NEMO do not force to use 0. as FillValue
2100         IF( ll_chg )THEN
2101            ! not a dimension variable
2102            ! change FillValue
2103            SELECT CASE( TRIM(fct_lower(td_var%c_name)) )
2104               CASE DEFAULT
2105                  CALL var_chg_FillValue(td_var,0._dp)
2106               CASE('nav_lon','nav_lat', &
2107                  & 'glamt','glamu','glamv','glamf', &
2108                  & 'gphit','gphiu','gphiv','gphif', &
2109                  & 'e1t','e1u','e1v','e1f',         &
2110                  & 'e2t','e2u','e2v','e2f','ff',    &
2111                  & 'gcost','gcosu','gcosv','gcosf', &
2112                  & 'gsint','gsinu','gsinv','gsinf', &
2113                  & 'mbathy','misf','isf_draft','isfdraft',     &
2114                  & 'hbatt','hbatu','hbatv','hbatf', &
2115                  & 'gsigt','gsigu','gsigv','gsigf', &
2116                  & 'e3t_0','e3u_0','e3v_0','e3w_0', &
2117                  & 'e3f_0','gdepw_1d','gdept_1d',   &
2118                  & 'e3tp','e3wp','gdepw_0','rx1',   &
2119                  & 'gdept_0','gdepu','gdepv',       &
2120                  & 'hdept','hdepw','e3w_1d','e3t_1d',&
2121                  & 'tmask','umask','vmask','fmask'  )
2122                  ! do not change for coordinates and meshmask variables
2123            END SELECT
2124         ENDIF
2125
2126         ! define variable in file
2127         td_var%i_id=iom_cdf__write_var_def(td_file, td_var) 
2128
2129         IF( td_file%l_def )THEN
2130
2131            CALL logger_trace( &
2132            &  " IOM CDF WRITE VAR: Leave define mode, file "//&
2133            &  TRIM(td_file%c_name))
2134
2135            ! Leave define mode
2136            il_status=NF90_ENDDEF(td_file%i_id)
2137            CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR: ")
2138
2139            td_file%l_def=.FALSE.
2140
2141         ENDIF
2142
2143         IF( ASSOCIATED(td_var%d_value) )THEN
2144            ! write variable value in file
2145            CALL iom_cdf__write_var_value(td_file, td_var)
2146         ENDIF
2147
2148      ENDIF
2149
2150   END SUBROUTINE iom_cdf__write_var
2151   !-------------------------------------------------------------------
2152   !> @brief This function define variable in an opened netcdf file.
2153   !
2154   !> @author J.Paul
2155   !> @date November, 2013 - Initial Version
2156   !
2157   !> @param[in] td_file   file structure
2158   !> @param[in] td_var    variable structure
2159   !> @return  variable id
2160   !-------------------------------------------------------------------
2161   INTEGER(i4) FUNCTION iom_cdf__write_var_def(td_file, td_var)
2162      IMPLICIT NONE
2163      ! Argument     
2164      TYPE(TFILE), INTENT(IN) :: td_file
2165      TYPE(TVAR),  INTENT(IN) :: td_var
2166
2167      ! local variable
2168      INTEGER(i4)                       :: il_status
2169      INTEGER(i4)                       :: il_ind
2170      INTEGER(i4), DIMENSION(ip_maxdim) :: il_dimid
2171
2172      TYPE(TVAR)                        :: tl_var
2173
2174      ! loop indices
2175      INTEGER(i4) :: ji
2176      INTEGER(i4) :: jj
2177      !----------------------------------------------------------------
2178
2179      ! copy structure
2180      tl_var=var_copy(td_var)
2181
2182      ! forced to use float type
2183      IF( tl_var%d_unf /= 1. .AND. tl_var%i_type==NF90_SHORT )THEN
2184         tl_var%i_type=NF90_FLOAT
2185      ENDIF
2186
2187      IF( ALL( .NOT. tl_var%t_dim(:)%l_use ) )THEN
2188         CALL logger_debug( &
2189         &  "IOM CDF WRITE VAR DEF scalar: define variable "//&
2190         &  TRIM(tl_var%c_name)//" in file "//TRIM(td_file%c_name))
2191         ! scalar value
2192         il_status = NF90_DEF_VAR(td_file%i_id, TRIM(tl_var%c_name), &
2193         &                        tl_var%i_type, varid=iom_cdf__write_var_def) 
2194         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ")
2195      ELSE
2196
2197         ! check which dimension use
2198         jj=0
2199         il_dimid(:)=0
2200         ! reorder dimension, so unused dimension won't be written
2201         DO ji = 1,  ip_maxdim
2202            IF( tl_var%t_dim(ji)%l_use )THEN
2203               jj=jj+1
2204               il_dimid(jj)=dim_get_id(td_file%t_dim(:),tl_var%t_dim(ji)%c_name)
2205            ENDIF
2206         ENDDO
2207
2208         CALL logger_debug( &
2209         &  "IOM CDF WRITE VAR DEF: define dimension to be used for variable "//&
2210         &  TRIM(tl_var%c_name)//" in file "//TRIM(td_file%c_name))
2211
2212         DO ji=1,jj
2213            CALL logger_debug("IOM CDF WRITE VAR DEF: dimid "//TRIM(fct_str(il_dimid(ji))) )
2214         ENDDO
2215
2216         il_status = NF90_DEF_VAR(td_file%i_id, TRIM(tl_var%c_name),     &
2217         &                        tl_var%i_type,                         &
2218         &                        il_dimid(1:jj),                        &
2219         &                        varid=iom_cdf__write_var_def           )
2220         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ")
2221      ENDIF
2222      CALL logger_debug("IOM CDF WRITE VAR DEF: type = "//TRIM(fct_str(tl_var%i_type)))
2223
2224      ! remove unuseful attribute
2225      il_ind=att_get_index( tl_var%t_att(:), "ew_overlap" )
2226      IF( il_ind /= 0 )THEN
2227         IF( tl_var%t_att(il_ind)%d_value(1) == -1 )THEN
2228            CALL var_del_att(tl_var, tl_var%t_att(il_ind))
2229         ENDIF
2230      ENDIF
2231
2232      DO ji = 1, tl_var%i_natt
2233         CALL logger_debug( &
2234         &  " IOM CDF WRITE VAR DEF: put attribute "//TRIM(tl_var%t_att(ji)%c_name)//&
2235         &  " for variable "//TRIM(tl_var%c_name)//&
2236         &  " in file "//TRIM(td_file%c_name) )
2237
2238         ! forced FillValue to have same type than variable
2239         IF( TRIM(tl_var%t_att(ji)%c_name) == '_FillValue' )THEN
2240            tl_var%t_att(ji)%i_type=tl_var%i_type
2241         ENDIF
2242
2243         SELECT CASE(tl_var%t_att(ji)%i_type)
2244            CASE(NF90_CHAR)
2245               IF( TRIM(tl_var%t_att(ji)%c_value) /= '' )THEN
2246                  il_status = NF90_PUT_ATT(td_file%i_id, iom_cdf__write_var_def, &
2247                  &                        TRIM(tl_var%t_att(ji)%c_name),        &
2248                  &                        TRIM(tl_var%t_att(ji)%c_value)        )
2249               ENDIF
2250            CASE(NF90_BYTE)
2251               il_status = NF90_PUT_ATT(td_file%i_id,                   &
2252               &                        iom_cdf__write_var_def,         &
2253               &                        TRIM(tl_var%t_att(ji)%c_name),  &
2254               &                        INT(tl_var%t_att(ji)%d_value(:),i1))
2255            CASE(NF90_SHORT)
2256               il_status = NF90_PUT_ATT(td_file%i_id,                   &
2257               &                        iom_cdf__write_var_def,         &
2258               &                        TRIM(tl_var%t_att(ji)%c_name),  &
2259               &                        INT(tl_var%t_att(ji)%d_value(:),i2))
2260            CASE(NF90_INT)
2261               il_status = NF90_PUT_ATT(td_file%i_id,                   &
2262               &                        iom_cdf__write_var_def,         &
2263               &                        TRIM(tl_var%t_att(ji)%c_name),  &
2264               &                        INT(tl_var%t_att(ji)%d_value(:),i4))
2265            CASE(NF90_FLOAT)
2266               il_status = NF90_PUT_ATT(td_file%i_id,                   &
2267               &                        iom_cdf__write_var_def,         &
2268               &                        TRIM(tl_var%t_att(ji)%c_name),  &
2269               &                        REAL(tl_var%t_att(ji)%d_value(:),sp))
2270            CASE(NF90_DOUBLE)
2271               il_status = NF90_PUT_ATT(td_file%i_id,                   &
2272               &                        iom_cdf__write_var_def,         &
2273               &                        TRIM(tl_var%t_att(ji)%c_name),  &
2274               &                        REAL(tl_var%t_att(ji)%d_value(:),dp))
2275         END SELECT
2276         CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR DEF: ")
2277
2278      ENDDO
2279
2280   END FUNCTION iom_cdf__write_var_def
2281   !-------------------------------------------------------------------
2282   !> @brief This subroutine put variable value in an opened netcdf file.
2283   !
2284   !> @details
2285   !> The variable is written in the type define in variable structure.
2286   !> Only dimension used are printed, and fillValue in array are
2287   !> replaced by default fill values defined in module netcdf for each type.
2288   !
2289   !> @author J.Paul
2290   !> @date November, 2013 - Initial Version
2291   !> @date June, 2015
2292   !> - reuse scale factor and offset, before writing variable
2293   !
2294   !> @param[in] td_file   file structure
2295   !> @param[in] td_var    variable structure
2296   !-------------------------------------------------------------------
2297   SUBROUTINE iom_cdf__write_var_value(td_file, td_var)
2298      IMPLICIT NONE
2299      ! Argument     
2300      TYPE(TFILE), INTENT(IN) :: td_file
2301      TYPE(TVAR),  INTENT(IN) :: td_var
2302
2303      ! local variable
2304      INTEGER(i4)                       :: il_status
2305      INTEGER(i4), DIMENSION(ip_maxdim) :: il_order
2306      INTEGER(i4), DIMENSION(ip_maxdim) :: il_shape
2307      REAL(dp),    DIMENSION(:,:,:,:), ALLOCATABLE :: dl_value
2308
2309      ! loop indices
2310      INTEGER(i4) :: ji, jj
2311      !----------------------------------------------------------------
2312
2313      ! check which dimension use
2314      CALL logger_trace( &
2315      &  "IOM CDF WRITE VAR VALUE: get dimension to be used for variable "//&
2316      &  TRIM(td_var%c_name)//" in file "//TRIM(td_file%c_name))
2317   
2318      ! use scale factor and offset
2319      WHERE( td_var%d_value(:,:,:,:) /= td_var%d_fill )
2320         td_var%d_value(:,:,:,:) = &
2321         &  (td_var%d_value(:,:,:,:)-td_var%d_ofs)/td_var%d_scf
2322      END WHERE
2323
2324      jj=0
2325      DO ji = 1, ip_maxdim
2326         IF( td_var%t_dim(ji)%l_use )THEN
2327            jj=jj+1
2328            il_order(jj)=ji
2329            il_shape(jj)=td_var%t_dim(ji)%i_len
2330         ENDIF
2331      ENDDO
2332      ! dimension not use
2333      DO ji = 1, ip_maxdim
2334         IF( .NOT. td_var%t_dim(ji)%l_use )THEN
2335            jj=jj+1
2336            il_order(jj)=ji
2337            il_shape(jj)=td_var%t_dim(ji)%i_len
2338         ENDIF
2339      ENDDO
2340
2341      ALLOCATE( dl_value( il_shape(1),il_shape(2),il_shape(3),il_shape(4) ) )
2342
2343      ! reshape array, so unused dimension won't be written
2344      dl_value(:,:,:,:)=RESHAPE(source=td_var%d_value(:,:,:,:),&
2345      &                         SHAPE = il_shape(:), &
2346      &                         ORDER = il_order(:))
2347
2348      ! put value
2349      CALL logger_debug( &
2350      &  "IOM CDF WRITE VAR VALUE: put "//TRIM(td_var%c_name)//" value "//&
2351      &  "in file "//TRIM(td_file%c_name))
2352
2353      il_status = NF90_PUT_VAR( td_file%i_id, td_var%i_id, dl_value(:,:,:,:))
2354      CALL iom_cdf__check(il_status,"IOM CDF WRITE VAR VALUE ("//&
2355         &  TRIM(td_var%c_name)//") :" )
2356
2357      DEALLOCATE( dl_value )
2358
2359   END SUBROUTINE iom_cdf__write_var_value
2360END MODULE iom_cdf
Note: See TracBrowser for help on using the repository browser.