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.f90 in utils/tools/SIREN/src – NEMO

source: utils/tools/SIREN/src/iom.f90 @ 12080

Last change on this file since 12080 was 12080, checked in by jpaul, 4 years ago

update nemo trunk

File size: 26.9 KB
Line 
1!----------------------------------------------------------------------
2! NEMO system team, System and Interface for oceanic RElocable Nesting
3!----------------------------------------------------------------------
4!
5! DESCRIPTION:
6!> @brief Input/Output manager :  Library to read input files
7!>
8!> @details
9!>    to open file:<br/>
10!> @code
11!>    CALL iom_open(td_file)
12!> @endcode
13!>       - td_file is file structure
14!>
15!>    to create file:<br/>
16!> @code
17!>    CALL iom_create(td_file)
18!> @endcode
19!>       - td_file is file structure
20!>
21!>    to write in file:<br/>
22!> @code
23!>    CALL  iom_write_file(td_file)
24!> @endcode
25!>
26!>    to close file:<br/>
27!> @code
28!>    CALL iom_close(tl_file)
29!> @endcode
30!>
31!>    to read one dimension in file:<br/>
32!> @code
33!>    tl_dim = iom_read_dim(tl_file, id_dimid)
34!> @endcode
35!>    or<br/>
36!> @code
37!>    tl_dim = iom_read_dim(tl_file, cd_name)
38!> @endcode
39!>       - id_dimid is dimension id
40!>       - cd_name is dimension name
41!>
42!>    to read variable or global attribute in file:<br/>
43!> @code
44!>    tl_att = iom_read_att(tl_file, id_varid, id_attid)
45!> @endcode
46!>    or
47!> @code
48!>    tl_att = iom_read_att(tl_file, id_varid, cd_attname)
49!> @endcode
50!>    or
51!> @code
52!>    tl_att = iom_read_att(tl_file, cd_varname, id_attid)
53!> @endcode
54!>    or
55!> @code
56!>    tl_att = iom_read_att(tl_file, cd_varname, cd_attname)
57!> @endcode
58!>       - id_varid is variable id
59!>       - id_attid is attribute id
60!>       - cd_attname is attribute name
61!>       - cd_varname is variable name or standard name
62!>   
63!>    to read one variable in file:<br/>
64!> @code
65!>    tl_var = iom_read_var(td_file, id_varid, [id_start, id_count])
66!> @endcode
67!>    or
68!> @code
69!>    tl_var = iom_read_var(td_file, cd_name, [id_start, [id_count,]])
70!> @endcode
71!>       - id_varid is variabale id
72!>       - cd_name is variabale name or standard name.
73!>       - id_start is a integer(4) 1D array of index from which the data
74!>          values will be read [optional]
75!>       - id_count is a integer(4) 1D array of the number of indices selected
76!>          along each dimension [optional]
77!>
78!> @author
79!> J.Paul
80!>
81!> @date November, 2013 - Initial Version
82!> @date August, 2017
83!> - permit to write header and variable independantly
84!>
85!> @todo
86!> - see lbc_lnk
87!> - see goup netcdf4
88!>
89!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
90!----------------------------------------------------------------------
91MODULE iom
92
93   USE netcdf                          ! nf90 library
94   USE global                          ! global parameter
95   USE kind                            ! F90 kind parameter
96   USE fct                             ! basic useful function
97   USE logger                          ! log file manager
98   USE dim                             ! dimension manager
99   USE att                             ! attribute manager
100   USE var                             ! variable manager
101   USE file                            ! file manager
102   USE iom_cdf                         ! netcdf I/O manager
103   USE iom_rstdimg                     ! restart dimg I/O manager
104
105   IMPLICIT NONE
106   ! NOTE_avoid_public_variables_if_possible
107
108   ! function and subroutine
109   PUBLIC :: iom_open        !< open or create file, fill file structure
110   PUBLIC :: iom_create      !< create file, fill file structure
111   PUBLIC :: iom_close       !< close file
112   PUBLIC :: iom_read_dim    !< read one dimension in an opened file
113   PUBLIC :: iom_read_att    !< read one attribute in an opened file
114   PUBLIC :: iom_read_var    !< read one variable  in an opened file   
115   PUBLIC :: iom_write_file  !< write file structure contents in an opened file
116   PUBLIC :: iom_write_header!< write header in an opened file
117   PUBLIC :: iom_write_var   !< write variable an opened file
118
119                                          ! read variable or global attribute in an opened file
120   PRIVATE :: iom__read_att_varname_id   ! given variable name or standard name and attribute id.
121   PRIVATE :: iom__read_att_varid_id     ! given variable id and attribute id.
122   PRIVATE :: iom__read_att_varname_name ! given variable name or standard name, and attribute name.
123   PRIVATE :: iom__read_att_varid_name   ! given variable id and attribute name.
124
125   PRIVATE :: iom__read_dim_id            ! read one dimension in an opened file, given dimension id.
126   PRIVATE :: iom__read_dim_name          ! read one dimension in an opened netcdf file, given dimension name.
127   PRIVATE :: iom__read_var_id            ! read variable value in an opened file, given variable id.
128   PRIVATE :: iom__read_var_name          ! read variable value in an opened file, given variable name or standard name.
129
130   INTERFACE iom_read_var
131      MODULE PROCEDURE iom__read_var_id
132      MODULE PROCEDURE iom__read_var_name
133   END INTERFACE iom_read_var
134
135   INTERFACE iom_read_dim
136      MODULE PROCEDURE iom__read_dim_id
137      MODULE PROCEDURE iom__read_dim_name
138   END INTERFACE iom_read_dim
139
140   INTERFACE iom_read_att    !< read variable or global attribute in an opened file
141      MODULE PROCEDURE iom__read_att_varname_id   !< given variable name or standard name and attribute id.
142      MODULE PROCEDURE iom__read_att_varid_id     !< given variable id and attribute id.
143      MODULE PROCEDURE iom__read_att_varname_name !< given variable name or standard name, and attribute name.
144      MODULE PROCEDURE iom__read_att_varid_name   !< given variable id and attribute name.
145   END INTERFACE iom_read_att
146
147CONTAINS
148   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
149   SUBROUTINE iom_open(td_file)
150   !-------------------------------------------------------------------
151   !> @brief This function open a file in read or write mode
152   !> @details
153   !> If try to open a file in write mode that did not exist, create it.<br/>
154   !>
155   !> If file exist, get information about:
156   !> - the number of variables
157   !> - the number of dimensions
158   !> - the number of global attributes
159   !> - the ID of the unlimited dimension
160   !> - the file format
161   !> and finally read dimensions.
162   !>
163   !> @author J.Paul
164   !> @date November, 2013 - Initial Version
165   !>
166   !> @param[inout] td_file file structure
167   !-------------------------------------------------------------------
168
169      IMPLICIT NONE
170
171      ! Argument     
172      TYPE(TFILE), INTENT(INOUT)  :: td_file
173      !----------------------------------------------------------------
174
175      ! add suffix to file name
176      td_file%c_name = file_add_suffix( TRIM(td_file%c_name), &
177      &                                 TRIM(td_file%c_type)  )
178      ! check type
179      SELECT CASE(TRIM(ADJUSTL(fct_lower(td_file%c_type))))
180
181         CASE('cdf')
182            CALL iom_cdf_open(td_file)
183         !CASE('cdf4')
184         CASE('dimg')
185            CALL iom_rstdimg_open(td_file)
186         CASE DEFAULT
187            CALL logger_error("IOM OPEN: unknow type : "//TRIM(td_file%c_name))
188
189      END SELECT
190
191   END SUBROUTINE iom_open
192   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
193   SUBROUTINE iom_create(td_file)
194   !-------------------------------------------------------------------
195   !> @brief This subroutine create a file.
196   !>
197   !> @author J.Paul
198   !> @date November, 2013 - Initial Version
199   !>
200   !> @param[inout] td_file file structure
201   !-------------------------------------------------------------------
202
203      IMPLICIT NONE
204
205      ! Argument     
206      TYPE(TFILE), INTENT(INOUT)  :: td_file
207
208      ! local variable
209      LOGICAL     :: ll_exist
210      !----------------------------------------------------------------
211
212      INQUIRE(FILE=TRIM(td_file%c_name), EXIST=ll_exist )
213      IF( ll_exist )THEN
214         CALL logger_fatal("IOM CREATE: can not create file "//&
215         &  TRIM(td_file%c_name)//". file exist already.")
216      ENDIF
217
218      ! forced to open in write mode
219      td_file%l_wrt=.TRUE.
220      ! check type
221      SELECT CASE(TRIM(td_file%c_type))
222         CASE('cdf')
223            CALL iom_cdf_open(td_file)
224         CASE('dimg')
225            CALL iom_rstdimg_open(td_file)
226         CASE DEFAULT
227            CALL logger_error( "IOM CREATE: can't create file "//&
228            &               TRIM(td_file%c_name)//": type unknown " )
229      END SELECT
230
231   END SUBROUTINE iom_create
232   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
233   SUBROUTINE iom_close(td_file)
234   !-------------------------------------------------------------------
235   !> @brief This subroutine close file
236   !>
237   !> @author J.Paul
238   !> @date November, 2013 - Initial Version
239   !>
240   !> @param[inout] td_file file structure
241   !-------------------------------------------------------------------
242
243      IMPLICIT NONE
244
245      ! Argument     
246      TYPE(TFILE), INTENT(INOUT) :: td_file
247      !----------------------------------------------------------------
248
249      ! open file
250      SELECT CASE(TRIM(td_file%c_type))
251         CASE('cdf')
252            CALL iom_cdf_close(td_file)
253         CASE('dimg')
254            CALL iom_rstdimg_close(td_file)
255         CASE DEFAULT
256            CALL logger_debug( "IOM CLOSE: type "//TRIM(td_file%c_type))
257            CALL logger_error( "IOM CLOSE: can't close file "//&
258            &               TRIM(td_file%c_name)//": type unknown " )
259      END SELECT
260
261   END SUBROUTINE iom_close
262   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
263   FUNCTION iom__read_att_varname_id(td_file, cd_varname, id_attid) &
264         & RESULT (tf_att)
265   !-------------------------------------------------------------------
266   !> @brief This function read attribute (of variable or global) in an opened
267   !> file, given variable name or standard name and attribute id.
268   !> @details
269   !>  - to get global attribute use 'GLOBAL' as variable name.
270   !>
271   !> @author J.Paul
272   !> @date November, 2013 - Initial Version
273   !>
274   !> @param[in] td_file      file structure
275   !> @param[in] cd_varname   variable name. use 'GLOBAL' to read global
276   !> attribute in a file
277   !> @param[in] id_attid     attribute id
278   !> @return  attribute structure
279   !-------------------------------------------------------------------
280
281      IMPLICIT NONE
282
283      ! Argument
284      TYPE(TFILE),       INTENT(IN) :: td_file
285      CHARACTER(LEN=lc), INTENT(IN) :: cd_varname
286      INTEGER(i4),       INTENT(IN) :: id_attid
287
288      ! function
289      TYPE(TATT)                    :: tf_att
290
291      ! local variable
292      INTEGER(i4) :: il_varid
293      !----------------------------------------------------------------
294
295      ! get variable id
296      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
297         il_varid=NF90_GLOBAL
298      ELSE
299         il_varid=var_get_id(td_file%t_var(:), cd_varname)
300      ENDIF
301
302      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
303         ! open file
304         SELECT CASE(TRIM(td_file%c_type))
305            CASE('cdf')
306               tf_att=iom_read_att( td_file, il_varid, id_attid)
307            CASE('dimg')
308               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
309               &              "in dimg file : "//TRIM(td_file%c_name) )
310            CASE DEFAULT
311               CALL logger_error( " IOM READ ATT: can't read attribute "//&
312               &    " in file "//TRIM(td_file%c_name)//" : type unknown " )
313         END SELECT
314      ENDIF
315
316   END FUNCTION iom__read_att_varname_id
317   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
318   FUNCTION iom__read_att_varid_id(td_file, id_varid, id_attid) &
319         & RESULT (tf_att)
320   !-------------------------------------------------------------------
321   !> @brief This function read attribute (of variable or global) in an opened
322   !> file, given variable id and attribute id.
323   !>
324   !> @author J.Paul
325   !> @date November, 2013 - Initial Version
326   !>
327   !> @param[in] td_file   file structure
328   !> @param[in] id_varid  variable id. use NF90_GLOBAL to read global
329   !> attribute in a file
330   !> @param[in] id_attid  attribute id
331   !> @return  attribute structure
332   !-------------------------------------------------------------------
333
334      IMPLICIT NONE
335
336      ! Argument
337      TYPE(TFILE), INTENT(IN) :: td_file
338      INTEGER(i4), INTENT(IN) :: id_varid
339      INTEGER(i4), INTENT(IN) :: id_attid
340
341      ! function
342      TYPE(TATT)              :: tf_att
343      !----------------------------------------------------------------
344
345      ! open file
346      SELECT CASE(TRIM(td_file%c_type))
347         CASE('cdf')
348            tf_att=iom_cdf_read_att(td_file, id_varid, id_attid)
349         CASE('dimg')
350            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file "//&
351            &              TRIM(td_file%c_name) )
352         CASE DEFAULT
353            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
354            &               TRIM(td_file%c_name)//" : type unknown " )
355      END SELECT
356
357   END FUNCTION iom__read_att_varid_id
358   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
359   FUNCTION iom__read_att_varname_name(td_file, cd_varname, cd_attname) &
360         & RESULT (tf_att)
361   !-------------------------------------------------------------------
362   !> @brief This function read attribute (of variable or global) in an opened
363   !> file, given variable name or standard name, and attribute name.
364   !> @details
365   !> - to get global attribute use 'GLOBAL' as variable name.
366   !>
367   !> @author J.Paul
368   !> @date November, 2013 - Initial Version
369   !>
370   !> @param[in] td_file      file structure
371   !> @param[in] cd_varname   variable name or standard name. use 'GLOBAL' to read global
372   !> attribute in a file
373   !> @param[in] cd_attname   attribute name
374   !> @return  attribute structure   
375   !-------------------------------------------------------------------
376
377      IMPLICIT NONE
378
379      ! Argument
380      TYPE(TFILE),      INTENT(IN) :: td_file
381      CHARACTER(LEN=*), INTENT(IN) :: cd_varname
382      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
383
384      ! function
385      TYPE(TATT)                   :: tf_att
386
387      ! local variable
388      INTEGER(i4) :: il_varid
389      !----------------------------------------------------------------
390
391      ! get variable id
392      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
393         il_varid=NF90_GLOBAL
394      ELSE
395         il_varid=var_get_id(td_file%t_var(:), cd_varname)
396      ENDIF
397
398      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
399         ! open file
400         SELECT CASE(TRIM(td_file%c_type))
401            CASE('cdf')
402               tf_att=iom_cdf_read_att(td_file, il_varid, cd_attname)
403            CASE('dimg')
404               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
405               &              "in dimg file :"//TRIM(td_file%c_name) )
406            CASE DEFAULT
407               CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
408               &               TRIM(td_file%c_name)//" : type unknown " )
409         END SELECT
410      ENDIF
411
412   END FUNCTION iom__read_att_varname_name
413   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
414   FUNCTION iom__read_att_varid_name(td_file, id_varid, cd_attname) &
415         & RESULT (tf_att)
416   !-------------------------------------------------------------------
417   !> @brief This function read attribute (of variable or global) in an opened
418   !> file, given variable id and attribute name.
419   !>
420   !> @author J.Paul
421   !> @date November, 2013 - Initial Version
422   !>
423   !> @param[in] td_file      file structure
424   !> @param[in] id_varid     variable id. use NF90_GLOBAL to read global
425   !> attribute in a file
426   !> @param[in] cd_attname   attribute name
427   !> @return  attribute structure   
428   !-------------------------------------------------------------------
429
430      IMPLICIT NONE
431
432      ! Argument
433      TYPE(TFILE), INTENT(IN) :: td_file
434      INTEGER(i4), INTENT(IN) :: id_varid
435      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
436
437      ! function
438      TYPE(TATT)              :: tf_att
439      !----------------------------------------------------------------
440
441      ! open file
442      SELECT CASE(TRIM(td_file%c_type))
443         CASE('cdf')
444            tf_att=iom_cdf_read_att(td_file, id_varid, cd_attname)
445         CASE('dimg')
446            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file :"&
447            &              //TRIM(td_file%c_name) )
448         CASE DEFAULT
449            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
450            &               TRIM(td_file%c_name)//" : type unknown " )
451      END SELECT
452
453   END FUNCTION iom__read_att_varid_name
454   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
455   FUNCTION iom__read_dim_id(td_file, id_dimid) &
456         & RESULT (tf_dim)
457   !-------------------------------------------------------------------
458   !> @brief This function read one dimension in an opened file,
459   !> given dimension id.
460   !>
461   !> @author J.Paul
462   !> @date November, 2013 - Initial Version
463   !>
464   !> @param[in] td_file   file structure
465   !> @param[in] id_dimid  dimension id
466   !> @return  dimension structure
467   !-------------------------------------------------------------------
468
469      IMPLICIT NONE
470
471      ! Argument     
472      TYPE(TFILE), INTENT(IN) :: td_file
473      INTEGER(i4), INTENT(IN) :: id_dimid
474
475      ! function
476      TYPE(TDIM)              :: tf_dim
477      !----------------------------------------------------------------
478
479      ! open file
480      SELECT CASE(TRIM(td_file%c_type))
481         CASE('cdf')
482            tf_dim=iom_cdf_read_dim(td_file, id_dimid)
483         CASE('dimg')
484            tf_dim=iom_rstdimg_read_dim(td_file, id_dimid)
485         CASE DEFAULT
486            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
487            &               TRIM(td_file%c_name)//" : type unknown " )
488      END SELECT     
489
490   END FUNCTION iom__read_dim_id
491   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
492   FUNCTION iom__read_dim_name(td_file, cd_name) &
493         & RESULT(tf_dim)
494   !-------------------------------------------------------------------
495   !> @brief This function read one dimension in an opened netcdf file,
496   !> given dimension name.
497   !>
498   !> @author J.Paul
499   !> @date November, 2013 - Initial Version
500   !>
501   !> @param[in] td_file   file structure
502   !> @param[in] cd_name   dimension name
503   !> @return  dimension structure
504   !-------------------------------------------------------------------
505
506      IMPLICIT NONE
507
508      ! Argument     
509      TYPE(TFILE),      INTENT(IN) :: td_file
510      CHARACTER(LEN=*), INTENT(IN) :: cd_name
511
512      ! function
513      TYPE(TDIM)                   :: tf_dim
514      !----------------------------------------------------------------
515
516      ! open file
517      SELECT CASE(TRIM(td_file%c_type))
518         CASE('cdf')
519            tf_dim=iom_cdf_read_dim(td_file, cd_name)
520         CASE('dimg')
521            tf_dim=iom_rstdimg_read_dim(td_file, cd_name)
522         CASE DEFAULT
523            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
524            &               TRIM(td_file%c_name)//" : type unknown " )
525      END SELECT     
526
527   END FUNCTION iom__read_dim_name
528   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
529   FUNCTION iom__read_var_id(td_file, id_varid, id_start, id_count) &
530         & RESULT (tf_var)
531   !-------------------------------------------------------------------
532   !> @brief This function read variable value in an opened
533   !> file, given variable id.
534   !> @details
535   !> start indices and number of indices selected along each dimension
536   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
537   !>
538   !> @author J.Paul
539   !> @date November, 2013 - Initial Version
540   !>
541   !> @param[in] td_file   file structure
542   !> @param[in] id_varid  variable id
543   !> @param[in] id_start  index in the variable from which the data values
544   !> will be read
545   !> @param[in] id_count  number of indices selected along each dimension
546   !> @return  variable structure
547   !-------------------------------------------------------------------
548
549      IMPLICIT NONE
550
551      ! Argument     
552      TYPE(TFILE),                       INTENT(IN) :: td_file
553      INTEGER(i4),                       INTENT(IN) :: id_varid
554      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start
555      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count
556
557      ! function
558      TYPE(TVAR)                                    :: tf_var
559      !----------------------------------------------------------------
560
561      ! open file
562      SELECT CASE(TRIM(td_file%c_type))
563         CASE('cdf')
564            tf_var=iom_cdf_read_var(td_file, id_varid, id_start, id_count)
565         CASE('dimg')
566            tf_var=iom_rstdimg_read_var(td_file, id_varid, id_start, id_count)
567         CASE DEFAULT
568            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
569            &               TRIM(td_file%c_name)//" : type unknown " )
570      END SELECT
571
572   END FUNCTION iom__read_var_id
573   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
574   FUNCTION iom__read_var_name(td_file, cd_name, id_start, id_count) &
575      & RESULT (tf_var)
576   !-------------------------------------------------------------------
577   !> @brief This function read variable value in an opened
578   !> file, given variable name or standard name.
579   !> @details
580   !> start indices and number of indices selected along each dimension
581   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
582   !>
583   !> look first for variable name. If it doesn't
584   !> exist in file, look for variable standard name.<br/>
585   !>
586   !> @author J.Paul
587   !> @date November, 2013 - Initial Version
588   !>
589   !> @param[in] td_file   file structure
590   !> @param[in] cd_name   variable name or standard name
591   !> @param[in] id_start  index in the variable from which the data values
592   !> will be read
593   !> @param[in] id_count  number of indices selected along each dimension
594   !> @return  variable structure
595   !-------------------------------------------------------------------
596
597      IMPLICIT NONE
598
599      ! Argument     
600      TYPE(TFILE)                   , INTENT(IN) :: td_file
601      CHARACTER(LEN=*)              , INTENT(IN) :: cd_name
602      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_start
603      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_count
604
605      ! function
606      TYPE(TVAR)                                 :: tf_var
607      !----------------------------------------------------------------
608     
609      ! open file
610      SELECT CASE(TRIM(td_file%c_type))
611         CASE('cdf')
612            tf_var=iom_cdf_read_var(td_file, cd_name, id_start, id_count )
613         CASE('dimg')
614            tf_var=iom_rstdimg_read_var(td_file, cd_name, id_start, id_count )
615         CASE DEFAULT
616            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
617            &               TRIM(td_file%c_name)//" : type unknown " )
618      END SELECT
619
620   END FUNCTION iom__read_var_name
621   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
622   SUBROUTINE iom_write_file(td_file, cd_dimorder)
623   !-------------------------------------------------------------------
624   !> @brief This subroutine write file structure in an opened file.
625   !>
626   !> @details
627   !> optionally, you could specify dimension order (default 'xyzt')
628   !>
629   !> @author J.Paul
630   !> @date November, 2013 - Initial Version
631   !> @date July, 2015 - add dimension order option
632   !> @date August, 2017
633   !> - split in write_header and write_var
634   !>
635   !> @param[in] td_file   file structure
636   !-------------------------------------------------------------------
637
638      IMPLICIT NONE
639
640      ! Argument     
641      TYPE(TFILE)     , INTENT(INOUT) :: td_file
642      CHARACTER(LEN=*), INTENT(IN   ), OPTIONAL :: cd_dimorder
643      !----------------------------------------------------------------
644
645      CALL iom_write_header(td_file, cd_dimorder)
646
647      CALL iom_write_var(td_file)
648
649   END SUBROUTINE iom_write_file
650   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
651   SUBROUTINE iom_write_header(td_file, cd_dimorder, td_dim)
652   !-------------------------------------------------------------------
653   !> @brief This subroutine write header from file structure
654   !> of an opened file.
655   !>
656   !> @details
657   !> optionally, you could specify dimension order (default 'xyzt'),
658   !> and dimension structure for netcdf case.
659   !>
660   !> @author J.Paul
661   !> @date August, 2017 - Initial Version
662   !>
663   !> @param[inout] td_file      file structure
664   !> @param[in] cd_dimorder  dimension order
665   !> @param[in] td_dim       array of dimension structure
666   !-------------------------------------------------------------------
667
668      IMPLICIT NONE
669
670      ! Argument     
671      TYPE(TFILE)                           , INTENT(INOUT) :: td_file
672      CHARACTER(LEN=*)                      , INTENT(IN   ), OPTIONAL :: cd_dimorder
673      TYPE(TDIM)      , DIMENSION(ip_maxdim), INTENT(IN   ), OPTIONAL :: td_dim
674      !----------------------------------------------------------------
675
676      ! open file
677      SELECT CASE(TRIM(td_file%c_type))
678         CASE('cdf')
679            CALL iom_cdf_write_header(td_file, cd_dimorder, td_dim)
680         CASE('dimg')
681            ! note: can not change dimension order in restart dimg file
682            CALL iom_rstdimg_write_header(td_file)
683         CASE DEFAULT
684            CALL logger_error( " IOM WRITE HEADER: can't write header&
685            &                  , file "//TRIM(td_file%c_name)//" : &
686            &                  type unknown " )
687      END SELECT
688
689   END SUBROUTINE iom_write_header
690   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
691   SUBROUTINE iom_write_var(td_file, cd_dimorder, id_start, id_count)
692   !-------------------------------------------------------------------
693   !> @brief This subroutine write variables from file structure
694   !> in an opened file.
695   !>
696   !> @details
697   !>
698   !> @author J.Paul
699   !> @date August, 2017 - Initial Version
700   !>
701   !> @param[inout] td_file   file structure
702   !> @param[in] cd_dimorder  dimension order
703   !> @param[in] id_start  index in the variable from which the data values
704   !> will be read
705   !> @param[in] id_count  number of indices selected along each dimension
706   !-------------------------------------------------------------------
707
708      IMPLICIT NONE
709
710      ! Argument     
711      TYPE(TFILE)                   , INTENT(INOUT) :: td_file
712      CHARACTER(LEN=*)              , INTENT(IN   ), OPTIONAL :: cd_dimorder
713      INTEGER(i4)     , DIMENSION(:), INTENT(IN   ), OPTIONAL :: id_start
714      INTEGER(i4)     , DIMENSION(:), INTENT(IN   ), OPTIONAL :: id_count
715      !----------------------------------------------------------------
716
717      ! open file
718      SELECT CASE(TRIM(td_file%c_type))
719         CASE('cdf')
720            CALL iom_cdf_write_var(td_file, cd_dimorder, &
721                 &                 id_start, id_count)
722         CASE('dimg')
723            ! note: can not change dimension order in restart dimg file
724            CALL iom_rstdimg_write_var(td_file)
725         CASE DEFAULT
726            CALL logger_error( " IOM WRITE VAR: can't write variable, file "//&
727            &               TRIM(td_file%c_name)//" : type unknown " )
728      END SELECT
729
730   END SUBROUTINE iom_write_var
731   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
732END MODULE iom
733
Note: See TracBrowser for help on using the repository browser.