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/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/TOOLS/SIREN/src/iom_cdf.f90 @ 5985

Last change on this file since 5985 was 5985, checked in by timgraham, 8 years ago

Reinstate keywords before upgrading to head of trunk

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