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/2014/dev_r4650_UKMO14.5_SST_BIAS_CORRECTION/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/2014/dev_r4650_UKMO14.5_SST_BIAS_CORRECTION/NEMOGCM/TOOLS/SIREN/src/iom.f90 @ 5967

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

Reset keywords before merging with head of trunk

  • Property svn:keywords set to Id
File size: 22.6 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
9!>
10!> @details
11!>    to open file:<br/>
12!> @code
13!>    CALL iom_open(td_file)
14!> @endcode
15!>       - td_file is file structure
16!>
17!>    to create file:<br/>
18!> @code
19!>    CALL iom_create(td_file)
20!> @endcode
21!>       - td_file is file structure
22!>
23!>    to write in file:<br/>
24!> @code
25!>    CALL  iom_write_file(td_file)
26!> @endcode
27!>
28!>    to close file:<br/>
29!> @code
30!>    CALL iom_close(tl_file)
31!> @endcode
32!>
33!>    to read one dimension in file:<br/>
34!> @code
35!>    tl_dim = iom_read_dim(tl_file, id_dimid)
36!> @endcode
37!>    or<br/>
38!> @code
39!>    tl_dim = iom_read_dim(tl_file, cd_name)
40!> @endcode
41!>       - id_dimid is dimension id
42!>       - cd_name is dimension name
43!>
44!>    to read variable or global attribute in file:<br/>
45!> @code
46!>    tl_att = iom_read_att(tl_file, id_varid, id_attid)
47!> @endcode
48!>    or
49!> @code
50!>    tl_att = iom_read_att(tl_file, id_varid, cd_attname)
51!> @endcode
52!>    or
53!> @code
54!>    tl_att = iom_read_att(tl_file, cd_varname, id_attid)
55!> @endcode
56!>    or
57!> @code
58!>    tl_att = iom_read_att(tl_file, cd_varname, cd_attname)
59!> @endcode
60!>       - id_varid is variable id
61!>       - id_attid is attribute id
62!>       - cd_attname is attribute name
63!>       - cd_varname is variable name or standard name
64!>   
65!>    to read one variable in file:<br/>
66!> @code
67!>    tl_var = iom_read_var(td_file, id_varid, [id_start, id_count])
68!> @endcode
69!>    or
70!> @code
71!>    tl_var = iom_read_var(td_file, cd_name, [id_start, [id_count,]])
72!> @endcode
73!>       - id_varid is variabale id
74!>       - cd_name is variabale name or standard name.
75!>       - id_start is a integer(4) 1D array of index from which the data
76!>          values will be read [optional]
77!>       - id_count is a integer(4) 1D array of the number of indices selected
78!>          along each dimension [optional]
79!>
80!> @author
81!> J.Paul
82! REVISION HISTORY:
83!> @date November, 2013 - Initial Version
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   USE netcdf                          ! nf90 library
93   USE global                          ! global parameter
94   USE kind                            ! F90 kind parameter
95   USE fct                             ! basic useful function
96   USE logger                          ! log file manager
97   USE dim                             ! dimension manager
98   USE att                             ! attribute manager
99   USE var                             ! variable manager
100   USE file                            ! file manager
101   USE iom_cdf                         ! netcdf I/O manager
102   USE iom_rstdimg                     ! restart dimg I/O manager
103   IMPLICIT NONE
104   ! NOTE_avoid_public_variables_if_possible
105
106   ! function and subroutine
107   PUBLIC :: iom_open        !< open or create file, fill file structure
108   PUBLIC :: iom_create      !< create file, fill file structure
109   PUBLIC :: iom_close       !< close file
110   PUBLIC :: iom_read_dim    !< read one dimension in an opened file
111   PUBLIC :: iom_read_att    !< read one attribute in an opened file
112   PUBLIC :: iom_read_var    !< read one variable  in an opened file   
113   PUBLIC :: iom_write_file  !< write file structure contents in an opened file
114
115                                          ! read variable or global attribute in an opened file
116   PRIVATE :: iom__read_att_varname_id   ! given variable name or standard name and attribute id.
117   PRIVATE :: iom__read_att_varid_id     ! given variable id and attribute id.
118   PRIVATE :: iom__read_att_varname_name ! given variable name or standard name, and attribute name.
119   PRIVATE :: iom__read_att_varid_name   ! given variable id and attribute name.
120
121   PRIVATE :: iom__read_dim_id            ! read one dimension in an opened file, given dimension id.
122   PRIVATE :: iom__read_dim_name          ! read one dimension in an opened netcdf file, given dimension name.
123   PRIVATE :: iom__read_var_id            ! read variable value in an opened file, given variable id.
124   PRIVATE :: iom__read_var_name          ! read variable value in an opened file, given variable name or standard name.
125
126   INTERFACE iom_read_var
127      MODULE PROCEDURE iom__read_var_id
128      MODULE PROCEDURE iom__read_var_name
129   END INTERFACE iom_read_var
130
131   INTERFACE iom_read_dim
132      MODULE PROCEDURE iom__read_dim_id
133      MODULE PROCEDURE iom__read_dim_name
134   END INTERFACE iom_read_dim
135
136   INTERFACE iom_read_att    !< read variable or global attribute in an opened file
137      MODULE PROCEDURE iom__read_att_varname_id   !< given variable name or standard name and attribute id.
138      MODULE PROCEDURE iom__read_att_varid_id     !< given variable id and attribute id.
139      MODULE PROCEDURE iom__read_att_varname_name !< given variable name or standard name, and attribute name.
140      MODULE PROCEDURE iom__read_att_varid_name   !< given variable id and attribute name.
141   END INTERFACE iom_read_att
142
143CONTAINS
144   !-------------------------------------------------------------------
145   !> @brief This function open a file in read or write mode
146   !> @details
147   !> If try to open a file in write mode that did not exist, create it.<br/>
148   !>
149   !> If file exist, get information about:
150   !> - the number of variables
151   !> - the number of dimensions
152   !> - the number of global attributes
153   !> - the ID of the unlimited dimension
154   !> - the file format
155   !> and finally read dimensions.
156   !>
157   !> @author J.Paul
158   !> - November, 2013- Initial Version
159   !
160   !> @param[inout] td_file file structure
161   !-------------------------------------------------------------------
162   SUBROUTINE iom_open(td_file)
163      IMPLICIT NONE
164      ! Argument     
165      TYPE(TFILE), INTENT(INOUT)  :: td_file
166      !----------------------------------------------------------------
167
168      ! add suffix to file name
169      td_file%c_name = file_add_suffix( TRIM(td_file%c_name), &
170      &                                 TRIM(td_file%c_type)  )
171      ! check type
172      SELECT CASE(TRIM(ADJUSTL(fct_lower(td_file%c_type))))
173
174         CASE('cdf')
175            CALL iom_cdf_open(td_file)
176         CASE('dimg')
177            CALL iom_rstdimg_open(td_file)
178         CASE DEFAULT
179            CALL logger_error("IOM OPEN: unknow type : "//TRIM(td_file%c_name))
180
181      END SELECT
182
183   END SUBROUTINE iom_open
184   !-------------------------------------------------------------------
185   !> @brief This function create a file.
186   !>
187   !> @author J.Paul
188   !> - November, 2013- Initial Version
189   !
190   !> @param[inout] td_file file structure
191   !-------------------------------------------------------------------
192   SUBROUTINE iom_create(td_file)
193      IMPLICIT NONE
194      ! Argument     
195      TYPE(TFILE), INTENT(INOUT)  :: td_file
196
197      ! local variable
198      LOGICAL     :: ll_exist
199      !----------------------------------------------------------------
200
201      INQUIRE(FILE=TRIM(td_file%c_name), EXIST=ll_exist )
202      IF( ll_exist )THEN
203         CALL logger_fatal("IOM CREATE: can not create file "//&
204         &  TRIM(td_file%c_name)//". file exist already.")
205      ENDIF
206
207      ! forced to open in write mode
208      td_file%l_wrt=.TRUE.
209      ! check type
210      SELECT CASE(TRIM(td_file%c_type))
211         CASE('cdf')
212            CALL iom_cdf_open(td_file)
213         CASE('dimg')
214            CALL iom_rstdimg_open(td_file)
215         CASE DEFAULT
216            CALL logger_error( "IOM CREATE: can't create file "//&
217            &               TRIM(td_file%c_name)//": type unknown " )
218      END SELECT
219
220   END SUBROUTINE iom_create
221   !-------------------------------------------------------------------
222   !> @brief This subroutine close file
223   !>
224   !> @author J.Paul
225   !> - November, 2013- Initial Version
226   !
227   !> @param[inout] td_file file structure
228   !-------------------------------------------------------------------
229   SUBROUTINE iom_close(td_file)
230      IMPLICIT NONE
231      ! Argument     
232      TYPE(TFILE), INTENT(INOUT) :: td_file
233      !----------------------------------------------------------------
234
235      ! open file
236      SELECT CASE(TRIM(td_file%c_type))
237         CASE('cdf')
238            CALL iom_cdf_close(td_file)
239         CASE('dimg')
240            CALL iom_rstdimg_close(td_file)
241         CASE DEFAULT
242            CALL logger_error( "IOM CLOSE: can't close file "//&
243            &               TRIM(td_file%c_name)//": type unknown " )
244      END SELECT
245
246   END SUBROUTINE iom_close
247   !-------------------------------------------------------------------
248   !> @brief This function read attribute (of variable or global) in an opened
249   !> file, given variable name or standard name and attribute id.
250   !> @details
251   !>  - to get global attribute use 'GLOBAL' as variable name.
252   !
253   !> @author J.Paul
254   !> - November, 2013- Initial Version
255   !
256   !> @param[in] td_file      file structure
257   !> @param[in] cd_varname   variable name. use 'GLOBAL' to read global
258   !> attribute in a file
259   !> @param[in] id_attid     attribute id
260   !> @return  attribute structure
261   !-------------------------------------------------------------------
262   TYPE(TATT) FUNCTION iom__read_att_varname_id( td_file, cd_varname, &
263   &                                             id_attid)
264      IMPLICIT NONE
265      ! Argument
266      TYPE(TFILE),       INTENT(IN) :: td_file
267      CHARACTER(LEN=lc), INTENT(IN) :: cd_varname
268      INTEGER(i4),       INTENT(IN) :: id_attid
269
270      ! local variable
271      INTEGER(i4) :: il_varid
272      !----------------------------------------------------------------
273
274      ! get variable id
275      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
276         il_varid=NF90_GLOBAL
277      ELSE
278         il_varid=var_get_id(td_file%t_var(:), cd_varname)
279      ENDIF
280
281      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
282         ! open file
283         SELECT CASE(TRIM(td_file%c_type))
284            CASE('cdf')
285               iom__read_att_varname_id=iom_read_att( td_file, il_varid, &
286               &                                       id_attid)
287            CASE('dimg')
288               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
289               &              "in dimg file : "//TRIM(td_file%c_name) )
290            CASE DEFAULT
291               CALL logger_error( " IOM READ ATT: can't read attribute "//&
292               &    " in file "//TRIM(td_file%c_name)//" : type unknown " )
293         END SELECT
294      ENDIF
295
296   END FUNCTION iom__read_att_varname_id
297   !-------------------------------------------------------------------
298   !> @brief This function read attribute (of variable or global) in an opened
299   !> file, given variable id and attribute id.
300   !>
301   !> @author J.Paul
302   !> - November, 2013- Initial Version
303   !
304   !> @param[in] td_file   file structure
305   !> @param[in] id_varid  variable id. use NF90_GLOBAL to read global
306   !> attribute in a file
307   !> @param[in] id_attid  attribute id
308   !> @return  attribute structure
309   !-------------------------------------------------------------------
310   TYPE(TATT) FUNCTION iom__read_att_varid_id( td_file, id_varid, &
311   &                                            id_attid)
312      IMPLICIT NONE
313      ! Argument
314      TYPE(TFILE), INTENT(IN) :: td_file
315      INTEGER(i4), INTENT(IN) :: id_varid
316      INTEGER(i4), INTENT(IN) :: id_attid
317      !----------------------------------------------------------------
318
319      ! open file
320      SELECT CASE(TRIM(td_file%c_type))
321         CASE('cdf')
322            iom__read_att_varid_id=iom_cdf_read_att( td_file, id_varid, &
323            &                                         id_attid)
324         CASE('dimg')
325            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file "//&
326            &              TRIM(td_file%c_name) )
327         CASE DEFAULT
328            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
329            &               TRIM(td_file%c_name)//" : type unknown " )
330      END SELECT
331
332   END FUNCTION iom__read_att_varid_id
333   !-------------------------------------------------------------------
334   !> @brief This function read attribute (of variable or global) in an opened
335   !> file, given variable name or standard name, and attribute name.
336   !> @details
337   !> - to get global attribute use 'GLOBAL' as variable name.
338   !
339   !> @author J.Paul
340   !> - November, 2013- Initial Version
341   !
342   !> @param[in] td_file      file structure
343   !> @param[in] cd_varname   variable name or standard name. use 'GLOBAL' to read global
344   !> attribute in a file
345   !> @param[in] cd_attname   attribute name
346   !> @return  attribute structure   
347   !-------------------------------------------------------------------
348   TYPE(TATT) FUNCTION iom__read_att_varname_name( td_file, cd_varname, &
349   &                                                cd_attname)
350      IMPLICIT NONE
351      ! Argument
352      TYPE(TFILE),      INTENT(IN) :: td_file
353      CHARACTER(LEN=*), INTENT(IN) :: cd_varname
354      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
355
356      ! local variable
357      INTEGER(i4) :: il_varid
358      !----------------------------------------------------------------
359
360      ! get variable id
361      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
362         il_varid=NF90_GLOBAL
363      ELSE
364         il_varid=var_get_id(td_file%t_var(:), cd_varname)
365      ENDIF
366
367      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
368         ! open file
369         SELECT CASE(TRIM(td_file%c_type))
370            CASE('cdf')
371               iom__read_att_varname_name=iom_cdf_read_att( td_file, il_varid, &
372               &                                             cd_attname)
373            CASE('dimg')
374               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
375               &              "in dimg file :"//TRIM(td_file%c_name) )
376            CASE DEFAULT
377               CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
378               &               TRIM(td_file%c_name)//" : type unknown " )
379         END SELECT
380      ENDIF
381
382   END FUNCTION iom__read_att_varname_name
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   !> - November, 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_attname   attribute name
394   !> @return  attribute structure   
395   !-------------------------------------------------------------------
396   TYPE(TATT) FUNCTION iom__read_att_varid_name( td_file, id_varid, &
397   &                                              cd_attname)
398      IMPLICIT NONE
399      ! Argument
400      TYPE(TFILE), INTENT(IN) :: td_file
401      INTEGER(i4), INTENT(IN) :: id_varid
402      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
403      !----------------------------------------------------------------
404
405      ! open file
406      SELECT CASE(TRIM(td_file%c_type))
407         CASE('cdf')
408            iom__read_att_varid_name=iom_cdf_read_att( td_file, id_varid, &
409            &                                           cd_attname)
410         CASE('dimg')
411            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file :"&
412            &              //TRIM(td_file%c_name) )
413         CASE DEFAULT
414            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
415            &               TRIM(td_file%c_name)//" : type unknown " )
416      END SELECT
417
418   END FUNCTION iom__read_att_varid_name
419   !-------------------------------------------------------------------
420   !> @brief This function read one dimension in an opened file,
421   !> given dimension id.
422   !
423   !> @author J.Paul
424   !> - November, 2013- Initial Version
425   !
426   !> @param[in] td_file   file structure
427   !> @param[in] id_dimid  dimension id
428   !> @return  dimension structure
429   !-------------------------------------------------------------------
430   TYPE(TDIM) FUNCTION iom__read_dim_id(td_file, id_dimid)
431      IMPLICIT NONE
432      ! Argument     
433      TYPE(TFILE), INTENT(IN) :: td_file
434      INTEGER(i4), INTENT(IN) :: id_dimid
435      !----------------------------------------------------------------
436
437      ! open file
438      SELECT CASE(TRIM(td_file%c_type))
439         CASE('cdf')
440            iom__read_dim_id=iom_cdf_read_dim(td_file, id_dimid)
441         CASE('dimg')
442            iom__read_dim_id=iom_rstdimg_read_dim(td_file, id_dimid)
443         CASE DEFAULT
444            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
445            &               TRIM(td_file%c_name)//" : type unknown " )
446      END SELECT     
447
448   END FUNCTION iom__read_dim_id
449   !-------------------------------------------------------------------
450   !> @brief This function read one dimension in an opened netcdf file,
451   !> given dimension name.
452   !
453   !> @author J.Paul
454   !> - November, 2013- Initial Version
455   !
456   !> @param[in] td_file   file structure
457   !> @param[in] cd_name   dimension name
458   !> @return  dimension structure
459   !-------------------------------------------------------------------
460   TYPE(TDIM) FUNCTION iom__read_dim_name(td_file, cd_name)
461      IMPLICIT NONE
462      ! Argument     
463      TYPE(TFILE),      INTENT(IN) :: td_file
464      CHARACTER(LEN=*), INTENT(IN) :: cd_name
465      !----------------------------------------------------------------
466
467      ! open file
468      SELECT CASE(TRIM(td_file%c_type))
469         CASE('cdf')
470            iom__read_dim_name=iom_cdf_read_dim(td_file, cd_name)
471         CASE('dimg')
472            iom__read_dim_name=iom_rstdimg_read_dim(td_file, cd_name)
473         CASE DEFAULT
474            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
475            &               TRIM(td_file%c_name)//" : type unknown " )
476      END SELECT     
477
478   END FUNCTION iom__read_dim_name
479   !-------------------------------------------------------------------
480   !> @brief This function read variable value in an opened
481   !> file, given variable id.
482   !> @details
483   !> start indices and number of indices selected along each dimension
484   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
485   !
486   !> @author J.Paul
487   !> - November, 2013- Initial Version
488   !
489   !> @param[in] td_file   file structure
490   !> @param[in] id_varid  variable id
491   !> @param[in] id_start  index in the variable from which the data values
492   !> will be read
493   !> @param[in] id_count  number of indices selected along each dimension
494   !> @return  variable structure
495   !-------------------------------------------------------------------
496   TYPE(TVAR) FUNCTION iom__read_var_id( td_file, id_varid,&
497   &                                     id_start, id_count)
498      IMPLICIT NONE
499      ! Argument     
500      TYPE(TFILE),                       INTENT(IN) :: td_file
501      INTEGER(i4),                       INTENT(IN) :: id_varid
502      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start
503      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count
504      !----------------------------------------------------------------
505
506      ! open file
507      SELECT CASE(TRIM(td_file%c_type))
508         CASE('cdf')
509            iom__read_var_id=iom_cdf_read_var(td_file, id_varid, &
510            &                                 id_start, id_count)
511         CASE('dimg')
512            iom__read_var_id=iom_rstdimg_read_var(td_file, id_varid, &
513            &                                     id_start, id_count)
514         CASE DEFAULT
515            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
516            &               TRIM(td_file%c_name)//" : type unknown " )
517      END SELECT
518
519   END FUNCTION iom__read_var_id
520   !-------------------------------------------------------------------
521   !> @brief This function read variable value in an opened
522   !> file, given variable name or standard name.
523   !> @details
524   !> start indices and number of indices selected along each dimension
525   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
526   !>
527   !> look first for variable name. If it doesn't
528   !> exist in file, look for variable standard name.<br/>
529   !
530   !> @author J.Paul
531   !> - November, 2013- Initial Version
532   !
533   !> @param[in] td_file   file structure
534   !> @param[in] cd_name   variable name or standard name
535   !> @param[in] id_start  index in the variable from which the data values
536   !> will be read
537   !> @param[in] id_count  number of indices selected along each dimension
538   !> @return  variable structure
539   !-------------------------------------------------------------------
540   TYPE(TVAR) FUNCTION iom__read_var_name(td_file, cd_name,   &
541   &                                      id_start, id_count  )
542      IMPLICIT NONE
543      ! Argument     
544      TYPE(TFILE)                   , INTENT(IN) :: td_file
545      CHARACTER(LEN=*)              , INTENT(IN) :: cd_name
546      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_start
547      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_count
548      !----------------------------------------------------------------
549     
550      ! open file
551      SELECT CASE(TRIM(td_file%c_type))
552         CASE('cdf')
553            iom__read_var_name=iom_cdf_read_var(td_file, cd_name, &
554            &                                   id_start, id_count )
555         CASE('dimg')
556            iom__read_var_name=iom_rstdimg_read_var(td_file, cd_name, &
557            &                                   id_start, id_count )
558         CASE DEFAULT
559            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
560            &               TRIM(td_file%c_name)//" : type unknown " )
561      END SELECT
562
563   END FUNCTION iom__read_var_name
564   !-------------------------------------------------------------------
565   !> @brief This subroutine write file structure in an opened file.
566   !
567   !> @author J.Paul
568   !> - November, 2013- Initial Version
569   !
570   !> @param[in] td_file   file structure
571   !-------------------------------------------------------------------
572   SUBROUTINE iom_write_file(td_file)
573      IMPLICIT NONE
574      ! Argument     
575      TYPE(TFILE), INTENT(INOUT) :: td_file
576      !----------------------------------------------------------------
577
578      ! open file
579      SELECT CASE(TRIM(td_file%c_type))
580         CASE('cdf')
581            CALL iom_cdf_write_file(td_file)
582         CASE('dimg')
583            CALL iom_rstdimg_write_file(td_file)
584         CASE DEFAULT
585            CALL logger_error( " IOM WRITE: can't write file "//&
586            &               TRIM(td_file%c_name)//" : type unknown " )
587      END SELECT
588
589   END SUBROUTINE iom_write_file
590END MODULE iom
591
Note: See TracBrowser for help on using the repository browser.