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/2015/nemo_v3_6_STABLE/NEMOGCM/TOOLS/SIREN/src – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/TOOLS/SIREN/src/iom.f90 @ 8862

Last change on this file since 8862 was 8862, checked in by jpaul, 6 years ago

Bugs fix: see tickets #1989

File size: 23.1 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   !> @date 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('cdf4')
177         CASE('dimg')
178            CALL iom_rstdimg_open(td_file)
179         CASE DEFAULT
180            CALL logger_error("IOM OPEN: unknow type : "//TRIM(td_file%c_name))
181
182      END SELECT
183
184   END SUBROUTINE iom_open
185   !-------------------------------------------------------------------
186   !> @brief This function create a file.
187   !>
188   !> @author J.Paul
189   !> @date November, 2013 - Initial Version
190   !
191   !> @param[inout] td_file file structure
192   !-------------------------------------------------------------------
193   SUBROUTINE iom_create(td_file)
194      IMPLICIT NONE
195      ! Argument     
196      TYPE(TFILE), INTENT(INOUT)  :: td_file
197
198      ! local variable
199      LOGICAL     :: ll_exist
200      !----------------------------------------------------------------
201
202      INQUIRE(FILE=TRIM(td_file%c_name), EXIST=ll_exist )
203      IF( ll_exist )THEN
204         CALL logger_fatal("IOM CREATE: can not create file "//&
205         &  TRIM(td_file%c_name)//". file exist already.")
206      ENDIF
207
208      ! forced to open in write mode
209      td_file%l_wrt=.TRUE.
210      ! check type
211      SELECT CASE(TRIM(td_file%c_type))
212         CASE('cdf')
213            CALL iom_cdf_open(td_file)
214         CASE('dimg')
215            CALL iom_rstdimg_open(td_file)
216         CASE DEFAULT
217            CALL logger_error( "IOM CREATE: can't create file "//&
218            &               TRIM(td_file%c_name)//": type unknown " )
219      END SELECT
220
221   END SUBROUTINE iom_create
222   !-------------------------------------------------------------------
223   !> @brief This subroutine close file
224   !>
225   !> @author J.Paul
226   !> @date November, 2013 - Initial Version
227   !
228   !> @param[inout] td_file file structure
229   !-------------------------------------------------------------------
230   SUBROUTINE iom_close(td_file)
231      IMPLICIT NONE
232      ! Argument     
233      TYPE(TFILE), INTENT(INOUT) :: td_file
234      !----------------------------------------------------------------
235
236      ! open file
237      SELECT CASE(TRIM(td_file%c_type))
238         CASE('cdf')
239            CALL iom_cdf_close(td_file)
240         CASE('dimg')
241            CALL iom_rstdimg_close(td_file)
242         CASE DEFAULT
243            CALL logger_debug( "IOM CLOSE: type "//TRIM(td_file%c_type))
244            CALL logger_error( "IOM CLOSE: can't close file "//&
245            &               TRIM(td_file%c_name)//": type unknown " )
246      END SELECT
247
248   END SUBROUTINE iom_close
249   !-------------------------------------------------------------------
250   !> @brief This function read attribute (of variable or global) in an opened
251   !> file, given variable name or standard name and attribute id.
252   !> @details
253   !>  - to get global attribute use 'GLOBAL' as variable name.
254   !
255   !> @author J.Paul
256   !> @date November, 2013 - Initial Version
257   !
258   !> @param[in] td_file      file structure
259   !> @param[in] cd_varname   variable name. use 'GLOBAL' to read global
260   !> attribute in a file
261   !> @param[in] id_attid     attribute id
262   !> @return  attribute structure
263   !-------------------------------------------------------------------
264   TYPE(TATT) FUNCTION iom__read_att_varname_id( td_file, cd_varname, &
265   &                                             id_attid)
266      IMPLICIT NONE
267      ! Argument
268      TYPE(TFILE),       INTENT(IN) :: td_file
269      CHARACTER(LEN=lc), INTENT(IN) :: cd_varname
270      INTEGER(i4),       INTENT(IN) :: id_attid
271
272      ! local variable
273      INTEGER(i4) :: il_varid
274      !----------------------------------------------------------------
275
276      ! get variable id
277      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
278         il_varid=NF90_GLOBAL
279      ELSE
280         il_varid=var_get_id(td_file%t_var(:), cd_varname)
281      ENDIF
282
283      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
284         ! open file
285         SELECT CASE(TRIM(td_file%c_type))
286            CASE('cdf')
287               iom__read_att_varname_id=iom_read_att( td_file, il_varid, &
288               &                                       id_attid)
289            CASE('dimg')
290               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
291               &              "in dimg file : "//TRIM(td_file%c_name) )
292            CASE DEFAULT
293               CALL logger_error( " IOM READ ATT: can't read attribute "//&
294               &    " in file "//TRIM(td_file%c_name)//" : type unknown " )
295         END SELECT
296      ENDIF
297
298   END FUNCTION iom__read_att_varname_id
299   !-------------------------------------------------------------------
300   !> @brief This function read attribute (of variable or global) in an opened
301   !> file, given variable id and attribute id.
302   !>
303   !> @author J.Paul
304   !> @date November, 2013 - Initial Version
305   !
306   !> @param[in] td_file   file structure
307   !> @param[in] id_varid  variable id. use NF90_GLOBAL to read global
308   !> attribute in a file
309   !> @param[in] id_attid  attribute id
310   !> @return  attribute structure
311   !-------------------------------------------------------------------
312   TYPE(TATT) FUNCTION iom__read_att_varid_id( td_file, id_varid, &
313   &                                            id_attid)
314      IMPLICIT NONE
315      ! Argument
316      TYPE(TFILE), INTENT(IN) :: td_file
317      INTEGER(i4), INTENT(IN) :: id_varid
318      INTEGER(i4), INTENT(IN) :: id_attid
319      !----------------------------------------------------------------
320
321      ! open file
322      SELECT CASE(TRIM(td_file%c_type))
323         CASE('cdf')
324            iom__read_att_varid_id=iom_cdf_read_att( td_file, id_varid, &
325            &                                         id_attid)
326         CASE('dimg')
327            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file "//&
328            &              TRIM(td_file%c_name) )
329         CASE DEFAULT
330            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
331            &               TRIM(td_file%c_name)//" : type unknown " )
332      END SELECT
333
334   END FUNCTION iom__read_att_varid_id
335   !-------------------------------------------------------------------
336   !> @brief This function read attribute (of variable or global) in an opened
337   !> file, given variable name or standard name, and attribute name.
338   !> @details
339   !> - to get global attribute use 'GLOBAL' as variable name.
340   !
341   !> @author J.Paul
342   !> @date November, 2013 - Initial Version
343   !
344   !> @param[in] td_file      file structure
345   !> @param[in] cd_varname   variable name or standard name. use 'GLOBAL' to read global
346   !> attribute in a file
347   !> @param[in] cd_attname   attribute name
348   !> @return  attribute structure   
349   !-------------------------------------------------------------------
350   TYPE(TATT) FUNCTION iom__read_att_varname_name( td_file, cd_varname, &
351   &                                                cd_attname)
352      IMPLICIT NONE
353      ! Argument
354      TYPE(TFILE),      INTENT(IN) :: td_file
355      CHARACTER(LEN=*), INTENT(IN) :: cd_varname
356      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
357
358      ! local variable
359      INTEGER(i4) :: il_varid
360      !----------------------------------------------------------------
361
362      ! get variable id
363      IF( TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
364         il_varid=NF90_GLOBAL
365      ELSE
366         il_varid=var_get_id(td_file%t_var(:), cd_varname)
367      ENDIF
368
369      IF( il_varid /= 0 .OR. TRIM(fct_upper(cd_varname)) == 'GLOBAL' )THEN
370         ! open file
371         SELECT CASE(TRIM(td_file%c_type))
372            CASE('cdf')
373               iom__read_att_varname_name=iom_cdf_read_att( td_file, il_varid, &
374               &                                             cd_attname)
375            CASE('dimg')
376               CALL logger_warn( " IOM READ ATT: can't read attribute "//&
377               &              "in dimg file :"//TRIM(td_file%c_name) )
378            CASE DEFAULT
379               CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
380               &               TRIM(td_file%c_name)//" : type unknown " )
381         END SELECT
382      ENDIF
383
384   END FUNCTION iom__read_att_varname_name
385   !-------------------------------------------------------------------
386   !> @brief This function read attribute (of variable or global) in an opened
387   !> file, given variable id and attribute name.
388   !
389   !> @author J.Paul
390   !> @date November, 2013 - Initial Version
391   !
392   !> @param[in] td_file      file structure
393   !> @param[in] id_varid     variable id. use NF90_GLOBAL to read global
394   !> attribute in a file
395   !> @param[in] cd_attname   attribute name
396   !> @return  attribute structure   
397   !-------------------------------------------------------------------
398   TYPE(TATT) FUNCTION iom__read_att_varid_name( td_file, id_varid, &
399   &                                              cd_attname)
400      IMPLICIT NONE
401      ! Argument
402      TYPE(TFILE), INTENT(IN) :: td_file
403      INTEGER(i4), INTENT(IN) :: id_varid
404      CHARACTER(LEN=*), INTENT(IN) :: cd_attname
405      !----------------------------------------------------------------
406
407      ! open file
408      SELECT CASE(TRIM(td_file%c_type))
409         CASE('cdf')
410            iom__read_att_varid_name=iom_cdf_read_att( td_file, id_varid, &
411            &                                           cd_attname)
412         CASE('dimg')
413            CALL logger_warn( " IOM READ ATT: can't read attribute in dimg file :"&
414            &              //TRIM(td_file%c_name) )
415         CASE DEFAULT
416            CALL logger_error( " IOM READ ATT: can't read attribute in file "//&
417            &               TRIM(td_file%c_name)//" : type unknown " )
418      END SELECT
419
420   END FUNCTION iom__read_att_varid_name
421   !-------------------------------------------------------------------
422   !> @brief This function read one dimension in an opened file,
423   !> given dimension id.
424   !
425   !> @author J.Paul
426   !> @date November, 2013 - Initial Version
427   !
428   !> @param[in] td_file   file structure
429   !> @param[in] id_dimid  dimension id
430   !> @return  dimension structure
431   !-------------------------------------------------------------------
432   TYPE(TDIM) FUNCTION iom__read_dim_id(td_file, id_dimid)
433      IMPLICIT NONE
434      ! Argument     
435      TYPE(TFILE), INTENT(IN) :: td_file
436      INTEGER(i4), INTENT(IN) :: id_dimid
437      !----------------------------------------------------------------
438
439      ! open file
440      SELECT CASE(TRIM(td_file%c_type))
441         CASE('cdf')
442            iom__read_dim_id=iom_cdf_read_dim(td_file, id_dimid)
443         CASE('dimg')
444            iom__read_dim_id=iom_rstdimg_read_dim(td_file, id_dimid)
445         CASE DEFAULT
446            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
447            &               TRIM(td_file%c_name)//" : type unknown " )
448      END SELECT     
449
450   END FUNCTION iom__read_dim_id
451   !-------------------------------------------------------------------
452   !> @brief This function read one dimension in an opened netcdf file,
453   !> given dimension name.
454   !
455   !> @author J.Paul
456   !> @date November, 2013 - Initial Version
457   !
458   !> @param[in] td_file   file structure
459   !> @param[in] cd_name   dimension name
460   !> @return  dimension structure
461   !-------------------------------------------------------------------
462   TYPE(TDIM) FUNCTION iom__read_dim_name(td_file, cd_name)
463      IMPLICIT NONE
464      ! Argument     
465      TYPE(TFILE),      INTENT(IN) :: td_file
466      CHARACTER(LEN=*), INTENT(IN) :: cd_name
467      !----------------------------------------------------------------
468
469      ! open file
470      SELECT CASE(TRIM(td_file%c_type))
471         CASE('cdf')
472            iom__read_dim_name=iom_cdf_read_dim(td_file, cd_name)
473         CASE('dimg')
474            iom__read_dim_name=iom_rstdimg_read_dim(td_file, cd_name)
475         CASE DEFAULT
476            CALL logger_error( " IOM READ DIM: can't read dimension in file "//&
477            &               TRIM(td_file%c_name)//" : type unknown " )
478      END SELECT     
479
480   END FUNCTION iom__read_dim_name
481   !-------------------------------------------------------------------
482   !> @brief This function read variable value in an opened
483   !> file, given variable id.
484   !> @details
485   !> start indices and number of indices selected along each dimension
486   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
487   !
488   !> @author J.Paul
489   !> @date November, 2013 - Initial Version
490   !
491   !> @param[in] td_file   file structure
492   !> @param[in] id_varid  variable id
493   !> @param[in] id_start  index in the variable from which the data values
494   !> will be read
495   !> @param[in] id_count  number of indices selected along each dimension
496   !> @return  variable structure
497   !-------------------------------------------------------------------
498   TYPE(TVAR) FUNCTION iom__read_var_id( td_file, id_varid,&
499   &                                     id_start, id_count)
500      IMPLICIT NONE
501      ! Argument     
502      TYPE(TFILE),                       INTENT(IN) :: td_file
503      INTEGER(i4),                       INTENT(IN) :: id_varid
504      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_start
505      INTEGER(i4), DIMENSION(ip_maxdim), INTENT(IN), OPTIONAL :: id_count
506      !----------------------------------------------------------------
507
508      ! open file
509      SELECT CASE(TRIM(td_file%c_type))
510         CASE('cdf')
511            iom__read_var_id=iom_cdf_read_var(td_file, id_varid, &
512            &                                 id_start, id_count)
513         CASE('dimg')
514            iom__read_var_id=iom_rstdimg_read_var(td_file, id_varid, &
515            &                                     id_start, id_count)
516         CASE DEFAULT
517            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
518            &               TRIM(td_file%c_name)//" : type unknown " )
519      END SELECT
520
521   END FUNCTION iom__read_var_id
522   !-------------------------------------------------------------------
523   !> @brief This function read variable value in an opened
524   !> file, given variable name or standard name.
525   !> @details
526   !> start indices and number of indices selected along each dimension
527   !> could be specify in a 4 dimension array (/'x','y','z','t'/)
528   !>
529   !> look first for variable name. If it doesn't
530   !> exist in file, look for variable standard name.<br/>
531   !
532   !> @author J.Paul
533   !> @date November, 2013 - Initial Version
534   !
535   !> @param[in] td_file   file structure
536   !> @param[in] cd_name   variable name or standard name
537   !> @param[in] id_start  index in the variable from which the data values
538   !> will be read
539   !> @param[in] id_count  number of indices selected along each dimension
540   !> @return  variable structure
541   !-------------------------------------------------------------------
542   TYPE(TVAR) FUNCTION iom__read_var_name(td_file, cd_name,   &
543   &                                      id_start, id_count  )
544      IMPLICIT NONE
545      ! Argument     
546      TYPE(TFILE)                   , INTENT(IN) :: td_file
547      CHARACTER(LEN=*)              , INTENT(IN) :: cd_name
548      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_start
549      INTEGER(i4)     , DIMENSION(:), INTENT(IN), OPTIONAL :: id_count
550      !----------------------------------------------------------------
551     
552      ! open file
553      SELECT CASE(TRIM(td_file%c_type))
554         CASE('cdf')
555            iom__read_var_name=iom_cdf_read_var(td_file, cd_name, &
556            &                                   id_start, id_count )
557         CASE('dimg')
558            iom__read_var_name=iom_rstdimg_read_var(td_file, cd_name, &
559            &                                   id_start, id_count )
560         CASE DEFAULT
561            CALL logger_error( " IOM READ VAR: can't read variable in file "//&
562            &               TRIM(td_file%c_name)//" : type unknown " )
563      END SELECT
564
565   END FUNCTION iom__read_var_name
566   !-------------------------------------------------------------------
567   !> @brief This subroutine write file structure in an opened file.
568   !>
569   !> @details
570   !> optionally, you could specify dimension order (default 'xyzt')
571   !>
572   !> @author J.Paul
573   !> @date November, 2013 - Initial Version
574   !> @date July, 2015 - add dimension order option
575   !
576   !> @param[in] td_file   file structure
577   !-------------------------------------------------------------------
578   SUBROUTINE iom_write_file(td_file, cd_dimorder)
579      IMPLICIT NONE
580      ! Argument     
581      TYPE(TFILE)     , INTENT(INOUT) :: td_file
582      CHARACTER(LEN=*), INTENT(IN   ), OPTIONAL :: cd_dimorder
583      !----------------------------------------------------------------
584
585      ! open file
586      SELECT CASE(TRIM(td_file%c_type))
587         CASE('cdf')
588            CALL iom_cdf_write_file(td_file, cd_dimorder)
589         CASE('dimg')
590            ! note: can not change dimension order in restart dimg file
591            CALL iom_rstdimg_write_file(td_file)
592         CASE DEFAULT
593            CALL logger_error( " IOM WRITE: can't write file "//&
594            &               TRIM(td_file%c_name)//" : type unknown " )
595      END SELECT
596
597   END SUBROUTINE iom_write_file
598END MODULE iom
599
Note: See TracBrowser for help on using the repository browser.