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 branches/2016/dev_r6999_CONFIGMAN_1/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/2016/dev_r6999_CONFIGMAN_1/NEMOGCM/TOOLS/SIREN/src/iom_cdf.f90 @ 7233

Last change on this file since 7233 was 7233, checked in by jpaul, 7 years ago

see ticket #1781

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