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

source: branches/2013/dev_MERGE_2013/NEMOGCM/TOOLS/SIREN/src/iom.f90 @ 4317

Last change on this file since 4317 was 4213, checked in by cbricaud, 11 years ago

first draft of the CONFIGURATION MANAGER demonstrator

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